Modulefpreviousupnextcontents[BIG][Normal][small]
Next: 8.3 List of devices available Up: 8 Adapting a new terminal Prev: 8.1 Adapting a new input terminal Contents


8.2 Adapting a new output terminal

The link between FORTRAN 3D and the output terminals is made by two intermediary subroutines, PERFGN and ITRCTG.

Subroutine ITRCTG was presented in the previous section. Subroutine PERFGN serves as interface between the graphics software, FORTRAN 3D, and your basic device.

  
    PERFGN :
    ------


      SUBROUTINE PERFGN(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
      CHARACTER *(*)STRING
      REAL V1(*), V2(*), V3(*)
      INTEGER ICH(*)
      include 'data_f3d.ins'

      GOTO(1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11), IDEVIC
C     IF IDEVIC=0 ASSIGN THE NUMBER OF DEVICES TO ICH(1)
      IF(IDEVIC.EQ.0)THEN
C       ICH(1) = NUMBER OF DEVICES AVAILABLE
        ICH(1)=11
        RETURN
      ENDIF
      CALL PERIFX(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
      RETURN
001   CONTINUE
C         APOLLO
       CALL PERIF5(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
002   CONTINUE
C         LASER_WRITER(POST_SCRIPT)
       CALL PERIFD(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
003   CONTINUE
C         X_WINDOW_V11
       CALL PERIFX11(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
004   CONTINUE
C         TEKTRONIX_4014
       CALL PERIF1(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
005   CONTINUE
C         APOLLO_5
       CALL PERIF5(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
006   CONTINUE
C         PRINTER
       CALL PERIF7(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
007   CONTINUE
C         VERSATEK_SPECTRUM_V80
       CALL PERIF8(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
008   CONTINUE
C         VERSATEK_V80
       CALL PERIFC(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
009   CONTINUE
C         TEKTRONIX_4107
       CALL PERIFE(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
010   CONTINUE
C         TEKTRO_4105
       CALL PERIFN(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
011   CONTINUE
C         PHIGS
       CALL PERPHG(INSTRU, V1, V2, V3, I1, I2, I3, ICH, STRING)
       RETURN
       END

Note:
If you add or delete a terminal, do not forget to modify the values of ICH(1) (the number of terminals available) and the goto statement.

For an arbitrary driver, the parameters are:

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

To use a graphics terminal, which is not yet supplied on the MODULEF magnetic tape, the user needs to write program PERIF* (see below) and include a call to subroutine PERFGN 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')
          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 ICH(1), ICH(2), ... STRING
          return
        elseif(INSTRU.eq.-3)then
 c        default parameters (without dialogue) 
          ICH(1)=std   { affichage standard : plein ecran }
          ICH(2)=2     { couleur du fond}
          STRING='blabla'
          return
        endif
      endif
      call wchari(INSTRU, ' est une valeur incomprehensible')
      return
      GOTO indexe selon les valeurs >0 de INSTRU
      goto(1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,
     +     23,24,25,26,27,28,29,30,31,32,33,34,35), INSTRU

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

      INSTRU = 1 : INITIALIZATION OF THE TERMINAL   (DEVICE)
      ----------

         IN :  I1 : number of the active terminal
               ICH(*) and STRING : supplementary information
               for certain terminals
         All variables used are initialized by default
         (for example: line type, text size, ...).


      INSTRU = 2 : DEFINITION OF THE GRAPHIC CHARACTERISTICS  (LIGH3)
      ----------

         IN  : I1 : intensity (if >= 0 assign)
               I2 : blinking (0 no, 1 yes) (if >= 0 assign)
                    if stereo ( right=4  / left=2 )
               I3 : color number in the color table
                          (if >= 0 assign)


      INSTRU = 3 : DEFINITION OF LINES  (DRAW3)
      ----------

         IN  : I1   : line type (full, dotted ...)
                      define : type = I1
              if I1 < 0 no lines plotted  
              V1(1) : line thickness in mm. (if >= 0 assign)

      INSTRU = 4 : PLOT A LINE SEGMENT   (LIN2TO, LIN3TO, ...)
      ----------

         IN : V1(1) : abscissa of the beginning of the segment
              V1(2) : ordinate of the beginning of the segment
              V2(1) : abscissa of the end of the segment
              V2(2) : ordinate of the end of the segment
            if type < 0 no plot

      INSTRU = 5 : PLOT TEXT   (TXT2D, TXT3D,  ...)
      ----------
                 
         IN : I1     : number of characters in the text
              V1(1)  : abscissa of the beginning of the text
              V1(2)  : ordinate of the beginning of the text
              STRING : the text
            if type < 0 no plot
            if I1 = 1 and STRING(1:1) has a set
            of centerable characters ( O o X x + * 0 ) center
            the character.

      INSTRU = 6 : START OF A DESIGNATED ZONE  (DEBAS)
      ----------

         IN : I1 :  zone identifier


      INSTRU = 7 : END OF DESIGNATED ZONE  (FINAS)
      ----------


      INSTRU = 8 : TEXT PLOT CHARACTERISTICS   (DRW3TX)
      ----------

         IN : I1    : number of the character font available
                       i1=0 look for the font with the size 
                            closest to that chosen
                       i1#0 use font i1
              V1(1) : character size in cm.
              V2(1) : text angle w.r.t. the horizontal
                      (as a fraction of pi/2.)


      INSTRU = 9 : START OF A FACET   (DEBFAC)
      ----------

         IN : I1 : = 0 : external contour, 1 hole


      INSTRU = 10 : END OF FACET   (FINFAC)
      ----------

         plot the facet


      INSTRU = 11 : CLEAR SCREEN    (CLEAN)
      ----------

         all existing plots are deleted


      INSTRU = 12 : DISPLAY OF A SEGMENT. HIGHLIGHT (DSPLAY, HIGHLT)
      ----------

         I1 : 0 = normal display
              1 = highlight (blinking ...)
         ICH(1) = segment number


      INSTRU = 13 :  OPENING A SEGMENT  (OPENG)
      ----------

         ICH(1) = segment number

                 a segment represents a sequence of graphical 
                 instructions defined between openg and closeg.


      INSTRU = 14 :  CLOSING A SEGMENT  (CLOSEG)
      ----------


      INSTRU = 15 :  KILL A SEGMENT  (KILL)
      ----------

         ICH(1) = segment number


      INSTRU = 16 :  REMOVE A SEGMENT  (REMOVG)
      ----------

         ICH(1) = segment number


      INSTRU = 17 :  INQUIRE SCREEN SIZE  (SZSCRN)
      ----------

         OUT : V1(1) = abscissa of the lower left-hand corner in cm.
               V1(2) = its ordinate in cm.
               V1(3) = abscissa of the upper right-hand corner in cm.
               V1(4) = its ordinate in cm.
         The screen is thus defined in cm.


      INSTRU = 18 :  INQUIRE IF SEGMENT EXISTS  (INQEXS)
      ----------

         IN  : ICH(1)= segment number
         OUT : I2= 0 if the segment exists, 1 if not


      INSTRU = 19 :  LIST OF EXISTING SEGMENTS  (INQNXS)
      ----------

         IN : I1 = 1  initialization of the search
              I1 = 0  request next segment number
         OUT : if I1 = 0
               I2 = 0 if there is a next segment
                      ICH(1) number of this segment
               I2 -= 0 if there is no segment following


      INSTRU = 20 :  UPDATE SCREEN  (UPDATE)
      ----------


      INSTRU = 21 :  END, CLOSE DEVICE  (ENDDEV)
      ----------

         IN : I1 : terminal number


      INSTRU = 22 :  GO TO STEREO MODE  (STEREO)
      ----------

         IN: I1=1 (on) I1=0 (off)
         OUT: I2 =0 stereo
              I2-=0 no stereo


      INSTRU = 23 :  CURRENT COLOR  (INQCOL)
      ----------

         OUT : V1(1), V2(1), V3(1) reals between 0. and 1. giving R G B
               (proportion of Red, Green, Blue)


      INSTRU = 24 :  SET CURRENT COLOR  (SETCOL)
      ----------
 
         IN  : set the current color equal to the value in the array
               closest to (V1(1), V2(1), V3(1)


      INSTRU = 25 :  NUMBER OF COLORS  (INBCOL)
      ----------


         OUT : I1 : number of colors possible
                    (background color and at least the other : I1 >= 2)


      INSTRU = 26 :  DEFINE THE COLOR ARRAY   (SETTBC)
      ----------

         IN  : Set V1(1:), V2(1:), V3(1:) [0...1] in the color array
               between indices I1 and I2 inclusive.
               Indices I1 and I2 varies from 0 to nbcolo-1. 
         OUT : I3 = 0 assignment performed
               I3 = -1 table not modifiable


      INSTRU = 27 :  NUMBER OF COLORS  AND ARRAY   (INQTBC)
      ----------

         OUT : returns in V1(1:), V2(1:), V3(1:) [0...1] 
               the current color array between the indices I1 and
               I2 inclusive.
               Indices I1 and I2 varies from 0 to nbcolo-1.


      INSTRU = 28 :  HARD CLIP FOR TEXT   (CLIPHD)
      ----------

         IN  : V1(1)  min in x of the zone, in cm.
               V1(2)  max in x
               V1(3)  min in y
               V1(4)  max in y
               I1 = 1 clip, 0 if not


      INSTRU = 29 :  SELECTIVE DELETION  (INQFAC)
      ----------

         OUT : I1 : 0 if selective deletion is possible, 1 if not


      INSTRU = 30 :  EXISTENCE OF INPUT  (INQCUR)
      ----------

         OUT : I1 : 0 if there is input at the cursor (or other),
               1 if not
               If there is input we keep the same terminal number
               (see ITRCTG : adapting to a new input terminal)


      INSTRU = 31 :  MAXIMUM TEXT QUALITY  (INQMQT)
      ----------

         OUT : I1 =0 if the maximum text quality is HARD  
                     (le text soft est plus mauvais que le hard)
                  =1 if the maximum text quality is SOFT



      INSTRU = 32 :  TEXT CENTERING  (CTRTXT)
      ----------

         IN  : V1(1) = alpha   position in a box (0., 0.) (1., 1.)
               V1(2) = beta    of the center of the text in x (alpha)
                               and y (beta) : alpha and beta between 0. et 1.
               By default alpha = beta = 0.
          

      INSTRU = 33 : INQUIRE MAXIMUM NUMBER OF SEGMENTS MANAGED  (INQSGM)
      ----------

         OUT :  I1 = maximum number of segments managed (0 = none)
      if i1 >0 this signifies that ALL instructions are managed correctly:
                                   ===
                   12   DSPLAY
                   13   OPENG
                   14   CLOSEG
                   15   KILL
                   16   REMOVG
                   18   INQEXS
                   19   INQNXS
                    


       INSTRU = 34 : RETURN THE NUMBER OF THE CURRENT COLOR   (INQNCO)
      ----------

         OUT :  I1 = number of current color
                  


       INSTRU = 35 : hardcopy   (HARDCP)
      ----------
          IN: I1 = choix1  (if different hardcopy terminals)
              I2 = choix2  (if different material possibilities)

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, PEREXE, residing in library perf-example can serve as a model when creating the output 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.3 List of devices available Up: 8 Adapting a new terminal Prev: 8.1 Adapting a new input terminal Contents