PROGRAM LANDER USE F2KCLI USE FTCL CHARACTER(256) :: LINE CHARACTER(256) :: EXE CHARACTER(40) :: CMD INTEGER :: NARG,IARG NARG = COMMAND_ARGUMENT_COUNT() WRITE(unit=*,fmt=*) "Arg count=", NARG CALL GET_COMMAND(LINE) WRITE(unit=*,fmt=*) "Line=",TRIM(LINE) ! CALL GET_COMMAND_ARGUMENT(0,EXE) WRITE(unit=*,fmt=*) "Program=",TRIM(EXE) ! CALL ftcl_start('/zvfs/config.tcl', EXE) ! Fetch constants defined in Tcl script CALL ftcl_get_int('impulse', impulse) CALL ftcl_get_real('ht', fheight) CALL ftcl_get_real('speed', speed) CALL ftcl_get_real('fuel', fuel) CALL ftcl_get_real('gross', gross) i = 0; DO WHILE (fheight .GT. 0) irdy = 0 CALL ftcl_put_int('ready', irdy) CALL ftcl_script('wait4click') ! The Tcl burn variable now contains the amount of ! fuel to burn CALL ftcl_get_real('burn', burn) ! If we're out of fuel, no burn. IF (fuel .LE. 0) THEN fuel = 0 burn = 0 CALL ftcl_put_real('burn', burn) ENDIF ! Calculate the speed CALL CALCSPEED (speed, fuel, gross, burn, impulse, speed) ! Update the local variables i = i + 1 fuel = fuel - burn fheight = fheight - speed ! Update the Tcl variables CALL ftcl_put_int('time', i) CALL ftcl_put_real('speed', speed) CALL ftcl_put_real('fuel', fuel) CALL ftcl_put_real('ht', fheight) ! CALL ftcl_script('showState') ENDDO DO WHILE (1 .EQ. 1) CALL ftcl_script('update') ENDDO END SUBROUTINE CALCSPEED (finit, fuel, gross, burn, impulse, speed) mass = gross + fuel CALL ftcl_get_real('gravity', g) speed = speed + g - (impulse * log(mass/(mass-burn))) END