Skip to content

Commit

Permalink
minor testuite update
Browse files Browse the repository at this point in the history
to drop user-reported warnings from compiler/linker
  • Loading branch information
sf-mensch committed Oct 4, 2024
1 parent 3f89712 commit ca09f17
Show file tree
Hide file tree
Showing 4 changed files with 85 additions and 63 deletions.
10 changes: 6 additions & 4 deletions tests/testsuite.src/listings.at
Original file line number Diff line number Diff line change
Expand Up @@ -6913,7 +6913,8 @@ AT_CLEANUP
AT_SETUP([Long concatenated literal])
AT_KEYWORDS([listing overflow])

AT_DATA([prog.cob], [
# extra quoting here as we received a bug report of something adding a leading (
AT_DATA([prog.cob], [[
>>SOURCE FORMAT IS FREE
ID DIVISION.
PROGRAM-ID. ED000MAIN IS INITIAL.
Expand All @@ -6935,10 +6936,11 @@ WORKING-STORAGE SECTION.
"1234567890123456789012".
PROCEDURE DIVISION.
EXIT.
])
]])

# extra quoting here as we received a bug report of something adding a leading (
AT_CHECK([$COMPILE_LISTING0 -t- prog.cob], [0],
[GnuCOBOL V.R.P prog.cob
[[GnuCOBOL V.R.P prog.cob

LINE PG/LN A...B............................................................

Expand Down Expand Up @@ -6980,7 +6982,7 @@ LINE PG/LN A...B............................................................

0 warnings in compilation group
0 errors in compilation group
])
]])

AT_CLEANUP

8 changes: 5 additions & 3 deletions tests/testsuite.src/run_file.at
Original file line number Diff line number Diff line change
Expand Up @@ -9102,7 +9102,6 @@ TSTFH (unsigned char *opCodep, FCD3 *fcd)
static char * /* Return Text name of function */
txtOpCode(int opCode)
{
static char tmp[32];
switch (opCode) {
case OP_OPEN_INPUT: return "OPEN_IN";
case OP_OPEN_OUTPUT: return "OPEN_OUT";
Expand Down Expand Up @@ -9154,8 +9153,11 @@ txtOpCode(int opCode)
case OP_WRITE_AFTER_TAB: return "WRITE_AFTER_TAB";
case OP_WRITE_AFTER_PAGE: return "WRITE_AFTER_PAGE";
}
sprintf(tmp, "Func 0x%02X:", opCode);
return tmp;
{
static char wrk[20];
snprintf (wrk, sizeof(wrk), "Func 0x%02X", opCode);
return wrk;
}
}
]])

Expand Down
125 changes: 71 additions & 54 deletions tests/testsuite.src/run_misc.at
Original file line number Diff line number Diff line change
Expand Up @@ -11866,7 +11866,6 @@ AT_DATA([cmod.c], [[
static char *
getType (int type, int byvalue)
{
static char wrk[24];
switch (type) {
#if 1
case COB_TYPE_GROUP: return "Group";
Expand Down Expand Up @@ -11897,56 +11896,62 @@ getType (int type, int byvalue)
case COB_TYPE_NATIONAL: return "N";
#endif
}
sprintf (wrk,"Type %04X",type);
return wrk;
{
static char wrk[20];
snprintf (wrk, sizeof(wrk), "Type 0x%04X", type);
return wrk;
}
}

COB_EXT_EXPORT int
CAPI (void *p1, ...)
{
int k,nargs,type,digits,scale,size,sign,byvalue;
cob_s64_t val = 0;
char *str;
char wrk[80],pic[30]; /* note: maximum _theoretical_ size */
char wrk[80], pic[30]; /* note: maximum _theoretical_ size */
const int nargs = cob_get_num_params();
int k;
cob_s64_t val = 0;

nargs = cob_get_num_params();
printf ("CAPI called with %d parameters\n",nargs);
fflush(stdout);
fflush (stdout);
for (k=1; k <= nargs; k++) {
type = cob_get_param_type (k);
digits = cob_get_param_digits (k);
scale = cob_get_param_scale (k);
size = cob_get_param_size (k);
sign = cob_get_param_sign (k);
byvalue = cob_get_param_constant(k);
int type = cob_get_param_type (k);
int digits = cob_get_param_digits (k);
int scale = cob_get_param_scale (k);
int size = cob_get_param_size (k);
int sign = cob_get_param_sign (k);
int byvalue = cob_get_param_constant(k);
printf (" %d: %-8s ", k, getType (type, byvalue));
if (byvalue) {
printf ("BY VALUE ");
} else {
printf ("BY REFERENCE ");
}
if (type == COB_TYPE_ALPHANUMERIC) {
sprintf (pic, "X(%d)", size);
str = cob_get_picx_param (k, NULL, 0);
char *str = cob_get_picx_param (k, NULL, 0);
snprintf (pic, sizeof(pic), "X(%d)", size);
printf ("%-11s '%s'", pic, str);
cob_free ((void*)str);
cob_put_picx_param (k, "Bye!");
} else if (type == COB_TYPE_NATIONAL) {
sprintf (pic, "N(%d)", size); /* FIXME */
snprintf (pic, sizeof(pic), "N(%d)", size); /* FIXME */
printf ("exchange of national data is not supported yet");
} else if (type == COB_TYPE_GROUP) {
sprintf (pic, "(%d)", size);
str = cob_get_grp_param (k, NULL, 0);
char *str = cob_get_grp_param (k, NULL, 0);
snprintf (pic, sizeof(pic), "(%d)", size);
printf ("%-11s '%.*s'", pic, size, str);
cob_free ((void*)str);
memset (wrk,' ',sizeof(wrk));
memcpy (wrk,"Bye-Bye Birdie!",15);
memset (wrk, ' ',sizeof(wrk));
memcpy (wrk, "Bye-Bye Birdie!", 15);
cob_put_grp_param (k, wrk, sizeof(wrk));
} else if (type == COB_TYPE_NUMERIC_EDITED) {
if (scale > 0) {
sprintf (pic,"%s9(%d)V9(%d)",sign?"S":"",digits-scale,scale);
snprintf (pic, sizeof(pic), "%s9(%d)V9(%d)",
sign ? "S":"",
digits - scale, scale);
} else {
sprintf (pic,"%s9(%d)",sign?"S":"",digits-scale);
snprintf (pic, sizeof(pic), "%s9(%d)",
sign ? "S":"",
digits - scale);
}
val = cob_get_s64_param (k);
printf ("%-11s %lld ",pic,val);
Expand All @@ -11957,9 +11962,13 @@ CAPI (void *p1, ...)
printf (" to %.*s",size,wrk);
} else {
if(scale > 0) {
sprintf (pic,"%s9(%d)V9(%d)",sign?"S":"",digits-scale,scale);
snprintf (pic, sizeof(pic), "%s9(%d)V9(%d)",
sign ? "S":"",
digits - scale, scale);
} else {
sprintf (pic,"%s9(%d)",sign?"S":"",digits-scale);
snprintf (pic, sizeof(pic), "%s9(%d)",
sign ? "S":"",
digits - scale);
}
val = cob_get_s64_param (k);
printf ("%-11s %lld", pic, val);
Expand Down Expand Up @@ -12046,7 +12055,7 @@ AT_CLEANUP


AT_SETUP([C-API (field based)])
AT_KEYWORDS([runmisc CALL api])
AT_KEYWORDS([runmisc CALL api field])

AT_DATA([prog.cob], [
IDENTIFICATION DIVISION.
Expand Down Expand Up @@ -12102,7 +12111,6 @@ AT_DATA([cmod.c], [[
static char *
getType (int type, int byvalue)
{
static char wrk[24];
switch (type) {
#if 1
case COB_TYPE_GROUP: return "Group";
Expand Down Expand Up @@ -12133,73 +12141,82 @@ getType (int type, int byvalue)
case COB_TYPE_NATIONAL: return "N";
#endif
}
sprintf (wrk,"Type %04X",type);
return wrk;
{
static char wrk[20];
snprintf (wrk, sizeof(wrk), "Type 0x%04X", type);
return wrk;
}
}

COB_EXT_EXPORT int
CAPI (void *p1, ...)
{
int k,nargs,type,digits,scale,size,sign,byvalue;
cob_s64_t val;
char *str;
char wrk[80],pic[30]; /* note: maximum _theoretical_ size */
char wrk[80],pic[30]; /* note: maximum _theoretical_ size */
const int nargs = cob_get_num_params();
int k;

nargs = cob_get_num_params();
printf ("CAPI called with %d parameters\n",nargs);
fflush(stdout);
fflush (stdout);
for (k=1; k <= nargs; k++) {
cob_field *fld = cob_get_param_field (k, "CAPI");
type = cob_get_field_type (fld);
digits = cob_get_field_digits (fld);
scale = cob_get_field_scale (fld);
size = cob_get_field_size (fld);
sign = cob_get_field_sign (fld);
byvalue = cob_get_field_constant (fld);
char *str = (char *) cob_get_field_str_buffered (fld);
int type = cob_get_field_type (fld);
int digits = cob_get_field_digits (fld);
int scale = cob_get_field_scale (fld);
int size = cob_get_field_size (fld);
int sign = cob_get_field_sign (fld);
int byvalue = cob_get_field_constant (fld);
printf (" %d: %-8s ", k, getType (type, byvalue));
if (byvalue) {
printf ("BY VALUE ");
} else {
printf ("BY REFERENCE ");
}
str = (char *) cob_get_field_str_buffered (fld);
if (type == COB_TYPE_ALPHANUMERIC) {
sprintf (pic, "X(%d)", size);
snprintf (pic, sizeof(pic), "X(%d)", size);
printf ("%-11s '%s'", pic, str);
cob_put_field_str (fld, "Bye!");
} else if (type == COB_TYPE_NATIONAL) {
sprintf (pic,"N(%d)",size); /* FIXME */
snprintf (pic, sizeof(pic), "N(%d)", size); /* FIXME */
printf ("exchange of national data is not supported yet");
} else if (type == COB_TYPE_GROUP) {
sprintf (pic,"(%d)",size);
snprintf (pic, sizeof(pic), "(%d)",size);
printf ("%-11s '%.*s'",pic,size,str);
cob_put_field_str (fld, "Bye-Bye Birdie!");
} else if (type == COB_TYPE_NUMERIC_EDITED) {
cob_s64_t val = cob_get_s64_param (k);
if (scale > 0) {
sprintf (pic,"%s9(%d)V9(%d)",sign?"S":"",digits-scale,scale);
snprintf (pic, sizeof(pic), "%s9(%d)V9(%d)",
sign ? "S":"",
digits - scale, scale);
} else {
sprintf (pic,"%s9(%d)",sign?"S":"",digits-scale);
snprintf (pic, sizeof(pic), "%s9(%d)",
sign ? "S":"",
digits - scale);
}
printf ("%-11s %s ",pic,str);
val = cob_get_s64_param (k);
val = val + 130;
val = -val;
cob_put_s64_param (k, val);
str = (char *) cob_get_field_str (fld, wrk, 78);
printf (" to %.*s",size,wrk);
} else {
cob_s64_t val = cob_get_s64_param (k);
if(scale > 0) {
sprintf (pic,"%s9(%d)V9(%d)",sign?"S":"",digits-scale,scale);
snprintf (pic, sizeof(pic), "%s9(%d)V9(%d)",
sign ? "S":"",
digits - scale, scale);
} else {
sprintf (pic,"%s9(%d)",sign?"S":"",digits-scale);
snprintf (pic, sizeof(pic), "%s9(%d)",
sign ? "S":"",
digits - scale);
}
printf ("%-11s %s", pic, str);
val = cob_get_s64_param (k);
sprintf (wrk, "%lld", val + 3);
snprintf (wrk, sizeof(wrk), "%lld", val + 3);
cob_put_field_str (fld, wrk);
}
printf (";\n");
fflush(stdout);
fflush (stdout);
}
return 0;
}
Expand Down
5 changes: 3 additions & 2 deletions tests/testsuite.src/syn_functions.at
Original file line number Diff line number Diff line change
Expand Up @@ -582,10 +582,11 @@ AT_DATA([prog.cob], [
.
])

# extra quoting here as we received a bug report of something adding a leading (
AT_CHECK([$COMPILE -Wno-pending prog.cob], [1], [],
[prog.cob:7: error: syntax error, unexpected Literal, expecting PHYSICAL or )
[[prog.cob:7: error: syntax error, unexpected Literal, expecting PHYSICAL or )
prog.cob:8: error: a non-numeric literal is expected here
prog.cob:9: error: a non-numeric literal is expected here
])
]])

AT_CLEANUP

0 comments on commit ca09f17

Please sign in to comment.