Skip to content

Parse depending on variables

Note: for this to actually work it is necessary that cobcd-processing leaves all data of the expression (cob_get_int(), SET_DATA, ... intact); but if that is done everything should work when not debugging core-dumps.

Summary from #78 (closed):

The cobc generated code cob_dump_field_ext ( 1, "VAR-SATAB", COB_SET_FLD(f0, 30 * cob_get_numdisp (b_644, 3), b_645, &a_19), 0, 0); /* EXTERNAL */

is explicit, by purpose, changed in HackAway() to the length token

30*b_644

instead of the "correct"

30 * cob_get_numdisp (b_644, 3)

which can be evaluated (on a running process) by gdb.parse_and_eval.

To create consistent results which also work with core-dumps, that part could still be left in as is, but at least in cobcd.py (AddEmUp) the expression needs to be changed and the part in "cob_get_numdisp" (likely also cob_get_packed, cob_get_int ,...) be calculated by the python code.

For integration I'd argue that the version suggested is already better than what is currently in, even if the HackAway is not changed. If HackAway is changed and there is no further adjustment in cobcd.py then the code presented here would "just work" if not doing coredump debugging and would present a nice "cannot parse this" otherwise.

Note: There was an adjustment for that in 4.29 (which I internally call version 5 as this has incompatible symbol information) but that did not included any test cases, I'd suggest to use the following

WORKING-STORAGE SECTION.
 77 I-ENTRIES  PIC 9(10) EXTERNAL.
 77 I-ENTRIES2 PIC 9(10) COMP-3.
 77 I-ENTRIES3 PIC 9(10) COMP-5.
LINKAGE SECTION.
 01 TAB.
  02 TAB-T  OCCURS UNBOUNDED DEPENDING ON I-ENTRIES.
    05 TAB-ELEMENT     PIC X(15).
 01 TAB2.
  02 TAB2-T OCCURS UNBOUNDED DEPENDING ON I-ENTRIES2.
    05 TAB-ELEMENT2    PIC X(3).
 01 TAB3.
  02 TAB3-T OCCURS UNBOUNDED DEPENDING ON I-ENTRIES3.
    05 TAB-ELEMENT3    PIC X(1).

and

(gdb) cprint I-ENTRIES=10
(gdb) cprint I-ENTRIES2=5
(gdb) cprint I-ENTRIES3=12
(gdb) cprint TAB-ELEMENT  (5)
(gdb) cprint TAB-ELEMENT2 (4)
(gdb) cprint TAB-ELEMENT3 (11)
(gdb) cprint I-ENTRIES3=10
(gdb) cprint TAB-ELEMENT3 (11)

Merge request reports