Marc's Place

DIBIOL/DBL - Statements


Voor mogelijke I/O statements bij de diverse OPEN modes, zie onderaan.

#      -  12345#2     > 123
##     -  12345##2    > 12300

.eq(s)(u)., etc..

"ABC" .eq.  "ABCD"  > true
"ABC" .eqs. "ABCD"  > false
"ABC" .eqs. "ABC"   > true

intgr = -1
intgr .eq.  -1     > true
intgr .equ. -1     > false
intgr .equ. 255    > true

.(b)and., etc..

int1 = %b(1010)
int2 = %b(0110)

int1 .band. int2  >  0010                   int1 .and. int2  >  1
int1 .bor.  int2  >  1110                   int1 .or.  int2  >  1
int1 .bxor. int2  >  1100                   int1 .xor. int2  >  0
     .bnot. int1  >  1001                        .not. int1  >  0
     .bnot. int2  >  0101                        .not. int2  >  0


ACCEPT

     ACCEPT inputs a character (or key sequence) from a terminal. ANSI Escape
     sequence processing is set by XCALL DBL$TTFLGS(1000). Use %RTERM after
     the statement when accepting chars in an alpha field. Key definitions are listed
     in the includefile "KEYDEFS" in library SYS$LIBRARY:DBLTEXT.TLB.

             ACCEPT (ch,field{,label}{,WAIT{:seconds}})

    keywords

          ch          is a numeric expression that evaluates to a channel
                      number as specified in a previous OPEN statement.

          field       is an alpha field, numeric field, or record which will
                      contain the character input from the terminal.

          label       is a statement label where control is to be transferred
                      when a CTRL/Z is detected.

          WAIT:seconds
                      is an integer expression which specifies the number of
                      seconds to wait for terminal input before generating a
                      timeout error.

BEGIN-END

     The BEGIN-END block is a sequence of statements preceded by BEGIN and
     followed by END. A BEGIN-END block may be used wherever a statement is
     valid.

             BEGIN
                  statement
                       .
                       .
                       .
             END

CALL

     CALL transfers program control to an internal subroutine.

             CALL label

CLEAR

     CLEAR sets variables to zeros or spaces.

             CLEAR field{,...}

CLOSE

     CLOSE terminates the use of a channel by closing the associated file
     and releasing both the I/O channel and the file buffer.

             CLOSE ch{,ch...}

COMMON

     COMMON defines the areas in memory where variable data is stored.
     This data is to be shared between the main program and external
     subroutines.

             {|EXTERNAL|} COMMON {name}{,X}{,NOSUFFIX}
              | GLOBAL |

DECR

     DECR decreases a numeric field by 1.

             DECR nvar

DELETE

     DELETE eliminates a record from an indexed file.

             DELETE (ch)

DETACH

     DETACH is ignored by VAX DIBOL.

             DETACH

DISPLAY

     DISPLAY outputs characters to a device or file

             DISPLAY (ch,|aexp|{<output field attributes>})
                                 |nexp|

    attributes

       Output field attributes apply to fields specified in DISPLAY or
       WRITES.

       {field}<{POS:({l}{,c})}{,VIDEO:flags}{,ERASE:code}{,FORMAT:mask}>

      POS

         POS:(l,c) positions the cursor at the location specified by l and c. L
         and c are integer expressions. l is the line number and c is the column
         number.

      VIDEO

         VIDEO:flags specifies the terminal video attribute. Assigned codes are:

                 1 - BLINK
                 2 - BOLD
                 4 - REVERSE
                 8 - UNDERSCORE

      ERASE

         ERASE:area specifies the area of the screen to be erased after the
         cursor is positioned. Assigned codes are:

                 1 - total screen
                 2 - cursor to end of screen
                 3 - all of line
                 4 - cursor to end of line

      FORMAT

         FORMAT:mask specifies a formatting mask to be used. assigned codes
         are:

                 C - Any character
                 X - Digit
                 Z - Zero-suppressed digit
                 * - Check-protected digit
                 money - Floating money sign
                 minus - Negative sign if at beginning or end else dash
                 decpt - Decimal point
                 digsp - Digit separator

DO-UNTIL

     DO-UNTIL repetitively executes a statement until a condition is true.

             DO statement UNTIL condition

EXIT

     EXIT terminates execution of a BEGIN-END block in a structured manner.

             EXIT {label}

EXITLOOP

     EXITLOOP allows a structured method of leaving a DO-UNTIL, WHILE, FOR, or
     REPEAT loop.

             EXITLOOP

EXTERNAL FUNCTION (zie FUNCTIONS)

     EXTERNAL FUNCTION declares a function to be user-defined and to have a
     specified data type.

             EXTERNAL FUNCTION
              name, t{.}
              ...

FIND (zie %RFA)

     FIND locates a specified record in a disk file and makes it the "current"
     record for a subsequent READS, WRITE, or DELETE operation.

             FIND (ch{|{,mval}{,KEYNUM:iexp}{,MATCH:iexp}|}{,WAIT{:seconds}})
                      |{RFA:rfaddr}                      |

      mval

         mval is used to find a record in an indexed file or the record to use
         in a FIND to a relative file.

      KEYNUM

         KEYNUM:iexp is an integer expression that specifies which key number is
         to be used in a FIND from an indexed file.

      MATCH

         MATCH:iexp is an integer expression that determines the type of match
         to use on this key lookup.

      RFA

         RFA:rfaddr is the alpha string containing the record file access value
         that evaluates to the "record number" field.

      WAIT

         WAIT:seconds is an integer expression that specifies the number of
         seconds to wait if a record locked condition occurs before generating a
         timeout error.

FLUSH

     FLUSH causes any pending disk writes to be completed on the specified
     channel.

            FLUSH ch

FOR

     FOR repetitively executes a statement until n field is equal to final.

             FOR nfield FROM initial THRU final {BY step} statement

FORMS

     FORMS outputs device-dependent codes to effect forms control.  These
     codes are normally used by printers.

             FORMS (ch,nexp)

        Valid values for nexp:

              1-255    Output specified number of line-feeds.
                  0    Output form-feed
                 -1    Output vertical tab character
                 -3    Output carriage-return character

FRETURN

     FRETURN returns control to the calling program that executed the function.

            FRETURN expression

FUNCTION

     FUNCTION identifies a program as a function definition.

             FUNCTION name {,%VAL}

GOTO

     An unconditional GOTO transfers program control.

             GOTO label

GOTO-Computed

     A computed GOTO transfers program control based on the evaluation of
     an expression.

             GOTO (label{,...}), nexp

GROUP

     GROUP defines a field within RECORD or COMMON and defines its subfields.

             GROUP name, {n}{t}{s}{,X}
                   {subfield definition}
             ENDGROUP

             n     is the dimensional field count. this can only be in the array
                   format:

              (real array)([n{,...}])

             t     is the data type (A,D,I,P). the default is alpha (A).

             s     is the size of each data element.

      RECORD
      GROUP STATE,            [50]A
                  NAME,             A20
                  PEOPLE,           D7
                  GROUP CAPITOL,          A
                              NAME,             A20
                              PEOPLE,           D7

      Access: STATE[1].NAME or STATE[1].CAPITOL.NAME

IF

     IF executes a statement if a condition is true.

             IF condition statement

IF-THEN-ELSE

     IF-THEN-ELSE executes 1 of 2 statements based on a condition.

             IF condition THEN statement1 ELSE statement2

INCR

     INCR increases a numeric field by 1.

             INCR nfield

LITERAL (zie Argument/Field definitions)

     LITERAL defines data literals that can be used in the Data or Procedure
     Division.

              | GLOBAL |
             {|EXTERNAL|} LITERAL
              | LOCAL  |

             name, t {*} {,value}
                     {n} %XTRNL (xxx)

LOCASE

     LOCASE converts uppercase characters to corresponding lowercase
     characters.

             LOCASE afield

LPQUE

     LPQUE queues a file to be printed by the printer spooler.

             LPQUE(filespec{,LPNUM:exp}{,COPIES:nexp}{,FORM:exp}{,DELETE}{,ALIGN})

    filespec

       filespec is an alpha field containing the name of the file to be
       printed.

    LPNUM

       LPNUM:exp is either a numeric or alpha expression that specifies the
       printer. When using a numeric expression the result must match a symbol
       DBL$LPx.

    COPIES

       COPIES:nexp is a numeric expression which specifies the number of copies
       to print.

    FORM

       FORM:exp is either a numeric or alpha expression that specifies the type
       or name of the form to be inserted into the printer before the file is
       printed.

    DELETE

       DELETE deletes the file after all copies have been printed.

    ALIGN

       ALIGN queues the file in a "hold" state so that the operator can take
       whatever action is necessary.

NEXTLOOP

     NEXTLOOP causes the next iteration of the current loop.

NOP

     NOP is the "null operation". It is used as a placeholder.

OFFERROR

     OFFERROR disables trapping of run-time errors.

             OFFERROR

ONERROR

     ONERROR enables trapping of run-time errors which would otherwise
     cause program termination.

             ONERROR label

OPEN

     OPEN associates a channel number with a device or with a file on a
     device.
     Voor mogelijke I/O statements bij de diverse OPEN modes, zie onderaan.

        OPEN (ch, mode{:submode}, filespec {,ALLOC:nexp}
                                           {,BKTSIZ:nexp}
                                           {,BLKSIZ:nexp}
                                           {,BUFNUM:nexp}
                                           {,BUFSIZ:nexp}
                                           {,CONTIG:nexp}
                                           {,DEQ:nexp}
                                           {,FDL:fdlstr}
                                           {,KEY:(keylist)}
                                           {,NUMREC:nexp})
                                           {,PROTECT:astr}
                                           {,RECSIZ:nexp}
                                           {,RECTYPE:nexp}
                                           {,SHARE:nexp}

    Modes

       Valid OPEN modes            Valid OPEN sub-modes

          I    Input                     S    Sequential
          O    Output                    R    Relative
          U    Update                    I    Indexed
          A    Append                    P    Print
                                         B    Block
                                         *    Wildcard

       The combinations indicated by the * are valid:

                Submode
                   S    R    I    P    B    *
    Mode      +-------------------------------+
         I    |    *    *    *         *    * |
         O    |    *    *    *    *    *      |
         U    |    *    *    *         *    * |
         A    |    *    *    *    *    *    * |
              +-------------------------------+

      ALLOC

         ALLOC:nexp is a numeric expression that specifies the initial or
         additional file allocation with dexp specifying the number of blocks to
         be initially allocated or added to a file.

      BKTSIZ

         BKTSIZ:nexp is a numeric expression that specifies the bucketsize in
         blocks.

      BLKSIZ

         BLKSIZ:nexp is a numeric expression that specifies the block size
         (bytes) of magnetic tape.

      BUFNUM

         BUFNUM:nexp is a numeric expression that specifies the number of
         process local I/O buffers to allocate.

      BUFSIZ

         BUFSIZ:nexp is a numeric expression that specifies the size of the
         transfer buffer in blocks for this channel.

      RECSIZ

         RECSIZ:nexp is a numeric expression that specifies the length (bytes)
         of the records in the file.

      CONTIG

         CONTIG:nexp is a numeric expression that specifies the desired
         contiguity of the file.

      DEQ

         DEQ:nexp is a numeric expression that specifies the default number of
         the blocks to add when a disk file is automatically extended.

      PROTECT

         PROTECT:astr is an alpha expression that specifies a file protection
         string.

      RECTYPE

         RECTYPE:nexp specifies the type of records that will be written to the
         file.

      SHARE

         SHARE:nexp is a numeric expression that specifies the type of file
         access allowed to this file by other programs or channels.

      FDL

         FDL:fdlstr is an alpha expression which specifies a File Description
         Language (FDL) string or file specification containing an FDL
         description.

      NUMREC

         NUMREC:nexp is a numeric expression that specifies the number of
         logical records in lengths as defined by RECSIZ that is to be used as
         the initial allocation of a file, or to be added to an existing file.

      KEY

         KEY:(keylist) represents a list of keys which describe the primary and
         alternate keys for an indexed file.

         The format for a keylist item is:

         (SEG:(POS:SIZE{,TYPE:ttt}{,ATTR:aaa}){,TYPE:TTT}{,ATTR:AAA})

         or

         (POS:SIZE{,TYPE:TTT}{,ATTR:AAA})

         SEG indicates segment-specific information to the compiler.

            aaa     indicates segment-specific attributes
            ttt     indicates the segment type
            AAA     indicates the "whole key" attributes
            TTT     indicates the "whole key" type

PROC-END (Zie .MAIN, .PROC en .END)

     PROC-END identifies the beginning and ending of the Procedure
     Division.

             PROC {dliteral}
                  statement
                       .
                       .
                       .
             {END}

READ-Relative-file (zie %RFA)

     READ inputs a record from a relative file.

             READ (ch,record|,nexp      |{,WAIT{:seconds}})
                            |,RFA:rfaddr|

    ch

       ch is a numeric expression that evaluates to a channel number as
       specified in a previous OPEN statement.

    record

       record is an alpha field or record which will contain the data.

    nexp

       nexp is a numeric expression that specifies the sequence number of the
       record to be read.

      WAIT

         WAIT:seconds is a numeric expression that specifies the number of
         seconds to wait if a record locked condition occurs.

      RFA

         RFA:rfaddr is an alpha string containing the record file access value
         that evaluates to the "record number" field.

READ-Indexed-file  (zie %RFA)

     READ inputs a record from an indexed file.

        READ (ch,record,|keyfld{,KEYNUM:nexp}{MATCH:nexp}|{,WAIT{:seconds}})
                        |RFA:rfaddr                      |

    ch

       ch is a numeric expression that evaluates to a channel number as
       specified in a previous OPEN statement.

    record

       record is an alpha field or record which will contain the data.

    keyfld

       keyfld is an alpha field or record that identifies the record to be read.

      WAIT

         WAIT:seconds is a numeric expression that specifies the number of
         seconds to wait if a record locked condition occurs.

      MATCH

         MATCH:nexp is a numeric expression that determines the type of match to
         use on this key lookup.

      KEYNUM

         KEYNUM:nexp is a numeric expression that specifies which key of
         reference is to be used.

      RFA

         RFA:rfaddr is an alpha string containing the record file access value
         that evaluates to the "record number" field.

READ-Sequential-File (zie %RFA)

     Read inputs a record from a sequential file by RFA.

          READ (ch,record,RFA:rfaddr)

    ch

       ch is a numeric expression that evaluates to a channel number as
       specified in a previous OPEN statement.

    record

       record is an alpha field or record which will contain the data.

      RFA

         RFA:rfaddr is an alpha string containing the record file access value
         that evaluates to the "record number" field.

READS

     READS inputs the next available record in sequence from a file, or
     requests input from a terminal.

                READS (ch,record{<input field attributes>}{,label}{,WAIT{:seconds})

      WAIT

         WAIT:seconds is a numeric expression which specifies the number of
         seconds to wait if a record locked condition or to wait for terminal
         input before generating a timeout error.

    attributes

       Input field attributes affect how the field is input.

         POS

         POS:(l,c) positions the cursor at the location specified by l and c. l
         is the line number and c is the column number.

         VIDEO

         VIDEO:vflags enables various terminal video attributes. These
         attributes (codes) may be added together to enable multiple attributes.
         Codes assigned are:

                 1 - BLINK
                 2 - BOLD
                 4 - REVERSE
                 8 - UNDERSCORE

          ERASE

         ERASE:code specifies the area of the screen to be erased after the
         cursor is positioned. Codes are:

                 1 - All the screen
                 2 - Cursor to end of screen
                 3 - All of line
                 4 - Cursor to end of the line

         EDIT

         EDIT:mask specifies an edit mask to be used for verification of input.
         mask is an alpha expression. Valid characters are:

            C - Any character             Y - Any alpha plus digit
            P - Any printable character   Space or 0 - DEFAULT string character
            A - Alpha                     N - Period, dash, plus sign, decimal
            U - Uppercase                 point, or numeric punctuation.
            L - Lowercase
            X - Digit

         DEFAULT

         DEFAULT:exp indicates the default value of the field if nothing input.

         FLAGS

         FLAGS:iexp enables/disables certain XCALL FLAGS settings. Codes may be
         added together to enable multiple FLAGS settings.

               1 = ECHO (enables ECHO)
               2 = NOECHO (disables ECHO)
               4 = AUTO (enables automatic termination)
               8 = NOAUTO (disables automatic termination)
              16 = UPCASE (specifies input is to be uppercased after entry)
              32 = NOUPCASE (specifies input is not to be uppercased after
                      entry)
              64 = TERMECHO (enables echo of READS terminator)
             128 = NOTERMECHO
             256 = TYPAHD (purges typeahead buffer before accepting input)
             512 = NOTYPAHD

         OFFSET

         OFFSET:nexp indicates the beginning character position within DEFAULT
         to start entering characters. If OFFSET is not specified, it defaults
         to length of DEFAULT.

         PROMPT

         PROMPT:aexp indicates a prompt string (aexp) to be output to the
         terminal before input is accepted.

RECORD

     RECORD defines the areas of memory where variable data is stored.

             RECORD {name}{,X}

REPEAT

     REPEAT repetitively executes a statment until a condition occurs to divert
     control out of that block.

           REPEAT statement

RECV

     RECV accepts a message which was sent by another program.

             RECV (message,label{,size})

RETURN

     RETURN transfers program control to the statement logically following
     the most recently executed CALL or XCALL statement.

             RETURN

SEND (zie ook %WAIT)

     SEND transmits a message to another program.

             SEND (message,program{,terminal})

SLEEP

     SLEEP suspends program execution for a specified period of time.
     Do not use in a DIBOL AST routine.

             SLEEP seconds

STOP

     STOP terminates program execution.

     If STOP is followed by an alpha field, the current program is terminated
     and a "chain" is performed to the program specified in the alpha field
     (filespec). If the first character of the filespec is an '@', it indicates
     that the filespec is a command file.

             STOP |status            |
                  |filespec          |
                  |@cmdfil           |
                  |@cmdfil prmtr-lst |
                  |$ dcl-cmd-ln      |
                  |nexp              |

     If STOP is followed by a numeric variable or expression, the current
     program is terminated and the numeric value is returned to the
     operating system as the program's exit status.

STORE

     STORE adds a record to an indexed file.

             STORE (ch,record)

SUBROUTINE

     SUBROUTINE identifies a program as an external subroutine.

             SUBROUTINE name

UNLOCK

     UNLOCK clears the lock condition on a specified channel.

             UNLOCK ch

UPCASE

     UPCASE converts lowercase characters to corresponding uppercase
     characters.

             UPCASE afield

USING

     USING conditionally executes one statement from a list of statements
     based on the evaluation of an expression.

             USING selection_value SELECT
                  ({match-expression{,...}}), statement
                       .
                       .
                       .
             ENDUSING

    Match-expression

       A match-expression takes one of the following forms:

               |value                 |
               |value THRU value      |
               |.LE.,.LEU.,.LES. value|
               |.LT.,.LTU.,.LTS. value|
               |.GE.,.GEU.,.GES. value|
               |.GT.,.GTU.,.GTS. value|

       Multiple match-expressions can be specified for each statement.
       An empty match-expression list matches any selection-value.
       No match will occur if the value to the left of THRU (low-value) is
       greater than the value to the right of THRU (high-value).
       The data types of the values within the match-expression must match
       the data type of the selection-value.

      Example

                 USING VAR SELECT
                      (M1),
                           RSLT = 5
                      (M4 THRU M9, M15, M20 THRU M30),
                           RSLT = 10
                      (),
                           BEGIN
                           DISPLAY (15,10,"NO MATCH",13)
                           CLEAR RSLT
                           END
                 ENDUSING

USING-RANGE

     USING with a specified range conditionally executes one statement from a
     list of statements based on the value of an expression.

             USING sexp RANGE low THRU high SELECT
             ({mexp{,...}}), statement
             .
             .
             .
             ENDUSING

    Match-expression

       mexp is one or more match expressions in the following format:

               compile-time-expression
               cte THRU cte
               .LT. cte
               .LE. cte
               .GT. cte
               .GE. cte

      Example

                 USING VAR RANGE 10 THRU 14 SELECT
                      (10), RSLT = 5
                      (11), RSLT = 10
                      (12), RSLT = 4
                      (13), RSLT = 17
                      (14), RSLT = 7
                      (%INRANGE), RSLT = 99
                      (%OUTRANGE), RSLT = 88
                 ENDUSING

WHILE

     WHILE repetitively executes a statement as long as a condition is
     true.

             WHILE condition statement

WRITE-Relative-file (zie %RFA)

     WRITE outputs a record into a specified position in a relative file.

             WRITE (ch,record|,nexp           |)
                                        |,RFA:rfaddr|

    ch

       ch is a numeric expression that evaluates to a channel number as
       specified in a previous OPEN statement.

    record

       record is an alpha field or record which will contain the data.

    nexp

       nexp is a numeric expression that specifies the sequence number of the
       record to be written.

    RFA

       RFA:rfaddr is an alpha string containing the record file access value or
       "record number" field.

WRITE-Indexed-file

     WRITE updates a record in an indexed file.

             WRITE (ch,record)

    ch

       ch is a numeric expression that evaluates to a channel number as
       specified in a previous OPEN statement.

    record

       record is an alpha field or record which will contain the data.

WRITE-Sequential-file (zie %RFA)

     WRITE updates a record in a sequential file.

             WRITE (ch,record,RFA:rfaddr)

    ch

       ch is a numeric expression that evaluates to a channel number as
       specified in a previous OPEN statement.

    record

       record is an alpha field or record which will contain the data.

    RFA

       RFA:rfaddr is an alpha string containing the record file access value or
       "record number" field.

WRITES

     WRITES outputs a record to the next available position in a file.

             WRITES (ch,record{<output attributes>})

    ch

       ch is a numeric expression that evaluates to a channel number as
       specified in a previous OPEN statement.

    record

       record is an alpha field or record which will contain the data.

    Attributes (see DISPLAY)

       WRITES output attributes add enhancements to the record. If the channel is
       not opened to a terminal, the escape sequences are inserted in the file.

XCALL

     XCALL transfers program control to an external program.

             XCALL name {(arg{,...})}

    %DESCR

       %DESCR causes the argument to be passed by descriptor.  This is the
       default passing mechanism for VAX DIBOL.

               XCALL subr (%DESCR(arg))

    %REF

       %REF causes the argument to be passed by reference.

               XCALL subr (%REF(arg))

    %VAL

       %VAL causes the argument to be passed by value.

               XCALL subr (%VAL(arg))

    %XTRNL

       %XTRNL causes the value of an externally-defined symbol to be passed.

                                  |+|
                                  |-||arg |
            XCALL subr %XTRNL(arg{|*||dlit|})
                                  |/|

XRETURN

     XRETURN transfers program control to the statement logically following the
     most recently executed XCALL statement.

     XRETURN {status}


Parameter schema ACCEPT, FIND, READ en READS:

                         mval    KEYNUM     MATCH    WAIT    RFA
                        -----------------------------------------
         mval             -         X         X       X       0
                        -----------------------------------------
         KEYNUM           X         -         X       X       0
                        -----------------------------------------
         MATCH            X         X         -       X       0
                        -----------------------------------------
         WAIT             X         X         X       -       X
                        -----------------------------------------
         RFA              0         0         0       X       -
                        -----------------------------------------


I/O schema:

          Sequential     Relative       Block          Indexed        Terminal   Printer  
          I  O  U  A     I  O  U  A     I  O  U  A     I  O  U  A     I  O       O        
reads     x  x  x  x     x  x  x  x     x  x  x  x     x  x  x  x     x  x
writes       x  x  x        x  x  x        x  x  x        x  x  x     x  x       x
read            x        x  x  x  x     x  x  x  x     x  x  x  x
write           x           x  x  x        x  x  x        x  x  x
delete                                                       x  x
store                                                     x  x  x
accept                                                                x  x
display      *                                                        x  x       x
forms        x  x  x                                                  x  x       x
find      x  x  x  x     x  x  x  x     x  x  x  x      x  x  x  x    x  x
flush        x  x  x        x  x  x        x  x  x         x  x  x 

*O:P only
© 1997- Marc Vos (and others)   -   Privacy Statement   -    Contact Me

On this website, Google Analytics is used to track visitor statistics. These are anonymised data about the number of visitors, which pages they visit on this site, from which regions they visit, which web browsers they use, etc.. You will also see non-personalised ads via Google AdSense. Cookies from Paddle or Paypal are placed when you click on a 'Buy now!' or 'Donate!' button, and possible cookies from Disqus when you use that system to comment on one or more blogposts.
Privacy Statement