support for level 88 / conditionals is missing
I've thought to have raised that before, but sadly this was only posted via mail (October 2021). Therefore I'll quote from that mail - not everything may be up-to-date, but the general issue is still the same (other than GC3.2-rc1 actually leaving the level 88 informations in the dump code, so cobcd could read those in).
Note, that there's a "quite intense" request of this "missing feature" in cbl-gdb...
Code example:
01 ME-EXCH-BASIS.
05 ME-X-FX PIC X(01) VALUE SPACE.
05 ME-X-P PIC X(01) VALUE SPACE.
05 ME-X-C PIC X(01) VALUE SPACE.
01 FILLER REDEFINES ME-EXCH-BASIS PIC X(03).
88 SW-EXCH-BASIS-KOMPLETT VALUE "JJJ", "XXX".
The programmer can (early 428) ask for all symbols but SW-EXCH-BASIS-KOMPLETT - the level 88 variable which returns
No symbol matches "SW-EXCH-RMS-KOMPLETT" in current context
As a comparison, this is what happens with different debuggers:
ACUCOBOL-GT:
d SW-EXCH-RMS-KOMPLETT -> actually prints whatever is at the memory there, so possibly JNJ; that is not "good" but at least allows to easier check manually for true/false
MF SE:
SW-EXCH-RMS-KOMPLETT: False (would print "True" if "JJJ" is in there)
Ideally cobcd would:
(gdb) cp ME-EXCH-BASIS="JNJ"
ME-EXCH-BASIS="JNJ"
(gdb) cp SW-EXCH-RMS-KOMPLETT
False ("JNJ")
(gdb) cp SW-EXCH-RMS-KOMPLETT = true # setting the memory to the first TRUE value, but that's optional
True ("JJJ")
(gdb) cp /d SW-EXCH-RMS-KOMPLETT
--> showing all attributes and storage as now, but additional
TRUE: "JJJ", "XXX"
or similar, so showing the values that would display a TRUE value
Neither ACU nor MF allow an explicit setting of true/false (which COBOL does), not sure if you want to add that to cobcd (that's totally "optional", you likely want to consider this for gcobol + gdb integration in any case).
The old output of cobc back then:
P_dump:
{
cob_field f0;
memset(&f0,0,sizeof(f0));
/* Dump WORKING-STORAGE */
cob_dump_output("WORKING-STORAGE");
cob_dump_field_ext ( 1, "ME-EXCH-BASIS", COB_SET_FLD(f0, 3, b_8, &a_3), 0, 0);
cob_dump_field_ext ( 5, "ME-X-FX", COB_SET_FLD(f0, 1, b_8, &a_1), 0, 0);
cob_dump_field_ext ( 5, "ME-X-P", COB_SET_FLD(f0, 1, b_8 + 1, &a_1), 0, 0);
cob_dump_field_ext ( 5, "ME-X-C", COB_SET_FLD(f0, 1, b_8 + 2, &a_1), 0, 0);
/* cob_dump_field_ext ( 1, "FILLER", COB_SET_FLD(f0, 3, b_8, &a_1), 0, 0); REDEFINES */
/* cob_dump_field_ext ( 1, "ME-EXCH-RMS", COB_SET_FLD(f0, 1, b_14, &a_3), 0, 0); */
/* cob_dump_field_ext ( 5, "ME-X-RMS", &f_15, 0, 0); */
/* cob_dump_field_ext ( 1, "FILLER", &f_16, 0, 0); REDEFINES */
}
... so there's no info there - of course cobcd.py could not do anything.
I've put some time in to add the missing information, which then was generated as follows:
P_dump:
{
cob_field f0;
memset(&f0,0,sizeof(f0));
/* Dump WORKING-STORAGE */
cob_dump_output("WORKING-STORAGE");
cob_dump_field_ext ( 1, "ME-EXCH-BASIS ", COB_SET_FLD(f0, 3, b_8, &a_3), 0, 0);
cob_dump_field_ext ( 5, "ME-X-FX", COB_SET_FLD(f0, 1, b_8, &a_1), 0, 0);
cob_dump_field_ext ( 5, "ME-X-P", COB_SET_FLD(f0, 1, b_8 + 1, &a_1), 0, 0);
cob_dump_field_ext ( 5, "ME-X-C", COB_SET_FLD(f0, 1, b_8 + 2, &a_1), 0, 0);
/* cob_dump_field_ext ( 1, "FILLER", COB_SET_FLD(f0, 3, b_8, &a_1), 0, 0); REDEFINES */
/* cob_dump_field_ext (88, "SW-EXCH-BASIS-KOMPLETT", COB_SET_FLD(f0, 3, b_8, &a_1), 0, 0); VALUE (cob_field *)&c_3 */
/* cob_dump_field_ext ( 1, "ME-EXCH-RMS", COB_SET_FLD(f0, 1, b_14, &a_3), 0, 0); */
/* cob_dump_field_ext ( 5, "ME-X-RMS", &f_15, 0, 0); */
/* cob_dump_field_ext ( 1, "FILLER", &f_16, 0, 0); REDEFINES */
/* cob_dump_field_ext (88, "SW-EXCH-RMS-KOMPLETT", &f_16, 0, 0); VALUE (cob_field *)&c_1 OR (cob_field *)&c_4 */
}
As you see the validation fields are in now, pointing to the related memory ("parent" with a new VALUE constant [OR constant | contant THRU constant]... generated.
This now shows up in cobcd as expected (because neither cobcd nor cobcd.py know anything about the VALUE stuff):
(gdb) cp SW-EXCH-RMS-KOMPLETT 88 SW-EXCH-RMS-KOMPLETT/FILLER : "J^^^" (gdb) cp/x SW-EXCH-RMS-KOMPLETT 88 SW-EXCH-RMS-KOMPLETT/FILLER : 0x4a000000
So we already have the ACUCOBOL-GT debugger's behaviour by those changes with GnuCOBOL 3.2 "for free" - it seems that this didn't break anything and everything else still works. Here's the full output:
(gdb) cp * 1 : 01 ME-EXCH-BASIS : " " 2 : 05 ME-X-FX/ME-EXCH-BASIS : " " 3 : 05 ME-X-P/ME-EXCH-BASIS : " " 4 : 05 ME-X-C/ME-EXCH-BASIS : " " 5 : 01 FILLER : " " 6 : 88 SW-EXCH-BASIS-KOMPLETT/FILLER : " " 7 : 01 ME-EXCH-RMS : "J" 8 : 05 ME-X-RMS/ME-EXCH-RMS : "J" 9 : 01 FILLER : "J^^^" 10 : 88 SW-EXCH-RMS-KOMPLETT/FILLER : "J^^^"
For users this will obviously mean a bit longer compile times and an even bigger VARIABLE_STRING
(static read-only data), but fixing the unknown symbols is worth it.
Can you please adjust at least cobcd to read in the additional VALUE information? As expected those aren't in:
(gdb) with print elements unlimited -- print VARIABLE_STRING_MDCFS202Ecob
$2 = "000000496P||MDCFS20|/tmp/MDCFS20.cob|||24||||~E||MDCFS20|/tmp/MDCFS20.cob|||24||||~W|1|ME-EXCH-BASIS||b_8|a_3||3|||~W|5|ME-X-FX||b_8|a_1||1|||~W|5|ME-X-P||b_8|a_1|1|1|||~W|5|ME-X-C||b_8|a_1|2|1|||~W|1|FILLER||b_8|a_1||3|||~W|88|SW-EXCH-BASIS-KOMPLETT||b_8|a_1||3|||~W|1|ME-EXCH-RMS||b_14|a_3||1|||~W|5|ME-X-RMS|f_15|b_14|a_1||1|||~W|1|FILLER|f_16|b_14|a_1||4|||~W|88|SW-EXCH-RMS-KOMPLETT|f_16|b_14|a_1||4|||~"
Note: the list of VALUE consist often of 1 entry, but it may also be hundred entries with OR and possibly also some combined with THRU.
Of course integrating them in VARIABLE_STRING is only useful if you intend to provide the MF Animator feature of printing True/False someday, ideally with the cobcd.py feature of showing the actually validated variable content in parens.
Even if you don't do this for the next release in the python side - please consider it for cobcd - because shipping an updated cobcd.py is easy, installing cobcd and recompiling everything isn't...
Side note: adjustment to handle these a bit better in cobcd.py:
in ProcessArguments()
:
payload = GV_ModuleInformation.var_trie.storage_list[index]
+ if payload.level == 88:
+ ConditionalRaise("a conditional variable (level 88) may not be used as source")
+ return
in set_var_value()
:
var_left = GV_GlobalVariables.VarLeft
+ if var_left.level == 88:
+ ConditionalRaise("a conditional variable (level 88) may not be set directly")
+ # note: should be done later via = true/false
+ return 0