next up previous contents index
Next: The Help File Up: Initializing SIC: Languages and Previous: Language Definition   Contents   Index

The command dispatching and handling

The dispatching routine is typically a big SELECT CASE based on the command name, like this one
subroutine run_clean (line,comm,error)
  use gbl_message
  !----------------------------------------------------------------------
  ! CLEAN Main routine
  !     Call appropriate subroutine according to COMM
  !----------------------------------------------------------------------
  character(len=*), intent(inout) :: line  ! Command line
  character(len=*), intent(in)    :: comm  ! Command name
  logical,          intent(out)   :: error ! Logical error flag
  !
  call map_message(seve%c,'CLEAN',line)
  !
  ! Analyze command
  select case (comm)
  case ('LOAD')
     call load_buffer(line,error)
  case ('READ')
     call read_image(line,error)
  case ('CLARK')
     call clark_clean(line,error)
  case ('FIT')
   ... etc...
  case default
     call map_message(seve%i,'CLEAN',comm//' not yet implemented')
  end select
  !
end subroutine run_clean

A handling routine for the a command looks like

      SUBROUTINE COM1(LINE,ERROR)
      CHARACTER*(*) LINE
      LOGICAL ERROR
      LOGICAL SIC_PRESENT
      INTEGER IARG1_OPT1
      REAL ARG1
!
! Test presence of option 1, and if so
!       Decode Argument 1 of this option with a default value
      IF (SIC_PRESENT(1,0)) THEN
          IARG1_OPT1 = 10
          CALL SIC_I4 (LINE,1,1,IARG1_OPT1,.FALSE.,ERROR)
          IF (ERROR) RETURN
          WRITE (6,*) 'Option 1 Set With Argument',IARG1_OPT1
      ENDIF
!
! Retrieves and decode first argument of the command
      CALL SIC_R4 (LINE,0,1,ARG1,.TRUE.,ERROR)
      IF (ERROR) RETURN
      WRITE (6,*) 'Command COM1 activated. ARG1',ARG1
! End of interface analysis, call a standard FORTRAN routine with
! all parameters now defined
      CALL SUB1(ARG1,ARG2,...,IARG1,...,ERROR)
      RETURN
      END
The command line buffer LINE must be passed by argument, never in a Module, to allow modularity and multi-language use.



Gildas manager 2014-07-01