VMS Help  —  FORTRAN  Format Specifiers
  A format appearing in an input or output (I/O) statement specifies
  the form of data being transferred and the data conversion
  (editing) required to achieve that form.  The format specified can
  be explicit or implicit.

  Explicit format is indicated in a format specification that appears
  in a FORMAT statement or a character expression (the expression
  must evaluate to a valid format specification).

  The format specification contains edit descriptors, which can be
  data edit descriptors, control edit descriptors, or string edit
  descriptors.

  Implicit format is determined by the processor and is specified
  using list-directed or namelist formatting.

  List-directed formatting is specified with an asterisk (*);
  namelist formatting is specified with a namelist group name.

  List-directed formatting can be specified for advancing, sequential
  files and internal files.  Namelist formatting can be specified
  only for advancing, sequential files.

1  –  Default Data Descriptors

  The defaults for data edit descriptors follow:

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

2  –  General Form

  The general form of a FORMAT statement follows:

     FORMAT (q1 f1s1 f2s2 ... fnsn qn)

     qn   Is zero or more slash (/) record terminators.

     fn   Is a data edit descriptor, a control edit descriptor, or
          a group of data or control 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, EN, ES, D, or G edit descriptor.

          o Before a slash (/) record terminator (if there is
            no optional repeat specification)

          o After a slash (/) record terminator.

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

  In data transfer I/O statements, a format specifier ([FMT=]format)
  can be a character expression that is a character array, character
  array element, or character constant.  This type of format is also
  called a run-time format because it can be constructed or altered
  during program execution.

  The expression must evaluate to a character string whose leading
  part is a valid format specification (including the enclosing
  parentheses).  Variable format expressions must not appear in this
  kind of format specification.

2.1  –  Data Edit Format

  A data edit descriptor takes one of the following forms:

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

     r    Is an optional repeat count.  (If you omit "r",
          the repeat count is assumed to be 1.)

     c    Is a format code (I,B,O,Z,F,E,EN,ES,D,G,L, or A).

     w    Is the total number of digits in the field (the
          field width).

     m    Is the minimum number of digits that must appear
          in the field (including leading zeros).

     d    Is the number of digits to the right of the decimal point.

     E    Identifies an exponent field.

     e    Is the number of digits in the exponent.

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

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

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

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

2.2  –  Control Edit Format

  A control edit descriptor takes one of the following forms:

     c  nc  cn

     c     Is a format code (X, T, TL, TR, SP, SS, S, BN, BZ,
           P, /, '...', "...", Q, \, $, or :).

     n     Is an optional number of character positions.

  The term "n" must be a positive, unsigned, integer constant or a
  variable format expression.

  For all format codes (except P), the value of "n" must be within
  the range 1 through 2147483647 (2**31-1); actual useful ranges may
  be constrained by record sizes (RECL) and the file system.

  The P edit descriptor is an exception to the general control edit
  descriptor syntax.  It is preceded by a scale factor, rather than a
  character position specifier.  The value of "n" for P must be
  within the range -128 to 127.

  Control edit descriptors can be grouped in parentheses and preceded
  by a group repeat specification.

2.3  –  Character String Format

  The character string edit descriptors are the character constant
  and H edit descriptor.

  The character constant edit descriptor ('string' or "string")
  causes string to be output to an external record.  (For more
  information on the H edit descriptor, see FORMAT H in online Help.)

  Although no string edit descriptor can be preceded by a repeat
  specification, a parenthesized group of string edit descriptors can
  be preceded by a repeat specification.

3  –  Format Descriptors

  A format descriptor can be one of the following:

   o  Data edit descriptor

      Causes the transfer or conversion of data to or from its
      internal representation.  The part of a record that is input or
      output and formatted with data edit descriptors a field.

      The data edit descriptors are:  I, B, O, Z, F, E, EN, ES, D, G,
      L, and A.

   o  Control edit descriptor

      Either directly determines how text is displayed or affects the
      conversions performed by subsequent data edit descriptors.

      The control edit descriptors are:  T, TL, TR, X, S, SP, SS, BN,
      BZ, P, :, /, $, and Q.

   o  String edit descriptor

      Controls the output of character strings.  The string edit
      descriptors are the character constant and H edit descriptor.

  Format descriptors are generally separated by commas, but you can
  also use the slash (/) edit descriptor 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  –  Nested and Group Repeats

  Format specifications can include nested format specifications
  enclosed in parentheses; for example:

    15   FORMAT (E7.2,I8,I2,(A5,I6))

    35   FORMAT (A6,(L8(3I2)),A)

  A group repeat specification can precede a nested group of edit
  descriptors.  For example, the following statements are equivalent,
  and the second statement shows a group repeat specification:

    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),2I5)

  If a nested group does not show a repeat count, a default count of
  1 is assumed.

  Normally, the string edit descriptors and control edit descriptors
  cannot be repeated (except for slash), but any of these descriptors
  can be enclosed in parentheses and preceded by a group repeat
  specification.  For example, the following statements are valid:

    76   FORMAT ('MONTHLY',3('TOTAL'))

    100  FORMAT (I8,4(T7),A4)

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 I
  (integer) 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 can also be used in character format
  specifications.

  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  –  Data Edit

  The specific forms for data edit descriptors follow:

    +-----------------------------------+
    |      Function      |  Format      |
    +--------------------+--------------+
    | Integer            | Iw[.m]       |
    | Binary             | Bw[.m]       |
    | Octal              | Ow[.m]       |
    | Hexadecimal        | Zw[.m]       |
    | Real number        | Fw.d         |
    | Exponential form   | Ew.d[Ee]     |
    | D exponential form | Dw.d         |
    | G exponential form | Gw.d[Ee]     |
    | Scientific form    | ESw.d[Ee]    |
    | Engineering form   | ENw.d[Ee]    |
    | Logical            | Lw           |
    | Character          | A[w]         |
    +--------------------+--------------+

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

8  –  Control Edit

  The specific forms for control edit descriptors follow:

    +--------------------------+--------------+
    |         Function         |    Format    |
    +--------------------------+--------------+
    | Scale factor             | kP           |
    | Blanks are null (input)  | BN           |
    | Blanks are zero (input)  | BZ           |
    | Characters in input      | 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         | $ or \       |
    | Terminate list           | :            |
    | Terminate record         | /            |
    +--------------------------+--------------+

9  –  String Edit

  The specific forms for string edit descriptors follow:

    +--------------------------+--------------+
    |         Function         |    Format    |
    +--------------------------+--------------+
    | Character constant       |  'string'    |
    |                          |      or      |
    |                          |  "string"    |
    | Hollerith                |  nHstring    |
    +--------------------------+--------------+

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
                  current position in 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 the following line), but no
                  carriage return.

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

  Any other character is interpreted as a blank 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  –  $_or_\

  In a format specification, the dollar sign ($) and backslash (\)
  characters modify the carriage control specified by the first
  character of the record.  They only affect carriage control for
  formatted files, and have no effect on input.

  If the first character of the record is a blank or a plus sign (+)
  the dollar sign and backslash descriptors suppress carriage return
  (after printing the record).

  For terminal device I/O, when this trailing carriage return is
  suppressed, a response follows output on the same line.

  If the first character of the record is 0, 1, or ASCII NUL, the
  dollar sign and backslash descriptors have no effect.

12  –  :

  Terminates format control if no more items are in the I/O list.

  If I/O list items remain, the colon edit descriptor has no effect.

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 2**31-1.

  The G edit descriptor can be used to edit character data; it
  follows the same rules as Aw.

  On input, the A edit descriptor 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, the A edit descriptor 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.

  It affects all subsequent I, B, O, Z, F, E, EN, ES, D, and G
  editing (in the same FORMAT statement) until another blank editing
  descriptor occurs.

  The BN and BZ descriptors supersede the default interpretation of
  blanks during execution of a particular input data transfer
  statement.

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.) An
  all-blank field is treated as zero.

  It affects all subsequent I, B, O, Z, F, E, EN, ES, D, and G
  editing (in the same FORMAT statement) until another blank editing
  descriptor occurs.

  The BN and BZ descriptors supersede the default interpretation of
  blanks during execution of a particular input data transfer
  statement.

16  –  D

  Dw.d
  (Exponential Editing)

  On input, D performs the same as F format.

  On output, D 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, E 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 of 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  –  EN

  ENw.d[Ee] (Exponential Editing:  Engineering form)

  On input, EN performs the same as F format.

  On output, EN 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.  The real value is output in
  engineering notation, where the decimal exponent is divisible by 3
  and the absolute value of the significand is greater than or equal
  to 1 and less than 1000 (unless the output value is zero).

  "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 of the following:
  a minus sign (when necessary) or a plus sign (if SP editing is in
  effect), one to three digits, 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"+9.

  The exponent field width ("e") is optional; if omitted, the default
  is value is 2.  If "e" is specified, the "w" should be greater than
  or equal to "d"+"e"+5.

19  –  ES

  ESw.d[Ee] (Exponential Editing:  Scientific form)

  On input, ES 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.  The real value is output in
  scientific notation, where the absolute value of the significand is
  greater than or equal to 1 and less than 10 (unless the output
  value is zero).

  "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 of the following:
  a minus sign (when necessary) or a plus sign (if SP editing is in
  effect), one digit, 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.

  The exponent field width ("e") is optional; if omitted, the default
  is value is 2.  If "e" is specified, the "w" should be greater than
  or equal to "d"+"e"+5.

20  –  F

  Fw.d (Fixed Floating Editing)

  On input, F 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, F 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 of 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.

21  –  G

  Gw.d[Ee] (General Floating Editing)

  On input, G performs the same as F format.

  On output, G 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                                    Equivalent Conversion
    --------------                                    --------------------
    0 < m < 0.1 - 0.5x10**-d-1                        Ew.d[Ee]
    m = 0                                             F(w-n).(d-1),n('b')
    0.1 - 0.5x10**-d-1 <= m < 1 - 0.5x10**-d          F(w-n).d, n('b')
    1 - 0.5x10**-d <= m < 10 - 0.5x10**-d+1           F(w-n).(d-1), n('b')
    10 - 0.5x10**-d+1 <= n < 100 - 0.5x10**-d+2       F(w-n).(d-2), n('b')
          .                                               .
          .                                               .
          .                                               .
    10**d-2 - 0.5x10**-2 <= m < 10**d-1 - 0.5x10**-1  F(w-n).1, n('b')
    10**d-1 - 0.5x10**-1 <= m < 10**d - 0.5           F(w-n).0, n('b')
    m >= 10**d - 0.5                                  Ew.d[Ee]

  The 'b' is a blank following the numeric data representation.  For
  Gw.d, n('b') is 4 blanks.  For Gw.dEe, n('b') is "e"+2 blanks.

  The term "w" must be greater than or equal to d+7 to allow for the
  following:  a sign (optional if the value is positive and
  descriptor SP is not in effect), one digit to the left of the
  decimal point, a decimal point, "d" digits to the right of the
  decimal point, and either a 4-digit or an "e"+2-digit exponent.

  If "e" is specified, "w" must be greater than or equal to
  "d"+"e"+5.

22  –  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 prior to 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.

                                 NOTE

          This feature has been deleted in Fortran 95; it was
          an  obsolescent  feature  in  Fortran  90.   HP
          Fortran fully supports features deleted in  Fortran
          95.

23  –  I

  Iw[.m] (Integer Editing)

  On input, I 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, I 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.

24  –  L

  Lw (Logical Editing)

  On input, L 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, L 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.

25  –  O

  Ow[.m] (Octal Editing)

  On input, O 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, O 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.

26  –  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, EN, ES, or G field descriptor that
  is to be associated with it and affects all subsequent 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, EN, ES, 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, EN, ES, and 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.

26.1  –  F editing

  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 descriptor
  alters the magnitude of the data.

26.2  –  E editing

  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.

26.3  –  D editing

  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.

26.4  –  EN editing

  On output, the scale factor has no effect on EN editing.

26.5  –  ES editing

  On output, the scale factor has no effect on ES editing.

26.6  –  G editing

  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.

27  –  Q

  (Query Remaining Character Count)

  On input, Q 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.

28  –  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 subsequent I, F,
  E, D, and G editing (in the same FORMAT statement) during the
  execution of an output statement.

29  –  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
  subsequent I, F, E, D, and G editing (in the same FORMAT statement)
  during the execution of an output statement.

30  –  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 subsequent 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.

31  –  Slash

  [r]/

  Terminates data transfer for the current record and starts data
  transfer for a new record.  The "r" is an optional repeat
  specification.

  Multiple slashes cause the system to skip input records or to
  output blank records, as follows:

   o  When "n" consecutive slashes appear between two 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.

   o  When "n" consecutive slashes appear at the beginning or end of
      a format specification, "n" records are skipped or "n" blank
      records are output, because the opening and closing parentheses
      of the format specification are themselves a record initiator
      and terminator, respectively.

32  –  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.

33  –  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.

34  –  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.

35  –  X

  nX (Skip Right n Positions)

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

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

  On output, X 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 in integer in the range 1 through
  the size of the record.

36  –  Z

  Zw[.m] (Hexadecimal Editing)

  On input, Z 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, Z 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 Help