Menu

#61 extfh: alternate keys are not created correctly

GC 3.x
pending
nobody
EXTFH (2)
5 - default
2023-05-31
2023-05-23
No

consider the following code

       IDENTIFICATION DIVISION.
       PROGRAM-ID.    CKALTERNATEKEY.
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SPECIAL-NAMES.
           DECIMAL-POINT IS COMMA.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT WSORTMEN ASSIGN TO NOME-WSORTMEN
                  LOCK MODE IS MANUAL
                  WITH LOCK ON MULTIPLE RECORDS
                  ORGANIZATION INDEXED ACCESS DYNAMIC
                  STATUS ST-FILE RECORD KEY WSORTM-KEY
                  ALTERNATE RECORD KEY WSORTM-PGM=WSORTM-LIV WSORTM-CODICE WITH DUPLICATES
                  ALTERNATE RECORD KEY WSORTM-PROG=WSORTM-PROGRESSIVO      WITH DUPLICATES
                  ALTERNATE RECORD KEY WSORTM-ITEM=WSORTM-HITEM            WITH DUPLICATES.

       DATA DIVISION.
       FILE SECTION.
       FD  WSORTMEN.
       01  WSORTMEN-REC.
           02      WSORTM-KEY.
             03    WSORTM-CT               PIC 9.
             03    WSORTM-PADRE            PIC X(16).
             03    WSORTM-ORDIN            PIC 999.
             03    WSORTM-CODICE           PIC X(16).
           02      WSORTM-DATI.
             03    WSORTM-PROGRESSIVO      PIC 9(6).
             03    WSORTM-HITEM            PIC XXXX COMP-5.
             03    WSORTM-LIV              PIC 9.
           02      FILLER                  PIC X(759).
       WORKING-STORAGE SECTION.
           01 ST-FILE                      PIC XX.   
       PROCEDURE DIVISION.
       MAIN-PROGRAM SECTION.
       BEGIN-PROGRAM.
           MOVE "WGMEN_GC" TO NOME-WSORTMEN
           OPEN OUTPUT WSORTMEN
           CLOSE WSORTMEN
           GOBACK.

Compiled and executed with Microfocus create the file as below:

File   : WGMEN_MF
Rcdlg  :    806
N. rk  :    269
N. key :      4

Key: 0  Seg: 1  start =    1    len = 36        String
Key: 1  Seg: 1  start =   47    len =  1        String
        Seg: 2  start =   21    len = 16        String
Key: 2  Seg: 1  start =   37    len =  6        String
Key: 3  Seg: 1  start =   43    len =  4        String

Compiled and executed with GnuCOBOL:

File   : WGMEN_GC
Rcdlg  :    806
N. rk  :    269
N. key :      4

Key: 0  Seg: 1  start =    1    len = 36        String
Key: 1  Seg: 1  start =   47    len =  1        String
        Seg: 2  start =   21    len = 16        String
Key: 2  Seg: 1  start =    1    len =  6        String
Key: 3  Seg: 1  start =    1    len =  4        String

the last two indexes are wrong!

to work around the problem I modified the "copy_file_to_fcd" function in fileio.c as below (partial):

        for(idx=0; idx < nkeys; idx++) {
            key = (EXTKEY*)((char*)((char*)kdb) + keypos);
            STCOMPX2(keypos, kdb->key[idx].offset);
            kdb->key[idx].keyFlags = 0;
            if(f->keys[idx].tf_duplicates)
                kdb->key[idx].keyFlags |= KEY_DUPS;
            if(f->keys[idx].tf_suppress) {
                kdb->key[idx].keyFlags |= KEY_SPARSE;
                kdb->key[idx].sparse = (unsigned char)f->keys[idx].char_suppress;
            }
                 /*if(f->keys[idx].count_components <= 1) {  ---> the offset of an alternate record key is not calculated correctly in case of single component   ->>line 7672 of fileio.c vers. 3.1.2 */
                if(f->keys[idx].count_components < 1) { /* to work around the problem: expression valid only for count_components equal 0 or less  */
                STCOMPX2(1,kdb->key[idx].count);
                STCOMPX4(f->keys[idx].offset, key->pos);
                STCOMPX4(f->keys[idx].field->size, key->len);
                keypos = keypos + sizeof(EXTKEY);
            } else {
                STCOMPX2(f->keys[idx].count_components, kdb->key[idx].count);
                for(k=0; k < f->keys[idx].count_components; k++) {
                    key = (EXTKEY*)((char*)((char*)kdb) + keypos);
                    STCOMPX4(f->keys[idx].component[k]->data - f->record->data, key->pos);
                    STCOMPX4(f->keys[idx].component[k]->size, key->len);
                    keypos = keypos + sizeof(EXTKEY);
                }
            }
        }

Discussion

  • Simon Sobisch

    Simon Sobisch - 2023-05-31

    Ticket moved from /p/gnucobol/bugs/885/

     
  • Simon Sobisch

    Simon Sobisch - 2023-05-31
    • status: open --> pending
     
  • Simon Sobisch

    Simon Sobisch - 2023-05-31

    Can you please recheck with GC 3.2, either current dev snapshot or rc2? This has [r4347] included which is a huge step in EXTFH handling and - I guess - fixes the issue.

     

    Related

    Commit: [r4347]


Log in to post a comment.