Menu

Having trouble with RECORD LIMITS. Is this something related with the compiler?

lukecow
2020-09-27
2020-09-28
  • lukecow

    lukecow - 2020-09-27

    I'm practicing from a book and the FILE-CONTROL code is the next one

    FILE-CONTROL.
      6            SELECT LongNameFile
      7                   ASSIGN TO NameOfFile
      8                   ORGANIZATION IS LINE SEQUENTIAL.
      9         DATA DIVISION.
     10         FILE SECTION.
     11         FD LongNameFile
     12            RECORD IS VARYING IN SIZE
     13            DEPENDING ON NameLength.
     14         01 LongNameRec          PIC X(40).
     15            88 EndOfNames        VALUE HIGH-VALUES.
     16 
     17         WORKING-STORAGE SECTION.
     18         01 NameLength           PIC 99.
     19         01 NameOfFile           PIC X(20).
    

    I still don't know what's the issue if COBOL is capable of controling record limits like it is displayed in the code.

     
    • Simon Sobisch

      Simon Sobisch - 2020-09-27

      That will vanish with rc2 (maybe a warning that can be explicit enabled). It tells you that you have defined a varying size, but there's only one FD entry with a defined fixed size.
      Either patch cobc or change the 01 variable to

                  01 LongNameRec.
                     88 EndOfNames        VALUE HIGH-VALUES.
                   03 FILLER              PIC X OCCURS 0 TO 40 TIMES
                                                DEPENDING ON NameLength.
      
       

      Last edit: Simon Sobisch 2020-09-27
    • Arnold Trembley

      Arnold Trembley - 2020-09-28

      According to the GnuCOBOL programmer's guide, section 6.2.1. File/Sort-Description,
      The varying clause for the FD entry should be coded this way for variable length records:
      ~~~
      [ RECORD { CONTAINS [ integer-7 TO ] integer-8 CHARACTERS } ]
      { IS VARYING IN SIZE }
      { ~~~~~~~ }
      { [ FROM [ integer-7 TO ] integer-8 CHARACTERS }
      { ~~ }
      { DEPENDING ON identifier-6 ] }
      ~~~~~~
      After that, I believe the 01 record under the FD should be coded for the maximum record length. And "identifier-6" must be an integer numeric data item in Working Storage and it cannot be signed (a negative record length is illegal).

      There is also an option for different record lengths under the FD where each record length has its own 01 record definition, but that's probably not what you want for this application.

      Kind regards,

       

Anonymous
Anonymous

Add attachments
Cancel