You cannot select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

41 lines
1008 B
Fortran

SUBROUTINE backc(ient)
use winteracter
implicit none
include 'd.inc'
!
! Declare window-type and message variables
!
TYPE(WIN_STYLE) :: WINDOW
TYPE(WIN_MESSAGE) :: MESSAGE
INTEGER :: IW,IH,ihandle,ient,IHAND1,IHAND2,IXPM,IYPX,IXPX,IYPM,IRGB
common /hands/ iw,ih,ihandle,IHAND1,IHAND2,IXPM,IYPX,IXPX,IYPM
if(ient .eq. 1) then
iw=WinfoWindow(WindowWidth)
ih=WinfoWindow(WindowHeight)
WRITE(90,*) 'IW,IH',IW,IH
IF(IHANDLE .EQ. 0) THEN
IRGB = WRGB(220,220,220)
call WBitmapCreate(ihandle,iw,ih,irgb)
call IGrSelect(DrawBitmap,ihandle)
! CALL WBitmapPut(IHAND2,1,1,IXPM,IYPX,IXPX,IYPM)
ELSE
call IGrSelect(DrawBitmap,ihandle)
! CALL WBitmapPut(IHAND2,1,1,IXPM,IYPX,IXPX,IYPM)
ENDIF
return
else
call IGrSelect(DrawWin)
call WBitmapPut(ihandle,0,0)
call WBitmapDestroy(ihandle)
ihandle=0
endif
return
end