Modulefpreviousupnextcontents[BIG][Normal][small]
Next: 8.2 Adapting a new output terminal Up: 8 Adapting a new terminal Prev: 8 Adapting a new terminal Contents


8.1 Adapting a new input terminal

The link between FORTRAN 3D and the input terminals is made through two intermediary subroutines PERFGN and ITRCTG.

Subroutine PERFGN will be defined in the next section. Subroutine ITRCTG is constructed as follows:

  ITRCTG :
  ------

      SUBROUTINE ITRCTG(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
      CHARACTER *(*)STRING
      REAL T1(*), T2(*), T3(*)
      INTEGER IT1(*), IT2(*), IT3(*)
      include 'data_f3d.ins'

      GOTO(1 , 2, 3, 4, 5, 6, 7, 8, 9, 10 , 11), IDEVIN 
C
      CALL  ITRCTX(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
      RETURN
001   CONTINUE
C         APOLLO
       CALL ITRCT5(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
002   CONTINUE
C         LASER_WRITER(POST_SCRIPT)
       CALL  ITRCTX(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
003   CONTINUE
C         X_WINDOW_V11
       CALL ITRCTX11(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
004   CONTINUE
C         TEKTRONIX_4014
       CALL ITRCT1(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
005   CONTINUE
C         APOLLO_5
       CALL ITRCT5(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
006   CONTINUE
C         PRINTER
       CALL  ITRCTX(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
007   CONTINUE
C         VERSATEK_SPECTRUM_V80
       CALL  ITRCTX(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
008   CONTINUE
C         VERSATEK_V80
       CALL  ITRCTX(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
009   CONTINUE
C         TEKTRONIX_4107
       CALL ITRCTE(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
010   CONTINUE
C         TEKTRO_4105
       CALL ITRCTN(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
011   CONTINUE
C         PHIGS
       CALL ITRPHG(INSTRU, T1, T2, T3, IT1, IT2, IT3, STRING)
       RETURN
       END

Note:
If you add or delete a terminal, do not forget to modify the goto statement.

For an arbitrary driver, the parameters are:

The use of these variables depends on INSTRU (see below).

To use a graphics terminal, which is not yet offered on the MODULEF magnetic tape, the user needs to write program ITRCT* (see below) and include a call to subroutine ITRCTG in it.

Parameter INSTRU has very particular effects if it is negative:

      if(INSTRU.lt.0)then {interrogation du device}
        if(   INSTRU.eq.-1)then
   c      print on i1= number of order
          call wchari(i1, 'PERIPHERIQUE XXX en entree')
          return
        elseif(INSTRU.eq.-2)then 
   c        definition of the call parameters with dialogue
   c        we assign, using dialogue, the call parameters
   c        that we store in IT2(1), IT2(2), ... STRING
          return
        elseif(INSTRU.eq.-3)then 
   c      default parameters (without dialogue) 
          IT2(1)=std   { type standard du curseur }
          return
        endif
      endif
      call wchari(INSTRU, ' est une valeur incomprehensible en entree')
      return
      GOTO indexe selon les valeurs >0 de INSTRU
      goto(1, 2, 3, 4, 5, 6, 7, 8, 9), INSTRU

The different tasks to be performed, referenced by INSTRU, are described below:

      INSTRU = 1 : INITIALIZATIONS OF THE INPUT TERMINAL   (DEVICI)
      ----------

         IN :  IT1 : number of the active terminal
               IT2(*) and STRING : supplementary information for 
               certain terminals
         Initialize the values of the keys whose names are in
         key_board.ins
c     key values for APOLLO
      bs=char(8)
      cr=char(13)
      lf=char(10)
      del=char(127)
      mark=char(129)
      line_del=char(130)
      char_del=char(131)
      marg_left=char(132)
      cmd=char(133)
      marg_right=char(134)
      pad_left=char(135)
      curs_down=char(136)
      pad_right=char(137)
      curs_left=char(138)
      next_window=char(139)
      curs_right=char(140)
      pad_up=char(141)
      curs_up=char(142)
      pad_down=char(143)
      pop=char(144)
      again=char(145)
      exit=char(148)
      back_space=char(149)
      return=char(150)
      funct1=char(192)
      funct2=char(193)
      funct3=char(194)
      funct4=char(195)
      funct5=char(196)
      funct6=char(197)
      funct7=char(198)
      funct8=char(199)
      funct9=char(187)
      funct10=char(0)
      funct11=char(0)
      funct12=char(0)
      shell=char(205)
      copy=char(232)
      tpast=char(233)
      grow=char(234)
      hold=char(235)
      cut=char(236)
      undo=char(237)
      move=char(238)
      help=char(239)
c     with shift
      funct0=char(186)
      sfunct0=char(190)
      sfunct1=char(208)
      sfunct2=char(209)
      sfunct3=char(210)
      sfunct4=char(211)
      sfunct5=char(212)
      sfunct6=char(213)
      sfunct7=char(214)
      sfunct8=char(215)
      sfunct9=char(191)
      sfunct10=char(0)
      sfunct11=char(0)
      sfunct12=char(0)
      smarg_right=char(206)
      spad_left=char(207)
      scurs_down=char(216)
      spad_right=char(217)
      scurs_left=char(218)
      snext_window=char(219)
      scurs_right=char(220)
      spad_up=char(221)
      scurs_up=char(222)
      spad_down=char(219)
      sagain=char(181)
      sread=char(182)
      spop=char(200)

      INSTRU = 2 : INPUT A POSITION   (GETXY)
      ----------

         OUT  : T1(1) :  X in cm.
                T2(1) :  Y in cm.


      INSTRU = 3 : INPUT A POSITION AND ENTER A CHARACTER (GETXYC)
      ----------

         OUT  : T1(1) :  X in cm.
                T2(1) :  Y in cm.
                STRING(1:1) the character entered


      INSTRU = 4 : INPUT A BROKEN LINE  (STROKE)
      ----------

         IN   : IT1(1) number of points to input
                IT1(2) constraint
                       0 : no constraint
                       1 : 2 successive points on the curve input
                         are separated by a minimum of T3(1) cm. and
                         a maximum of T3(2) cm.

         OUT  : IT2(1) number of points actually input
                T1(*) : array containing the abscissas in cm.
                T2(*) : array containing the coordinates in cm.


      INSTRU = 5 : INPUT A TEXT (GETEXT)
      ----------

         IN : T1(1) : X in cm. of the beginning of the text
              T2(1) : Y in cm. of the beginning of the text
              STRING(1:IT1(1)) : the non-editable text to print
              IT1(1) : number of characters in the non-editable text
                       to print
              IT2(1) : maximum number of characters
              IT3(1) : number of characters in the initial editable text
              STRING(IT1(1)+1:IT1(1)+IT3(1)) : initial editable text

         OUT : T3(1) : X in cm. of the end of the text
               T3(2) : Y in cm. of the end of the text
               IT3(1) : number of characters input
               STRING(IT1(1)+1 : IT1(1)+IT3(1)) : text input


      INSTRU = 6 : INPUT A NUMBER  (GETNUM)
      ----------

         IN : T1(1) : X in cm. of the beginning of the text
              T2(1) : Y in cm. of the beginning of the text
              STRING(1:IT1(1)) : the text to print
              IT1(1) : number of characters in the text to print
              IT2(1) : type  of number (0 integer, 1 real, 2 boolean)
              IT2(2) : constraint
                       0 : no constraint
                       1 : min  and max constraints for the numbers:
                       the constraints are stored in:
                           T3(1)=min and T3(2)=max for reals
                           IT3(1)=min and IT3(2)=max for integers
         OUT  : depending on type:
              IT3(3) the integer or boolean (0=.TRUE., 1=.FALSE.) number
              T3(3)  the real number

         If the user types (return) the variables are not modified on exit.


      INSTRU = 7 : INPUT AN IDENTIFICATION  (GETHIT)
      ----------

         OUT : IT1(1) : number of the designated segment 
               IT1(2) : associated value
                     ( value given by debas(*)  if not -1 )      


      INSTRU = 8 : DIMENSION OF THE INPUT SURFACE  (SZSCRI)
      ----------

         OUT : T1(1) : Xmin in cm.
               T1(2) : Xmax in cm.
               T1(3) : Ymin in cm.
               T1(4) : Ymax in cm.
  

      INSTRU = 9 : INQUIRY OF THE NUMBER OF MOUSE KEYS (INQCRC)
      ----------
         OUT : IT1(1) : number of keys on the mouse
               IT2(*) : the integer codes of the keys or 0 if undefined code

Inspired by the programs already proposed, we define the different actions as a function of the possibilities offered by the graphics terminal at our disposal.

The fictitious subroutine, ITREXE, residing in library perf-example can serve as a model when creating the input program for a new device.

In addition, a certain number of subroutines were written to aid with a quick implementation of the drivers (see chapter 7 and the index):

 

      GETUNF     RCHARS      RINTG
      RREAL      CHARI       WCHARS
      ZCENTR     ZCOLOR      ZFNDTC
      ZGNUM      ZGTEXT      ZSTROK
      ZTXT


Modulefpreviousupnextcontents[BIG][Normal][small]
Next: 8.2 Adapting a new output terminal Up: 8 Adapting a new terminal Prev: 8 Adapting a new terminal Contents