Fortraneries/GrafAnim/usegenplot.f90

98 lines
2.2 KiB
Fortran

module usegenplot
implicit none
integer, private :: color = 4
logical, private :: initialised = .FALSE.
contains
! -------------------------------------------------------------------
subroutine init_genplot(filename)
character(*), intent(in) :: filename
write(0, *) '--> init genplot "', filename, '"'
initialised = .TRUE.
color = 4
end subroutine
subroutine end_genplot(message)
character(*), intent(in) :: message
write(0, *) '--> end genplot "', message, '"'
initialised = .FALSE.
end subroutine
! -------------------------------------------------------------------
subroutine do_initialise_once(motif)
character(*), intent(in) :: motif
write(0, *) '--> do initialise once "', motif, '", flag is ', initialised
call init_genplot('a.scratch')
end subroutine
! -------------------------------------------------------------------
subroutine gplt_setcol(col)
integer, intent(in) :: col
color = col
end subroutine
function gplt_getcol()
integer gplt_getcol
gplt_getcol = color
end function
! -------------------------------------------------------------------
subroutine gplt_move(x, y)
integer, intent(in) :: x, y
if (.NOT. initialised) then
call do_initialise_once('in gplt_move')
endif
print *, x, y, 0
end subroutine
! -------------------------------------------------------------------
subroutine gplt_draw(x, y)
integer, intent(in) :: x, y
if (.NOT. initialised) then
call do_initialise_once('in gplt_draw')
endif
print *, x, y, color
end subroutine
! -------------------------------------------------------------------
subroutine gplt_line(x1, y1, x2, y2)
integer, intent(in) :: x1, y1, x2, y2
call gplt_move(x1, y1)
call gplt_draw(x2, y2)
end subroutine
! -------------------------------------------------------------------
subroutine gplt_rect(x1, y1, x2, y2)
integer, intent(in) :: x1, y1, x2, y2
call gplt_move(x1, y1)
call gplt_draw(x2, y1)
call gplt_draw(x2, y2)
call gplt_draw(x1, y2)
call gplt_draw(x1, y1)
end subroutine
! -------------------------------------------------------------------
! -------------------------------------------------------------------
end module