From 705204d36988011e2effa07a09d72fb8f8f33c2a Mon Sep 17 00:00:00 2001
From: Bob Dubner <rdubner@symas.com>
Date: Wed, 3 Jan 2024 13:23:06 -0500
Subject: [PATCH] Put failures/playpen back into the repository

---
 gcc/cobol/failures/.gitignore             |  1 -
 gcc/cobol/failures/playpen/Makefile       |  1 +
 gcc/cobol/failures/playpen/input.txt      |  0
 gcc/cobol/failures/playpen/playpen.cbl    | 37 +++++++++++++++++++++++
 gcc/cobol/tests/c-to-cobol/call_stuff.cbl |  4 +--
 5 files changed, 40 insertions(+), 3 deletions(-)
 create mode 100644 gcc/cobol/failures/playpen/Makefile
 create mode 100644 gcc/cobol/failures/playpen/input.txt
 create mode 100644 gcc/cobol/failures/playpen/playpen.cbl

diff --git a/gcc/cobol/failures/.gitignore b/gcc/cobol/failures/.gitignore
index 2062f0d68afc..b58c7495295e 100644
--- a/gcc/cobol/failures/.gitignore
+++ b/gcc/cobol/failures/.gitignore
@@ -10,4 +10,3 @@ dump.txt
 *.html
 XXXXX*
 REPORTT
-playpen/
diff --git a/gcc/cobol/failures/playpen/Makefile b/gcc/cobol/failures/playpen/Makefile
new file mode 100644
index 000000000000..f77e46b3451a
--- /dev/null
+++ b/gcc/cobol/failures/playpen/Makefile
@@ -0,0 +1 @@
+include ../Makefile.inc
diff --git a/gcc/cobol/failures/playpen/input.txt b/gcc/cobol/failures/playpen/input.txt
new file mode 100644
index 000000000000..e69de29bb2d1
diff --git a/gcc/cobol/failures/playpen/playpen.cbl b/gcc/cobol/failures/playpen/playpen.cbl
new file mode 100644
index 000000000000..80755fc361bd
--- /dev/null
+++ b/gcc/cobol/failures/playpen/playpen.cbl
@@ -0,0 +1,37 @@
+        IDENTIFICATION   DIVISION.
+        FUNCTION-ID.      callee.
+        DATA             DIVISION.
+        LOCAL-STORAGE    SECTION.
+        01 LCL-X         PIC 999 .
+        LINKAGE          SECTION.
+        01 parm          PIC 999.
+        01 retval        PIC 999.
+        PROCEDURE        DIVISION USING parm RETURNING retval.
+            display "On entry, parm is: " parm
+            move parm to lcl-x
+            move parm to retval
+            subtract 1 from parm
+            if parm > 0
+                display "A The function returns " function callee(parm).
+            if lcl-x not equal to retval
+                display "On exit, lcl-s and retval are: " lcl-x " and " retval
+                display "But they should be equal to each other"
+                end-if
+            goback.
+            end function callee.
+
+        IDENTIFICATION   DIVISION.
+        PROGRAM-ID.      caller.
+        ENVIRONMENT      DIVISION.
+        CONFIGURATION    SECTION.
+        REPOSITORY.
+                         FUNCTION callee.
+        DATA             DIVISION.
+        WORKING-STORAGE  SECTION.
+        01 val           PIC 999 VALUE 5.
+        PROCEDURE        DIVISION.
+           DISPLAY "Starting value is: " val
+           display "B The function returns " function callee(val).
+           STOP RUN.
+           end program caller.
+
diff --git a/gcc/cobol/tests/c-to-cobol/call_stuff.cbl b/gcc/cobol/tests/c-to-cobol/call_stuff.cbl
index 10513501abc7..a76c2919a856 100644
--- a/gcc/cobol/tests/c-to-cobol/call_stuff.cbl
+++ b/gcc/cobol/tests/c-to-cobol/call_stuff.cbl
@@ -6,7 +6,7 @@ WORKING-STORAGE SECTION.
 01  CWD          PIC X(100).
 01  RETURNED-CWD PIC X(100).
 01  LEN_OF_CWD   PIC 999 VALUE 100.
-01  USR-LOCAL-BIN  PIC X(14) VALUE "/usr/local/bin".
+01  USR-LOCAL-BIN  PIC X(15) VALUE "/usr/local/bin".
 01  CHDIR_RETURN PIC S999 BINARY.
 
 01  var1 pic x(24) VALUE "I shouldn't change".
@@ -17,7 +17,7 @@ WORKING-STORAGE SECTION.
 
 PROCEDURE DIVISION.
 
-    CALL    "chdir"
+    MOVE X'00' TO USR-LOCAL-BIN(15:1)
     CALL    "chdir"
             USING BY CONTENT USR-LOCAL-BIN
             RETURNING CHDIR_RETURN
-- 
GitLab