diff --git a/gcc/cobol/UAT/testsuite.src/syn_copy.at b/gcc/cobol/UAT/testsuite.src/syn_copy.at
index d78b18a90db7e2d9e80ba1bcaedf43799a0c8255..2fe7026f4ddefc41542577bdcc20c970aa6ead49 100644
--- a/gcc/cobol/UAT/testsuite.src/syn_copy.at
+++ b/gcc/cobol/UAT/testsuite.src/syn_copy.at
@@ -278,20 +278,14 @@ AT_DATA([copy3.CPY],
 [       COPY "copy1.CPY".
        01 TEST-VAR3 PIC X(2) VALUE "V3".
 ])
-AT_CHECK([$COMPILE_ONLY prog.cob], [1], [], stderr)
-# This strangeness is because autom4te eats trailing spaces.  The documentation
-# refers to this wacked-out behavior as a "feature".  So, we eat up trailing
-# spaces, too.
-AT_CHECK([sed 's/^\(.*\)[ ]$/\1/g' stderr], [1],
-[depth line copybook filename
------ ---- ------------------------------------------------
-    1    1 prog.cob
-    2    1 copy1.CPY
-    3    1 copy2.CPY
-    4    1 copy3.CPY
-prog.cob:1: error: recursive copybook: 'copy1.CPY' includes itself
-    1 | 
-prog.cob:1: error: copybook 'copy1.CPY' not found
+AT_CHECK([$COMPILE_ONLY prog.cob], [1], [], [In file included from copy3.CPY:128,
+                 from copy2.CPY:128,
+                 from copy1.CPY:128,
+                 from prog.cob:128:
+copy1.CPY:2:1: error: recursive copybook: 'copy1.CPY' includes itself
+    2 |        COPY copy2.
+      | ^
+copy1.CPY:2:1: error: copybook 'copy1.CPY' not found
 cobol1: error: failed compiling prog.cob
 ])
 AT_CLEANUP