From d67c193bdb9d809c6339ec68d61af3145726753c Mon Sep 17 00:00:00 2001 From: Bob Dubner <rdubner@symas.com> Date: Wed, 27 Dec 2023 13:43:35 -0500 Subject: [PATCH] Extend parser_ante.h new_temporary_clone() --- gcc/cobol/failures/copypar/playpen.cbl | 16 ++++++++++++++++ gcc/cobol/parse_ante.h | 3 +-- 2 files changed, 17 insertions(+), 2 deletions(-) diff --git a/gcc/cobol/failures/copypar/playpen.cbl b/gcc/cobol/failures/copypar/playpen.cbl index 0740403183db..4e09043e6f62 100644 --- a/gcc/cobol/failures/copypar/playpen.cbl +++ b/gcc/cobol/failures/copypar/playpen.cbl @@ -14,6 +14,18 @@ GOBACK. END FUNCTION COPYPAR. + IDENTIFICATION DIVISION. + FUNCTION-ID. COPYPAR2. + DATA DIVISION. + LINKAGE SECTION. + 01 PARSB PIC 99999. + 01 PAR5 PIC 99999. + PROCEDURE DIVISION USING PAR5 RETURNING PARSB. + MOVE PAR5 TO PARSB + DISPLAY PARSB + GOBACK. + END FUNCTION COPYPAR2. + IDENTIFICATION DIVISION. PROGRAM-ID. prog. ENVIRONMENT DIVISION. @@ -28,9 +40,13 @@ 01 PARS2. 02 PAR1 PICTURE X(32). 02 PAR2 PICTURE X(32). + + 01 PAR5 PICTURE 99999 VALUE 54321. PROCEDURE DIVISION. MOVE COPYPAR(PARS1) TO PARS2 DISPLAY PARS2. + + DISPLAY COPYPAR2(PAR5) STOP RUN. END PROGRAM prog. diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h index 223fb08f966d..65593f6f4c3a 100644 --- a/gcc/cobol/parse_ante.h +++ b/gcc/cobol/parse_ante.h @@ -1842,8 +1842,7 @@ new_temporary_clone( const cbl_field_t *orig) { cbl_field_type_t type = is_literal(orig)? FldAlphanumeric : orig->type; auto f = new_temporary_imply(type); - // Dubner kludge - if( orig->type == FldGroup ) + // Dubner attempt at a true temporary clone { cbl_name_t tname; memcpy(tname, f->name, sizeof(cbl_name_t)); -- GitLab