49 lines
1.4 KiB
Fortran
49 lines
1.4 KiB
Fortran
|
|
module centermag
|
|
implicit none
|
|
!-----------------------------------------------------------------------
|
|
! 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 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
|