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.

50 lines
1.1 KiB
Fortran

!IPK NEW ROUTINE SEP 9 2006
SUBROUTINE ADJUSTOPT(NTYP,NLOCC)
!
! Generate continuity lines
!
USE WINTERACTER
include 'd.inc'
!
! Declare window-type and message variables
!
TYPE(WIN_STYLE) :: WINDOW
TYPE(WIN_MESSAGE) :: MESSAGE
integer :: NTYP,NLOCC
call wdialogload(IDD_SETOPT)
ierr=infoerror(1)
CALL WDialogSelect(IDD_SETOPT)
ierr=infoerror(1)
IF(NTYP .EQ. 1) THEN
call wdialogputRadioButton(idf_radio1)
ELSE
call wdialogputRadioButton(idf_radio2)
ENDIF
call wdialogputcheckbox(IDF_check1,NLOCC)
CALL WDialogShow(-1,-1,0,Modal)
ierr=infoerror(1)
do
!
IF (WInfoDialog(ExitButton) .EQ. IDOK) THEN
call wdialoggetradiobutton(idf_radio1,ntyp)
call wdialogGetcheckbox(IDF_check1,NLOCC)
GO TO 100
ENDIF
enddo
100 CONTINUE
return
end