diff --git a/gcc/cobol/failures/playpen/playpen.cbl b/gcc/cobol/failures/playpen/playpen.cbl index a32a01a357e29f321ddca5bfedd7ba55449ffe2b..de07e7e80d403c08433f66f603c514d37a44a991 100644 --- a/gcc/cobol/failures/playpen/playpen.cbl +++ b/gcc/cobol/failures/playpen/playpen.cbl @@ -1,9 +1,12 @@ - - IDENTIFICATION DIVISION. - PROGRAM-ID. prog. - DATA DIVISION. - WORKING-STORAGE SECTION. - COPY copy1. - PROCEDURE DIVISION. - DISPLAY TEST-VAR. - STOP RUN. +01 identification division. +02 program-id. prog. +03 procedure division. +04 display "about to perform stuff" +05 perform stuff +06 display "about to fall through to stuff". +07 stuff. +08 display "This is paragraph ""stuff""". +09 endstuff. +10 display "That's all, folks!" +11 goback. +12 end program prog. diff --git a/gcc/cobol/genapi.cc b/gcc/cobol/genapi.cc index d19fdb1b7a709163cbf353d9ca4aa4e11b6ef59c..2369074dd4a2689d819b84d8ce52fb674256ba4e 100644 --- a/gcc/cobol/genapi.cc +++ b/gcc/cobol/genapi.cc @@ -2312,26 +2312,9 @@ assembler_label(const char *label) strcat(build, label); strcat(build, local_text); - gg_insert_into_assembler(build); + gg_assign(var_decl_nop, build_int_cst_type(INT, 107)); - // In order for the assembler label to be effective, it needs to be followed - // by a .loc directive. The __ASM__ directive won't make that happen; we - // need a different GENERIC tag. An ordinary label does the job: - - tree tgo_to; - tree tlabel; - tree taddr; - gg_create_goto_pair(&tgo_to, - &tlabel, - &taddr); - SET_EXPR_LOCATION (tgo_to, location_from_lineno()); - SET_EXPR_LOCATION (tlabel, location_from_lineno()); - - // The following two tags end up generating a NOP in -O0 code. This is - // almost ideal. I am still looking for another way, but this seems to be - // about as good as it gets. - gg_append_statement(tgo_to); - gg_append_statement(tlabel); + gg_insert_into_assembler(build); } static void