From 938850d7718d5a83131d05d06c7f98bef19cc4ec Mon Sep 17 00:00:00 2001 From: Bob Dubner <rdubner@symas.com> Date: Fri, 29 Mar 2024 10:16:02 -0400 Subject: [PATCH] Improved SHOW_PARSE for INSPECT --- gcc/cobol/failures/playpen/playpen.cbl | 35 +++++++++++++++-------- gcc/cobol/genapi.cc | 39 +++++++++++++++++++++++++- 2 files changed, 62 insertions(+), 12 deletions(-) diff --git a/gcc/cobol/failures/playpen/playpen.cbl b/gcc/cobol/failures/playpen/playpen.cbl index 5845fe142be7..58561291d2fc 100644 --- a/gcc/cobol/failures/playpen/playpen.cbl +++ b/gcc/cobol/failures/playpen/playpen.cbl @@ -1,15 +1,28 @@ IDENTIFICATION DIVISION. -PROGRAM-ID. "A". +PROGRAM-ID. Listing9-4. +AUTHOR. Michael Coughlan. + +*> Extended by Bob Dubner to exercise INSPECT a little more deeply +*> Not much, but a little + DATA DIVISION. WORKING-STORAGE SECTION. -01 USR-LOCAL-BIN PIC X(15) VALUE z"/usr/local/bin". -01 CHDIR_RETURN PIC S999 BINARY. -PROCEDURE DIVISION. - *> MOVE "/usr/local/bin" TO USR-LOCAL-BIN - *> MOVE X'00' TO USR-LOCAL-BIN(15:1) - CALL "chdir" - USING BY CONTENT USR-LOCAL-BIN - RETURNING CHDIR_RETURN - DISPLAY "Return from chdir is " CHDIR_RETURN - goback. +01 Stars PIC *****. +01 NumOfStars PIC 9. +01 twos pic 99 VALUE 10. +01 threes pic 99 VALUE 20. +01 fours pic 99 VALUE 30. +01 bobs pic 99 VALUE 40. + +01 inspect_text PIC X(24) VALUE "two22three333four4444bob". + +PROCEDURE DIVISION. +Begin. + PERFORM VARYING NumOfStars FROM 0 BY 1 UNTIL NumOfStars > 5 + COMPUTE Stars = 10 ** (4 - NumOfStars) + INSPECT Stars REPLACING ALL "1" BY SPACES + ALL "0" BY SPACES + DISPLAY NumOfStars " = " Stars + END-PERFORM + STOP RUN. diff --git a/gcc/cobol/genapi.cc b/gcc/cobol/genapi.cc index 6f6d2dbf31e8..ec354cc88ab2 100644 --- a/gcc/cobol/genapi.cc +++ b/gcc/cobol/genapi.cc @@ -8487,7 +8487,7 @@ parser_inspect_replacing( cbl_refer_t identifier_1, SHOW_PARSE { SHOW_PARSE_HEADER - SHOW_PARSE_END + SHOW_PARSE_TEXT(" ") } // For REPLACING, unlike TALLY, there can be but one operation @@ -8578,6 +8578,24 @@ parser_inspect_replacing( cbl_refer_t identifier_1, // Each identifier-5 gets a PHRASE1: pcbl_refers[pcbl_index++] = operations[0].opers[j].replaces[0].before.identifier_4; pcbl_refers[pcbl_index++] = operations[0].opers[j].replaces[0].after.identifier_4; + + SHOW_PARSE + { + if( j ) + { + SHOW_PARSE_INDENT + } + SHOW_PARSE_FIELD("ID-5 ", operations[0].opers[j].replaces[0].replacement.field) + if(operations[0].opers[j].replaces[0].before.identifier_4.field) + { + SHOW_PARSE_FIELD(" before ", operations[0].opers[j].replaces[0].before.identifier_4.field) + } + if(operations[0].opers[j].replaces[0].after.identifier_4.field) + { + SHOW_PARSE_FIELD(" after ", operations[0].opers[j].replaces[0].after.identifier_4.field) + } + SHOW_PARSE_END + } } else { @@ -8596,6 +8614,25 @@ parser_inspect_replacing( cbl_refer_t identifier_1, pcbl_refers[pcbl_index++] = operations[0].opers[j].replaces[k].before.identifier_4; pcbl_refers[pcbl_index++] = operations[0].opers[j].replaces[k].after.identifier_4; + + SHOW_PARSE + { + if( j || k ) + { + SHOW_PARSE_INDENT + } + SHOW_PARSE_FIELD("ID-3 ", operations[0].opers[j].replaces[k].matching.field) + SHOW_PARSE_FIELD(" ID-5 ", operations[0].opers[j].replaces[k].replacement.field) + if( operations[0].opers[j].replaces[k].before.identifier_4.field ) + { + SHOW_PARSE_FIELD("before ", operations[0].opers[j].replaces[k].before.identifier_4.field) + } + if(operations[0].opers[j].replaces[k].after.identifier_4.field) + { + SHOW_PARSE_FIELD("after ", operations[0].opers[j].replaces[k].after.identifier_4.field) + } + SHOW_PARSE_END + } } } } -- GitLab