Fortraneries/Modules/centermag.f90

68 lines
2.0 KiB
Fortran

module centermag
implicit none
!-----------------------------------------------------------------------
!-
! By definition, the default centermax (0, 0, 1) give us a
! (-1,-1), (1, 1) box, who is mapped to the screen size.
!-
!-----------------------------------------------------------------------
! definition of structures
!-
type t_centermag
integer :: wscr, hscr ! "physycal" screen size
real :: mag = 1.0 ! magnitude factor
real :: cx, cy ! the center
integer :: flag = 0
end type
!-------------------------------------------------------------------
contains
!-------------------------------------------------------------------
subroutine init_centermag(cntmag, w, h, mag)
type(t_centermag),intent(out) :: cntmag
integer, intent(in) :: w, h ! screen size
real, intent(in) :: mag
write(0, *) ">>> init centermag:", w, h
cntmag%wscr = w ; cntmag%hscr = h
cntmag%mag = mag
end subroutine
!-------------------------------------------------------------------
subroutine print_centermag (cm)
type(t_centermag), intent(in) :: cm
print *, "Screen ", cm%wscr, cm%hscr
print *, "MagFactor ", cm%mag
! print *, "Center ", cm%cx, cm%cy
end subroutine
!-------------------------------------------------------------------
!-------------------------------------------------------------------
subroutine centermag_scr2real (sx, sy, rx, ry)
integer, intent(in) :: sx, sy
real, intent(out) :: rx, ry
print *, 'from scr :', sx, sy
rx = 999.999
ry = 666.666
end subroutine
!-------------------------------------------------------------------
subroutine centermag_real2scr (rx, ry, sx, sy)
real, intent(in) :: rx, ry
integer, intent(out) :: sx, sy
print *, 'from real :', rx, ry
sx = -1
sy = -1
end subroutine
!-------------------------------------------------------------------
end module