VMS Help
FORTRAN, Format Specifiers

 *Conan The Librarian (sorry for the slow response - running on an old VAX)

  A FORMAT statement specifies the format in which data is to be
  transferred and the conversion (editing) required to achieve that
  format.  FORMAT statements are nonexecutable statements used with
  formatted I/O statements, ASSIGN statements, and with ENCODE and
  DECODE statements.

  Fields defined by a FORMAT statement can contain variable format
  expressions.  A variable format expression is an integer variable
  or expression enclosed in angle brackets that takes the place of an
  integer constant.  The value of the variable or variables can
  change during program execution.

  1 - Default Field Descriptors

  Default field descriptor values are as follows:

  Field
  Descriptor    List Element               w      d       e
  ----------------------------------------------------------
  I,O,Z         BYTE,INTEGER*1,LOGICAL*1   7
  I,O,Z         INTEGER*2,LOGICAL*2        7
  I,O,Z         INTEGER*4,LOGICAL*4       12
  O,Z           REAL*4                    12
  O,Z           REAL*8                    23
  O,Z           REAL*16                   44
  O,Z           CHARACTER*n               MAX(7,3*n)
  L             LOGICAL*1,LOGICAL*2,       2
                LOGICAL*4
  F,E,G,D       REAL,COMPLEX*8            15      7       2
  F,E,G,D       REAL*4,COMPLEX*16         25      16      2
  F,E,G,D       REAL*16                   42      33      3
  A             LOGICAL*1                  1
  A             LOGICAL*2,INTEGER*2        2
  A             LOGICAL*4,INTEGER*4        4
  A             REAL*8,COMPLEX*8           8
  A             REAL*8,COMPLEX*16          8
  A             REAL*16                   16
  A             CHARACTER*n                n

  2 - General Form

  The general form of a FORMAT statement is as follows:

     FORMAT (q1 f1s1 f2s2 ... fnsn qn)

     qn   Is zero or more slash (/) record terminators.
     fn   Is a field descriptor, an edit descriptor, or
          a group of field and edit descriptors enclosed
          in parentheses.
     sn   Is a field separator (a comma or slash).  A
          comma can be omitted in the following cases:

          o Between a P edit descriptor and an immediately
            following F, E, D, or G edit descriptor.

          o Before or after a slash (/) record terminator.

          o Before or after a colon (_:) edit descriptor.

  The "field descriptor" has one of the following forms:

     [r]c  [r]cw  [r]cw.m  [r]cw.d[Ee]

     r    Is the optional repeat count.  (If you omit "r",
          the repeat count is assumed to be 1.)
     c    Is a format code (I,O,Z,F,E,D,G,L, or A).
     w    Is the external field width in characters.  Each
          data item in the external medium is called an
          external field.
     m    Is the minimum number of characters that must appear
          in the field (including leading zeros).
     d    Is the number of characters to the right of the decimal point.
     E    Is an exponent field.
     e    Is the number of characters in the exponent.

  A group of field descriptors can be formed by enclosing a format
  specifier in parentheses and optionally preceding the group with a
  repeat count (defaults to 1).  Separate a group from other format
  specifiers or groups with field separators or record terminators.
  Groups can be nested to a depth of 8.

  The entire format specifier must be enclosed in parentheses.

  The ranges for "r", "w", "m", "d", and "e" are as follows:

  Term      Range
  ----      __________
   r        1 to 32767 (2**15-1)
   w        1 to 32767
   m        0 to 255 (2**8-1)
   d        0 to 255
   e        1 to 255

  The "d" and "e" terms are required in some field descriptors and
  are invalid in others.

  The terms must all be unsigned integer constants or variable format
  expressions.

  You cannot use PARAMETER constants for "r", "w", "m", "d", or "e".

  The "edit descriptor" has one of the following forms:

     c  [n]c  c[n]

     c     Is a format code (X,T,TL,TR,SP,SS,S,BN,BZ,P,H,Q,'...'
           $, or :).
     n     Is the optional number of characters or character
           positions.

  The term "n" must be an unsigned integer constant (for format code
  P, it can be signed or unsigned) or a variable format expression.

  The value of "n" for P must be within the range -128 to 127.

  For all other format codes, the value of "n" must be within the
  range 1 through 32767 (2**15-1); above 32767, you receive an error.
  Actual useful ranges can be constrained by record sizes (RECL) and
  the file system.

  3 - Format Descriptors

  A format descriptor can be one of the following:

     Field descriptor -- Defines the size and format of a data
     item.  Each field descriptor corresponds to the next data
     item in the statement's I/O list.

     Edit descriptor  --  Specifies editing functions to be
     performed on data items.

  Format descriptors are generally separated by commas, but you can
  also use the slash (/) record terminator to separate them.  A slash
  terminates input or output of the current record and initiates a
  new record; for example:

          WRITE (6,40) K,L,M,N,O,P
     40   FORMAT (3I6.6/I6,2F8.4)

  The preceding statements are equivalent to the following:

          WRITE (6,40) K,L,M
     40   FORMAT (3I6.6)
          WRITE (6,50) N,O,P
     50   FORMAT (I6,2F8.4)

  Multiple slashes cause the system to bypass input records or output
  blank records.  If "n" consecutive slashes appear between two field
  or edit descriptors, (n-1) records are skipped on input, or (n-1)
  blank records are output.  The first slash terminates the current
  record.  The second slash terminates the first skipped or blank
  record, and so on.

  However, "n" slashes at the beginning or end of a format
  specification result in "n" skipped or blank records.  This is
  because the opening and closing parentheses of the format
  specification are themselves a record initiator and terminator,
  respectively.

  4 - Repeat Count

  You can apply the field descriptors I, O, Z, F, E, D, G, L, and A
  to a number of successive data fields by preceding the field
  descriptor with an unsigned integer constant (PARAMETER constants
  are not allowed) specifying the number of repetitions.  This
  constant is called a repeat count.

  For example, the following two statements are equivalent:

    20 FORMAT (E12.4,E12.4,E12.4,I5,I5,I5,I5)
    20 FORMAT (3E12.4,4I5)

  Similarly, you can apply a group of field descriptors repeatedly to
  data fields by enclosing these field descriptors in parentheses and
  preceding them with an unsigned integer constant.  The integer
  constant is called a group repeat count.  For example, the
  following two statements are equivalent:

    50 FORMAT (I8,I8,F8.3,E15.7,F8.3,E15.7,F8.3,E15.7,I5,I5)
    50 FORMAT (2I8,3(F8.3,E15.7),2(I5))

  An H or Q field descriptor, which could not otherwise be repeated,
  can be enclosed in parentheses and treated as a group repeat
  specification.

  5 - Reversion

  When the last closing parenthesis of the format specification is
  reached, format control determines whether more I/O list elements
  are to be processed.  If not, format control terminates.  However,
  if additional list elements remain, part or all of the format
  specification is reused in a process called format reversion.

  In format reversion, the current record is terminated, a new one is
  initiated, and format control reverts to the group repeat
  specification whose opening parenthesis matches the next-to-last
  closing parenthesis of the format specification.  If the format
  does not contain a group repeat specification, format control
  returns to the initial opening parenthesis of the format
  specification.  Format control continues from that point.

  6 - Variable Format Expressions

  By enclosing an expression in angle brackets, you can use it in a
  FORMAT statement wherever you can use an integer (except as the
  specification of the number of characters in the H field).  For
  example:

    20 FORMAT (I<J+1>)

  When the format is scanned, the preceding statement performs an
  integer (I) data transfer with a field width of J+1.  The
  expression is reevaluated each time it is encountered in the normal
  format scan.

  The following rules apply to variable format expressions:

     - If the expression is not of integer data type, it is
       converted to integer data type before being used.
     - The expression can be any valid Fortran expression,
       including function calls and references to dummy arguments.
     - The value of a variable format expression must obey the
       restrictions on magnitude applying to its use in the
       format, or an error occurs.
     - Variable format expressions are not permitted in run-time
       formats.

  Variable format expressions are evaluated each time they are
  encountered in the scan of the format.  If the value of the
  variable used in the expression changes during the execution of the
  I/O statement, the new value is used the next time the format item
  containing the expression is processed.

  7 - Field

  Field descriptors:
    +-----------------------------------+
    |      Function      |  Format      |
    +--------------------+--------------+
    | Integer            | Iw[.m]       |
    | Real number        | Fw.d         |
    | Exponential form   | Ew.d[Ee]     |
    | D exponential form | Dw.d         |
    | G exponential form | Gw.d[Ee]     |
    | Character          | A[w]         |
    | Logical            | Lw           |
    | Hexadecimal        | Zw[.m]       |
    | Octal              | Ow[.m]       |
    +--------------------+--------------+

  NOTE:  Transfer complex numbers as two real (F, E, D, or G) numbers.

  8 - Edit

  Edit descriptors:
    +--------------------------+--------------+
    |         Function         |   Format     |
    +--------------------------+--------------+
    | Character constant       | 'characters' |
    | Hollerith                | nHchar...    |
    | Scale factor             | nP           |
    | Blanks are null (input)  | BN           |
    | Blanks are zero (input)  | BZ           |
    | Input size               | Q            |
    | Plus sign (always)       | SP           |
    | Plus sign (never)        | SS           |
    | Default plus sign        | S            |
    | Skip spaces (same as TRn)| nX           |
    | Position (Tab)           | Tn           |
    | Relative left tab        | TLn          |
    | Relative right tab       | TRn          |
    | Carriage control         | $            |
    | Terminate list           | :            |
    +--------------------------+--------------+

  9 - 'characters'

  You can use a character constant instead of an H field descriptor.
  Both types of format specifiers function identically.

  On input, this specifier transfers the specified characters from
  the external field.

  On output, this specifier transfers the specified characters to the
  record.

  10 - Carriage Control

  When the first character of a formatted record is transferred to an
  output file or printer, it can be interpreted as a carriage control
  character (and not printed) if the file is opened with
  CARRIAGECONTROL='FORTRAN' in effect.

  The I/O system recognizes the characters listed below as carriage
  control characters and does not print them.

     Character    Meaning
     ---------    -----------------------------------------
       '+'        Overprinting: Outputs the record (at the
                  beginning of the current line) and a
                  carriage return.

       ' '        One line feed: Outputs the record (at the
                  beginning of the following line) and a
                  carriage return.

       '0'        Two line feeds: Outputs the record (after
                  skipping a line) and a carriage return.

       '1'        Next page: Outputs the record (at the
                  beginning of a new page) and a carriage
                  return.

       '$'        Prompting: Outputs the record (at the
                  beginning of a new page), but no carriage
                  return.

     ASCII NULL   Overprinting with no advance: Outputs
                  the record (at the beginning of the current
                  line), but no carriage return. (ASCII NULL
                  is specified as CHAR(0).)

  Any character other than those listed above is interpreted as a
  space and is deleted from the print line.  If you accidentally omit
  a carriage control character, the first character of the record is
  not printed.

  11 - $

  (Carriage Control Editing)

  In a format specification, the dollar sign character ($) modifies
  the carriage control specified by the first character of the
  record.  It only affects the files for which the 'FORTRAN' carriage
  control attribute is in effect.

  In an input statement, the $ descriptor is ignored.

  In an output statement, the following rules apply:

     - If the first character of the record is 0, 1, or
       ASCII NUL, the $ descriptor is ignored.

     - If the first character of the record is a space or
       plus sign (+), the $ descriptor suppresses carriage
       return (after printing the record).

  For terminal I/O, whenever trailing carriage return control is
  suppressed by the $ descriptor, a typed response follows output on
  the same line.

  12 - :

  (Format Control)
  Terminates the I/O operation if no more items remain in the I/O
  list.

  13 - A

  A[w] (Character Editing)

  If the corresponding I/O list element has a character data type,
  character data is transmitted.  If it has any other data type,
  Hollerith data is transmitted.  The value of "w" must be less than
  or equal to 32767.

  On input, transfers "w" characters or Hollerith values from the
  external record and assigns them to the corresponding list element.
  If the input value contains fewer characters than "w", it is padded
  on the right with blanks.  If the input value contains excessive
  characters, it is truncated on the left.

  If the variable is numeric, the ASCII value of each character is
  placed in each byte of the variable, starting at the low-order
  byte.

  On output, transfers the contents of the corresponding I/O list
  element to an external field "w" characters long.  If the output
  value contains fewer characters than "w", it is padded on the left
  with blanks.  If the output value contains excess characters, it is
  truncated on the right (for numbers, the high-order bytes are
  lost).

  If the output value is numeric or untyped, the ASCII value of each
  byte of the variable, starting at the low-order byte, is
  transferred to the record.

  The "w" can be omitted and defaults to the number of characters in
  the character variable or the number of bytes in the numeric
  variable.

  14 - BN

  (Blank Control Editing)

  Causes embedded and trailing blanks to be ignored within a numeric
  input field.  Leading blanks are always ignored, and an all blank
  field is always treated as zero.  The BN descriptor must precede
  all field descriptors to which it applies.

  It affects all following I, O, Z, F, E, D, and G editing (in the
  same FORMAT statement) during the execution of an output statement.

  If the OPEN statement is not used or it is used and BLANK='ZERO' is
  specified, blanks are converted to zeros.  If the OPEN statement is
  used and either BLANK='NULL' is specified or the BLANK keyword is
  omitted, blanks are ignored.

  15 - BZ

  (Blank Control Editing)

  Causes embedded and trailing blanks to be treated as zeros within a
  numeric input field.  (Leading blanks are always ignored.) The BZ
  descriptor must precede all field descriptors to which it applies.

  It affects all following I, O, Z, F, E, D, and G editing (in the
  same FORMAT statement) during the execution of an output statement.

  If the OPEN statement is not used or it is used and BLANK='ZERO' is
  specified, blanks are converted to zeros.  If the OPEN statement is
  used and either BLANK='NULL' is specified or the BLANK keyword is
  omitted, nonleading blanks are treated as zeros.

  An all blank field is always treated as zero.

  16 - D

  Dw.d
  (Exponential Editing)

  On input, performs the same as F format.

  On output, performs the same as E format, except that the letter D
  replaces the letter E preceding the exponent and the size of the
  exponent is fixed at 2.

  17 - E

  Ew.d[Ee] (Exponential Editing)

  On input, performs the same as F format.

  On output, E transfers the value of the corresponding I/O list
  element, rounded to "d" decimal digits and right-justified to an
  external field "w" characters long.  "d" specifies the size of the
  fraction and "e" specifies the size of the exponent.  If the value
  does not fill the field, leading spaces are inserted; if the value
  is too large for the field, the entire field is filled with
  asterisks.

  The term "w" must be large enough to include all the following:  a
  minus sign (when necessary) or a plus sign (if SP editing is in
  effect), a zero, a decimal point, "d" digits, and an exponent.

  Therefore, to accommodate all possible components of the standard
  form, the term "w" must be greater than or equal to "d"+7; if "e"
  is present, "w" must be greater than or equal to "d"+"e"+5.

  However, "w" can be as small as "d"+5 or "d"+"e"+3 and still allow
  formatting of the value without error, if optional fields are
  omitted.  In this case, the sign is omitted (if the value is
  positive and SP editing is not in effect) and the zero to the left
  of the decimal point is also omitted, if necessary.

  18 - F

  Fw.d (Fixed Floating Editing)

  On input, transfers "w" characters from the external field and
  assigns them, as a real value, to the corresponding I/O list
  element (which must be real data type).  If the first nonblank
  character of the external field is a minus sign, the field is
  treated as a negative value.  If the first nonblank character is a
  plus sign or if no sign appears in the field, the field is treated
  as a positive value.

  If the field contains neither a decimal point nor an exponent, it
  is treated as a real number of w digits, in which the rightmost "d"
  digits are to the right of the decimal point, with leading zeros
  assumed if necessary.  If the field contains an explicit decimal
  point, the location of the decimal point overrides the location
  specified by the field descriptor.  If the field contains an
  exponent, that exponent is used to establish the magnitude of the
  value before it is assigned to the list element.

  On output, transfers the value of the corresponding I/O list
  element, rounded to "d" decimal positions and right-justified, to
  an external field that is "w" characters long.  If the value does
  not fill the field, leading spaces are inserted; if the value is
  too large for the field, the entire field is filled with asterisks.

  The term "w" must be large enough to include all the following:  a
  minus sign (when necessary) or a plus sign (if SP editing is in
  effect), at least one digit to the left of the decimal point, a
  decimal point, and "d" digits to the right of the decimal.

  Therefore, "w" must be greater than or equal to "d"+3.

  19 - G

  Gw.d[Ee] (General Floating Editing)

  On input, performs the same as F format.

  On output, transfers the value of the corresponding I/O list
  element, rounded to d decimal positions, and right-justified, to an
  external field that is "w" characters long.  The form in which the
  value is written is a function of the magnitude of the value.  as
  given below:

   Data Magnitude             Effective Conversion
   --------------             --------------------
          m < 0.1             Ew.d[Ee]
   0.1 <= m < 1.0             F(w-4).d, n(' ')
   1.0 <= m < 10.0            F(w-4).(d-1), n(' ')
        .                       .
        .                       .
        .                       .
   10**d-2 <= m < 10**d-1     F(w-4).1, n(' ')
   10**d-1 <= m < 10**d       F(w-4).0, n(' ')
         m >= 10**d           Ew.d[Ee]

  The term "w" must be large enough to include all the following:  a
  minus sign (when necessary) or a plus sign (if SP editing is in
  effect), a decimal point, one digit to the left of the decimal
  point, "d" digits to the right of the decimal, and either a
  4-character or "e"+2-character exponent.

  Therefore, "w" must be greater than or equal to "d"+8.  If "e" is
  present, "w" must be greater than or equal to "d"+"e"+6.

  20 - H

  nHc1c2c2...cn (Hollerith Editing)

  On input, transfers "n" characters from the external record to the
  field descriptor itself.  The first character appears immediately
  after the H.  Any characters in the field descriptor before the
  input operation are replaced by the input characters.

  On output, transfers "n" characters following the letter H from the
  field descriptor to the external field.

  21 - I

  Iw[.m] (Integer Editing)

  On input, transfers "w" characters from the external field and
  assigns them, as an integer value, to the corresponding I/O list
  element (which must be integer or logical data type).  The external
  data must have the form of an integer constant; it cannot contain a
  decimal point or exponent field.

  If the first nonblank character of the external field is a minus
  sign, the field is treated as a negative value.  If the first
  nonblank character is a plus sign or if no sign appears in the
  field, the field is treated as a positive value.

  On output, transfers the value of the corresponding I/O list
  element, right-justified, to an external field that is w characters
  long.  If the value does not fill the field, leading spaces are
  inserted; if the value is too large for the field, the entire field
  is filled with asterisks.  "w" must be large enough to include a
  possible minus sign.  If "m" is present, the external field
  consists of at least "m" digits and, if necessary, is zero filled
  on the left.

  22 - L

  Lw (Logical Editing)

  On input, transfers "w" characters from the external field and
  assigns a logical value to the corresponding I/O list element
  (which must be integer or logical data type).  If the first
  nonblank characters of the field are T, t, .T, or .t, the value
  .TRUE. is assigned to the corresponding I/O list element; if the
  first nonblank characters are F, f, .F, or .f, the value .FALSE. is
  assigned.  An all blank field is assigned the value .FALSE.  Any
  other value in the external field produces an error.  The logical
  constants .TRUE. and .FALSE. are acceptable input forms.

  On output, transfers either the letter T (if the value of the
  corresponding I/O list element is .TRUE.) or the letter F (if the
  value is .FALSE.) to an external field that is w characters long.
  The letter T or F is in the rightmost position of the field,
  preceded by w-1 spaces.

  23 - O

  Ow[.m] (Octal Editing)

  On input, transfers "w" characters from the external field and
  assigns them, as an octal value, to the corresponding I/O list
  element (which can be any data type).  The external field can
  contain only the numerals 0 though 7; it cannot contain a sign, a
  decimal point, or exponent field.  An all blank field is treated as
  a value of zero.  If the value of the external field exceeds the
  range of the corresponding list element, an error occurs.

  On output, transfers the octal value of the corresponding I/O list
  element, right-justified, to an external field that is "w"
  characters long.  No signs are transmitted; a negative value is
  transmitted in internal form.  If the value does not fill the
  field, leading spaces are inserted; if the value is too large for
  the field, the entire field is filled with asterisks.  If "m" is
  present, the external field consists of at least "m" digits and, if
  necessary, is zero filled on the left.

  "w" must be large enough to include a possible minus sign.  If "m"
  is present, the external field consists of at least "m" digits and,
  if necessary, is zero filled on the left.

  24 - P

  nP (Scale Factor Editing)

  The scale factor lets you alter, during input or output, the
  location of the decimal point both in real values and in the two
  parts of complex values.

  The "n" is a signed or unsigned integer constant, in the range -128
  to 127, that specifies the number of positions to the left or right
  that the decimal point is to move.

  A scale factor can appear anywhere in a format specification, but
  must precede the first F, E, D, or G field descriptor that is to be
  associated with it and affects all following real field descriptors
  in the same FORMAT statement (unless another scale factor appears.

  On input the scale factor of any of the F, E, D, and G field
  descriptors multiplies the data by 10**-n and assigns it to the
  corresponding I/O list element.  For example a 2P scale factor
  multiplies an input value by .01; a -2P multiplies an input value
  by 100.  However, if the external field contains an explicit
  exponent, the scale factor has no effect.

  E, D, or G field descriptors alter the form in which data is
  transferred.  On input a positive scale factor moves the decimal
  point to the left and a negative scale factor moves the decimal
  point to the right; on output, the effect is the reverse.

 24.1 - F field descriptor

  nPFw.d

  On output, the value of the I/O list element is multiplied by 10**n
  before transfer to the external record.  Thus, a positive scale
  factor moves the decimal point to the right; a negative scale
  factor moves the decimal point to the left.  Thus, the F field
  descriptor alters the magnitude of the data.

 24.2 - E field descriptor

  nPEw.d

  On output, the basic real constant part of the I/O list element is
  multiplied by 10**n, and "n" is subtracted from the exponent.  For
  a positive scale factor, "n" must be less than (d+2) or an output
  conversion error occurs.  Thus, a positive scale factor moves the
  decimal point to the right and decreases the exponent; a negative
  scale factor moves the decimal point to the left and increases the
  exponent.

 24.3 - D field descriptor

  nPDw.d

  On output, the basic real constant part of the I/O list element is
  multiplied by 10**n, and "n" is subtracted from the exponent.  For
  a positive scale factor, "n" must be less than (d+2) or an output
  conversion error occurs.  Thus, a positive scale factor moves the
  decimal point to the right and decreases the exponent; a negative
  scale factor moves the decimal point to the left and increases the
  exponent.

 24.4 - G field descriptor

  nPGw.d

  On output, the effect for the G field descriptor is suspended if
  the magnitude of the data to be output is within the effective
  range of the descriptor (because the G field descriptor supplies
  its own scaling function).  It functions as an E field descriptor
  if the magnitude of the data is outside its range.  In this case,
  the scale factor has the same effect as for the E field descriptor.

  25 - Q

  (Query Remaining Character Count)

  On input, obtains the number of characters remaining in the input
  record to be transferred during a read operation.  The following
  example uses the Q descriptor to determine the size of the input
  record:

     READ(5,'(Q,A)') LEN, REC(1:LEN)

  On output, the Q descriptor has no effect, except that the
  corresponding I/O item is skipped.

  26 - S

  (Normal Signing)

  Restores the option of producing plus characters (+) in numeric
  output fields.  The S descriptor counters the action of either the
  SP or SS descriptor by restoring to the processor the discretion of
  producing plus characters on an optional basis.

  This descriptor affects fields all that follow it, until an SP or
  SS is encountered.  The S descriptor affects all following I, F, E,
  D, and G editing (in the same FORMAT statement) during the
  execution of an output statement.

  27 - SP

  (Always + Signs)

  Causes the processor to produce a leading plus character (+) in any
  position where this character would otherwise be optional.

  This descriptor affects all (suppress + signs) fields that follow
  it, until an S or SS is encountered.  The SP descriptor affects all
  following I, F, E, D, and G editing (in the same FORMAT statement)
  during the execution of an output statement.

  28 - SS

  (Suppress Sign)

  Causes the processor to suppress a leading plus character from any
  position where this character would otherwise be optional.  It has
  the opposite effect of the SP field descriptor.

  The SS descriptor affects all following I, F, E, D, and G editing
  (in the same FORMAT statement) during the execution of an output
  statement.  This descriptor affects all fields that follow it,
  until an S or SS is encountered.

  29 - T

  Tn (Tab to Position n)

  On input, starts the next read operation at the character position
  (within the record) indicated by position(n).  For example, if an
  input statement reads a record containing:

     ABC   XYZ

  and this record is under the control of the FORMAT statement:

     10 FORMAT (T7,A3,T1,A3)

  On execution, the input statement would first read the characters
  XYZ and then read the characters ABC.

  On output, starts the next write operation at the character
  position n in the external record.

  The position specified must be an integer in the range 1 through
  the size of the record.

  30 - TL

  TLn (Tab Left n Positions)

  Indicates that the next character to be transferred to or from a
  record is the "n"th character to the left of the current character.

  The value of "n" must be greater than or equal to 1.

  If the value of "n" is greater than or equal to the current
  character position, the first character in the record is specified.

  31 - TR

  TRn (Tab Right n Positions)

  Indicates that the next character to be transferred to or from a
  record is the "n"th character to the right of the current
  character.

  The value of "n" must be greater than or equal to 1.

  32 - X

  nX (Skip Right n Positions)

  The X field descriptor functions the same as the TR field
  descriptor.

  On input, starts the next read operation after skipping "n"
  character positions.  If X is the last format item, it will have no
  effect.

  On output, starts the next write operation after skipping the "n"
  character positions.  Intervening characters are not written over.
  If X is the last format code executed, it will have no effect.

  The position specified must be an integer in the range 1 through
  the size of the record.

  33 - Z

  Zw[.m] (Hexadecimal Editing)

  On input, transfers w characters from the external field and
  assigns them, as a hexadecimal value, to the corresponding I/O list
  element (which can be any data type).  The input value must be in
  the form of a hexadecimal constant.  Each input character
  corresponds to four bits in the variable, high order to low order.
  If the input value contains more characters than specified by "w",
  an error occurs.  If the input value contains fewer characters, it
  is padded with zeros on the left before being converted.

  On output, transfers the number of hexadecimal characters specified
  by "w" from a variable or constant to the record.  The rightmost
  characters represent the low-order bits.  If the variable or
  constant contains more characters than "w" specifies, the value is
  set to all asterisks (an error occurs).  If the variable or
  constant contains fewer characters, the value is padded on the left
  with spaces.  "m" specifies the minimum number of characters (with
  zero padding) that the value can contain.  "m" must be an integer
  in the range 1 through 255.  "w" must be large enough to include a
  possible minus sign.  If "m" is present, the external field
  consists of at least "m" digits and, if necessary, is zero filled
  on the left.
  Close     HLB-list     TLB-list     Help  

[legal] [privacy] [GNU] [policy] [netiquette] [sponsors] [FAQ]
Tweet
Polarhome, production since 1999.
Member of Polarhome portal.