Hi!
Sorry, my mail got somehow truncated.
On Sun, Mar 16, 2025 at 01:42:52AM +0100, Jakub Jelinek wrote:
> On Sat, Mar 15, 2025 at 04:14:48PM -0500, Robert Dubner wrote:
> > --- /dev/null
> > +++ b/gcc/testsuite/cobol.dg/group1/check_88.cob
> > @@ -0,0 +1,116 @@
> > +*> { dg-do run }
> > +*> { dg-output "-><-\n" }
> > +*> { dg-output "-> <-\n" }
> > +*> { dg-output " \n" }
> > +*> { dg-output "There should be no garbage after character 32\n" }
> > +*> { dg-output
> > "-------------------------------\[*\]--------------------------------\n" }
The reason why I was suggesting using
*> { dg-output
{-------------------------------\*--------------------------------(\n|\r\n|\r)}
}
rather than this is that the quoting of special chars is then much simpler in
TCL
compared to "...".
In "" string you need to use "\\\*" to match literal *.
The reason for using (\n|\r\n|\r) is to be prepared for Darwin and Windows line
endings, so
that you don't have to rewrite all the tests later.
> > +*> { dg-output "CheckBinary Properly True\n" }
> > +*> { dg-output "CheckBinary Properly False\n" }
And the suggestion was not to require \n (or better (\n|\r\n|\r)
at the end of last dg-output, with some dejagnu boards and e.g. remote
testing the last newline is sometimes lost.
> > + IDENTIFICATION DIVISION.
> > + PROGRAM-ID. check88.
> > +
> > + DATA DIVISION.
> > + WORKING-STORAGE SECTION.
> > + 01 Check88 PIC XXX VALUE SPACE.
> > + 88 CheckSpace VALUE SPACE.
> > + 88 CheckHi VALUE HIGH-VALUES.
> > + 88 CheckLo VALUE LOW-VALUES.
> > + 88 CheckZero VALUE ZERO.
> > + 88 CheckQuotes VALUE QUOTE.
> > + 88 CheckBob VALUE "bob".
> > + 88 CheckBinary VALUE X"000102". *> { dg-warning .*embedded.* }
I'd suggest *> { dg-warning "embedded" } here (or if there is complicated
quoting, *> { dg-warning {embedded} }), it isn't needed to add .* at the start
and end, the regexp doesn't have ^ and $ implicitly added around it.
Note, if you want to use .* somewhere in the middle, better use
\[^\n\r\]* in the "" strings (I think just [^\n\r] in the {} ones).
I don't know what the line length limits in COBOL are (and if it applies to
comments too), it is also possible to put the directive on a separate line
and refer for diagnostics on previous (or next line):
88 CheckBinary VALUE X"000102".
*> { dg-warning "embedded" "" { target *-*-* } .-1 }
> > --- /dev/null
> > +++ b/gcc/testsuite/cobol.dg/group1/dg.exp
I'd strongly advise against putting hundreds of copies of the same
*.exp driver everywhere.
It is expensive, shows up visibly in the *.log/*.sum files and
complicates running individual tests.
You can run individual tests through e.g.
make check-cobol RUNTESTFLAGS="dg.exp='fail.cob pa*.cob'"
If every directory has its own *.exp file without a reason (reason
can be different rules on what to do in the directory), then you'd
need to remember or search to find out that to run your
check_88.cob test alone you need to use
make check-cobol RUNTESTFLAGS=group1.exp=check_88.cob
What you want instead is modify the existing dg.exp so that it
handles subdirectories.
E.g. the g++.dg/dg.exp has
# Recursively find files in $dir and subdirs, do not walk into subdirs
# that contain their own .exp file.
proc find-cxx-tests { dir suffix } {
set tests [lsort [glob -nocomplain -directory $dir "*.$suffix" ]]
foreach subdir [lsort [glob -nocomplain -type d -directory $dir *]] {
if { [glob -nocomplain -directory $subdir *.exp] eq "" } {
eval lappend tests [find-cxx-tests $subdir $suffix]
}
}
return $tests
}
set tests [find-cxx-tests $srcdir/$subdir {C}]
# Main loop.
g++-dg-runtest $tests "" $DEFAULT_CXXFLAGS
So, that would be for COBOL
# Recursively find files in $dir and subdirs, do not walk into subdirs
# that contain their own .exp file.
proc find-cob-tests { dir suffix } {
set tests [lsort [glob -nocomplain -directory $dir "*.$suffix" ]]
foreach subdir [lsort [glob -nocomplain -type d -directory $dir *]] {
if { [glob -nocomplain -directory $subdir *.exp] eq "" } {
eval lappend tests [find-cob-tests $subdir $suffix]
}
}
return $tests
}
set tests [find-cob-tests $srcdir/$subdir {cob}]
# Main loop.
if [check_effective_target_cobol] {
cobol-dg-runtest $tests "" $all_flags
}
Jakub