My program is giving the following error followed by a hard crash when I attempt to write to the system log.
---------------------------
Error
---------------------------
Invalid or missing parameter to "C$SYSLOG"
COBOL error at 000046 in csyslog.acu
("csyslog.cbl", line 50)
---------------------------
OK
---------------------------
Here is my source code. Do you see what the problem might be on line 50?
IDENTIFICATION DIVISION.
PROGRAM-ID. CSYSLOG.
DATA DIVISION.
WORKING-STORAGE SECTION.
* Opcodes for C$SYSLOG
* These codes were copied from acucobol.def.
78 CSYSLOG-OPEN VALUE 0.
78 CSYSLOG-WRITE VALUE 1.
78 CSYSLOG-CLOSE VALUE 2.
* Priority codes for C$SYSLOG
* These codes were copied from acucobol.def.
78 CSYSLOG-PRIORITY-SUCCESS VALUE 0.
78 CSYSLOG-PRIORITY-INFORMATION VALUE 1.
78 CSYSLOG-PRIORITY-WARNING VALUE 2.
78 CSYSLOG-PRIORITY-ERROR VALUE 3.
* Data items to be used as C$SYSLOG parameters.
* The NULL value in CSYSLOG-DOMAIN means "local machine".
78 W-CSYSLOG-DOMAIN VALUE NULL.
78 W-CSYSLOG-APPNAME VALUE "App name goes here".
01 W-CSYSLOG-PRIORITY PIC S9 VALUE ZERO.
01 W-CSYSLOG-MESSAGE PIC X(1024) VALUE SPACE.
* Other working fields.
01 W-CALL-STATUS PIC S9(2).
01 W-PROG-PATHNAME PIC X(260).
01 W-TRAILING-SPACE-COUNT PIC S9(9) COMP.
01 W-TMP-STRING-LENGTH PIC S9(9) COMP.
01 W-SUCCESS-MESSAGE PIC X(1024) VALUE SPACE.
01 W-INFO-MESSAGE PIC X(1024) VALUE SPACE.
01 W-WARNING-MESSAGE PIC X(1024) VALUE SPACE.
01 W-ERROR-MESSAGE PIC X(1024) VALUE SPACE.
PROCEDURE DIVISION.
MAIN-ROUTINE.
PERFORM SETUP-TEST-DATA THROUGH SETUP-TEST-DATA-EXIT
* Open the system log.
CALL "C$SYSLOG"
USING CSYSLOG-OPEN, W-CSYSLOG-DOMAIN, W-CSYSLOG-APPNAME
ON EXCEPTION CONTINUE
END-CALL
* Write a "Success" log entry.
MOVE CSYSLOG-PRIORITY-SUCCESS TO W-CSYSLOG-PRIORITY
MOVE W-SUCCESS-MESSAGE TO W-CSYSLOG-MESSAGE
CALL "C$SYSLOG"
USING CSYSLOG-WRITE, W-CSYSLOG-PRIORITY, W-CSYSLOG-MESSAGE
ON EXCEPTION CONTINUE
END-CALL
* Write an "Information" log entry.
MOVE CSYSLOG-PRIORITY-INFORMATION TO W-CSYSLOG-PRIORITY
MOVE W-INFO-MESSAGE TO W-CSYSLOG-MESSAGE
CALL "C$SYSLOG"
USING CSYSLOG-WRITE, W-CSYSLOG-PRIORITY, W-CSYSLOG-MESSAGE
ON EXCEPTION CONTINUE
END-CALL
* Write a "Warning" log entry.
MOVE CSYSLOG-PRIORITY-WARNING TO W-CSYSLOG-PRIORITY
MOVE W-WARNING-MESSAGE TO W-CSYSLOG-MESSAGE
CALL "C$SYSLOG"
USING CSYSLOG-WRITE, W-CSYSLOG-PRIORITY, W-CSYSLOG-MESSAGE
ON EXCEPTION CONTINUE
END-CALL
* Write an "Error" log entry.
MOVE CSYSLOG-PRIORITY-ERROR TO W-CSYSLOG-PRIORITY
MOVE W-ERROR-MESSAGE TO W-CSYSLOG-MESSAGE
CALL "C$SYSLOG"
USING CSYSLOG-WRITE, W-CSYSLOG-PRIORITY, W-CSYSLOG-MESSAGE
ON EXCEPTION CONTINUE
END-CALL
* Close the system log.
CALL "C$SYSLOG"
USING CSYSLOG-CLOSE
ON EXCEPTION CONTINUE
END-CALL
GOBACK 0.
SETUP-TEST-DATA.
* Get the pathname for the currently executing program.
CALL "C$MYFILE"
USING W-PROG-PATHNAME
GIVING W-CALL-STATUS
ON EXCEPTION CONTINUE
END-CALL
IF W-CALL-STATUS = -1
MOVE "[program pathname could not be retrieved]"
TO W-PROG-PATHNAME
END-IF
* Compute the length of the program's pathname.
MOVE 0 TO W-TRAILING-SPACE-COUNT
INSPECT W-PROG-PATHNAME
TALLYING W-TRAILING-SPACE-COUNT
FOR TRAILING SPACES
COMPUTE W-TMP-STRING-LENGTH
= FUNCTION LENGTH(W-PROG-PATHNAME)
- W-TRAILING-SPACE-COUNT
* Compute the success/info/warning/error messages.
STRING
"Some successful outcome was logged by "
W-PROG-PATHNAME(1:W-TMP-STRING-LENGTH)
"." DELIMITED SIZE
INTO W-SUCCESS-MESSAGE
END-STRING
STRING
"Some information was logged by "
W-PROG-PATHNAME(1:W-TMP-STRING-LENGTH)
"." DELIMITED SIZE
INTO W-INFO-MESSAGE
END-STRING
STRING
"Some warning was logged by "
W-PROG-PATHNAME(1:W-TMP-STRING-LENGTH)
"." DELIMITED SIZE
INTO W-WARNING-MESSAGE
END-STRING
STRING
"Some error was logged by "
W-PROG-PATHNAME(1:W-TMP-STRING-LENGTH)
"." DELIMITED SIZE
INTO W-ERROR-MESSAGE
END-STRING
.
SETUP-TEST-DATA-EXIT.
EXIT.
The commands used to compile and execute were:
ccbl32 -Ga csyslog.cbl
wrun32 -d csyslog.acu
The operating system is 64-bit Windows 7. The AcuCOBOL version is a 32-bit build of version 9.2.1.
Thanks in advance for any assistance!
#CSYSLOG
#libraryroutines