Download as pdf or txt
Download as pdf or txt
You are on page 1of 17

DOCUMENT MODULE:

USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL


CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 1

The GnuCOBOL DEBUGGER


HOW TO USE COBGDB

Table of Contents

Table of Contents .....................................................................................................................................................1

1. Introduction ...................................................................................................................................................2
1.1. Installing the debugger on Windows.........................................................................................................2
1.2. Compile and debug a program .................................................................................................................2
1.3. Main commands .......................................................................................................................................4

2. Tutorial - Sample Debugging Session ...........................................................................................................5

3. Test Program Source Code ......................................................................................................................... 13

4. Document Change Log ............................................................................................................................... 17

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 2

1. Introduction

COBGDB is a command-line application, programmed in C, designed to assist in debugging GnuCOBOL code


using GDB. The project is hosted at https://github.com/marcsosduma/cobgdb

The application is based on the extension for Visual Studio Code (VSCode) created by Oleg Kunitsyn, which can
be found on GitHub: https://github.com/OlegKunitsyn/gnucobol-debug.

warning: COBGDB is currently under development.

In the Windows subdirectory, the executable program for this operating system is available.
To compile the code on Windows, you can use MinGW.
The Makefile is configured to generate the program for both Windows and Linux.

1.1. Installing the debugger on Windows

On Windows, just download cobgdb.exe from


https://github.com/marcsosduma/cobgdb/tree/main/windows and move cobgdb.exe to the "bin" folder of
your GnuCOBOL installation (the same folder where cobc is located)

or

first install MinGW (Minimalist GNU for Windows).


Then execute the make ('mingw32-make' for Windows) command to compile the code.

1.2. Compile and debug a program


Run the example program using the following command: cobgdb customer.cob -x -lpdcurses
Note: '-lpdcurses' is an instance of an argument that can be indirectly passed to ' cobc' by 'cobgdb,' even if
it is not used by 'cobgdb' itself.
or, other example, use : cobgdb customer.cob -x

COBGDB takes one or more programs with COB/CBL extension as parameters and runs the GnuCOBOL
compiler with the following format:
cobc -g -fsource-location -ftraceall -v -free -O0 -x prog.cob prog2.cob ...

To debug multiple programs, use COBGDB with the following syntax:


cobgdb prog.cob subprog1.cob subprog2.cob

You can run GDB/GDBSERVER remotely using the "A" (Attach) key.
COBGDB will prompt you to provide the server and port in the format server: port or the PID of the application.
Example:
 localhost: 5555
 9112

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 3

COBGDB running:

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 4

1.3. Main commands

 ? (Help) Show the HELP window


 B (Breakpoint) - Sets a breakpoint at a specific point in the code.
 R (Run) - Runs the program until a breakpoint is encountered.
 C (Cursor) - Runs the program until it reaches the selected line.
 N (Next) - Runs the program until the next line but does not enter a subroutine executed by CALL or
PERFORM.
 S (Step) - Runs the program until the next line.
 G (Go) - Continues the program execution until it encounters a stopping point: breakpoint, end of the
program, or the return from a subroutine (PERFORM/CALL).
 V (Variables) - Displays the set of variables for the running program.
 H (sHow) - Shows the values of variables for the selected line.
 F (File) - Allows selecting the source file for debugging.
 A (Attach) - Attach to GDBSERVER or Application PID.
 Q (Quit) - Quits the program.

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 5

2. Tutorial - Sample Debugging Session

After executing cobgdb customer.cob -x the application displays following screen:

Here you can type ? to display the HELP window

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 6

and scroll with cursor keys UP and DOWN

use ESC to return to debugging session.

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 7

here you can type "B" to create a breakpoint and "R" for the system to run the application.

Scroll to line 116 and type B (to set a Breakpoint),


The application displays a "B" on the left of the line.
Type B again when you want to delete the Breakpoint.

Now you can type R (run) to execute the program until a breakpoint is detected:
The system reach the breakpoint and displays a ">" symbol to the left of the line to be executed.

Note that the debugger automatically shows the variables content from the line in execution.
From that moment on, you can use the keys "S" (Step), "N" (Next) and "G" (go) to debug the application.

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 8

The 'H' key allows you to view the variables on the highlighted line.
type H to display line variables

type V to display the list of all program variables:

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 9

scroll with cursor key UP and DOWN in this list to the variable WS-MODULE and type Enter: the application
displays its subfields

Now you can select a subfield whit cursor UP and down and type "C" (Change)
type a new value for that variable into the pop-up window and press enter:

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 10

type "R" (Return) to go back to the debugging session:

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 11

type "S" (Step) to execute the DISPLAY statement at line 116

type "S" again to execute the ACCEPT statement at line 117:

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 12

Note:
The application will run in a separate window.
The 'Accept' command switches the focus between windows.
In other words, after entering information via 'Accept,' it is necessary to click on the 'debugger' window to continue
debugging.

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 13

3. Test Program Source Code

FILE CUSTOMER.COB.
>>SOURCE FORMAT IS FREE
IDENTIFICATION DIVISION.
PROGRAM-ID. CUSTOMER.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER.
GNUCOBOL.
OBJECT-COMPUTER.
GNUCOBOL.
SPECIAL-NAMES.
DECIMAL-POINT IS COMMA.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT FILE1 ASSIGN TO DISK
ORGANIZATION IS INDEXED
ACCESS MODE IS RANDOM
FILE STATUS IS FS-STAT
RECORD KEY IS FS-KEY.

DATA DIVISION.
FILE SECTION.
FD FILE1 VALUE OF FILE-ID IS "customers.dat".
01 FILE1-REC.
05 FS-KEY.
10 FS-PHONE PIC 9(09) BLANK WHEN ZEROS.
05 FS-NAME PIC X(40).
05 FS-ADDRESS PIC X(40).
05 FILLER PIC X(20).

WORKING-STORAGE SECTION.

01 WS-MODULE.
05 FILLER PIC X(12) VALUE "CUSTOMERS - ".
05 WS-OP PIC X(20) VALUE SPACES.

77 WS-CHOICE PIC X.
88 E-INCLUDE VALUE IS "1".
88 E-CONSULT VALUE IS "2".
88 E-UPDATE VALUE IS "3".
88 E-DELETE VALUE IS "4".
88 E-EXIT VALUE IS "X" "x".
77 FS-STAT PIC 9(02).
88 FS-OK VALUE ZEROS.
88 FS-CANCEL VALUE 99.
88 FS-NOT-EXIST VALUE 35.
77 WS-ERROR PIC X.
88 E-YES VALUES ARE "Y" "y".

77 WS_NUMR PIC 999.


77 WS-NUMC012 PIC 999.
77 BACK-COLOR PIC 9 VALUE 1.
77 FRONT-COLOR PIC 9 VALUE 6.

77 WS-STATUS PIC X(30).


77 WS-ERRMSG PIC X(80).

COPY screenio.

SCREEN SECTION.
01 SS-CLS.
05 SS-FILLER.
10 BLANK SCREEN.
10 LINE 01 COLUMN 01 ERASE EOL

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 14

BACKGROUND-COLOR BACK-COLOR.
10 LINE WS_NUMR COLUMN 01 ERASE EOL
BACKGROUND-COLOR BACK-COLOR.
05 SS-HEADER.
10 LINE 01 COLUMN 02 PIC X(31) FROM WS-MODULE
HIGHLIGHT FOREGROUND-COLOR FRONT-COLOR
BACKGROUND-COLOR BACK-COLOR.
05 SS-STATUS.
10 LINE WS_NUMR COLUMN 2 ERASE EOL PIC X(30)
FROM WS-STATUS HIGHLIGHT
FOREGROUND-COLOR FRONT-COLOR
BACKGROUND-COLOR BACK-COLOR.

01 SS-MENU FOREGROUND-COLOR 6.
05 LINE 07 COLUMN 15 VALUE "1 - INCLUDE".
05 LINE 08 COLUMN 15 VALUE "2 - CONSULT".
05 LINE 09 COLUMN 15 VALUE "3 - UPDATE".
05 LINE 10 COLUMN 15 VALUE "4 - DELETE".
05 LINE 11 COLUMN 15 VALUE "X - EXIT".
05 LINE 13 COLUMN 15 VALUE "CHOICE: ".
05 LINE 13 COL PLUS 1 USING WS-CHOICE AUTO.

01 SS-RECORD-SCREEN.
05 SS-KEY FOREGROUND-COLOR 2.
10 LINE 10 COLUMN 10 VALUE " PHONE:".
10 COLUMN PLUS 2 PIC 9(09) USING FS-PHONE
BLANK WHEN ZEROS.
05 SS-DATA.
10 LINE 11 COLUMN 10 VALUE " NAME:".
10 COLUMN PLUS 2 PIC X(40) USING FS-NAME.
10 LINE 12 COLUMN 10 VALUE "ADDRESS:".
10 COLUMN PLUS 2 PIC X(40) USING FS-ADDRESS.

01 SS-ERROR.
05 FILLER FOREGROUND-COLOR 4 BACKGROUND-COLOR 1 HIGHLIGHT.
10 LINE WS_NUMR COLUMN 2 PIC X(80) FROM WS-ERRMSG BELL.
10 COLUMN PLUS 2 TO WS-ERROR.

PROCEDURE DIVISION.
001-START.
SET ENVIRONMENT 'COB_SCREEN_EXCEPTIONS' TO 'Y'
SET ENVIRONMENT 'COB_SCREEN_ESC' TO 'Y'
SET ENVIRONMENT 'ESCDELAY' TO '25'
*>CALL "SYSTEM" USING "chcp 437" WS-STATUS
*>CALL "SYSTEM" USING "mode con: lines=24 cols=80" *> WS-STATUS
ACCEPT WS_NUMR FROM LINES
ACCEPT WS-NUMC012 FROM COLUMNS *> WS-STATUS
PERFORM 007-OPEN-FILES
PERFORM UNTIL E-EXIT
MOVE "MENU" TO WS-OP
MOVE "CHOOSE AN OPTION" TO WS-STATUS *> WS-STATUS
MOVE SPACES TO WS-CHOICE
DISPLAY SS-CLS
ACCEPT SS-MENU
EVALUATE TRUE
WHEN E-INCLUDE
PERFORM 002-INCLUDE THRU 002-INCLUDE-END
WHEN E-CONSULT
PERFORM 003-CONSULT THRU 003-CONSULT-END
WHEN E-UPDATE
PERFORM 004-UPDATE THRU 004-UPDATE-END
WHEN E-DELETE
PERFORM 005-DELETE THRU 005-DELETE-END
END-EVALUATE
END-PERFORM.
001-FINISH.
CLOSE FILE1.
STOP RUN.

*> -----------------------------------
002-INCLUDE.
MOVE "INCLUDE" TO WS-OP.

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 15

MOVE "ESC TO EXIT" TO WS-STATUS.


DISPLAY SS-CLS.
MOVE SPACES TO FILE1-REC.
002-INCLUDE-LOOP.
ACCEPT SS-RECORD-SCREEN.
IF COB-CRT-STATUS = COB-SCR-ESC
GO 002-INCLUDE-END
END-IF
IF FS-NAME EQUAL SPACES OR FS-ADDRESS EQUAL SPACES
MOVE "PLEASE PROVIDE NAME AND ADDRESS" TO WS-ERRMSG
PERFORM 008-SHOW-ERROR
GO 002-INCLUDE-LOOP
END-IF
WRITE FILE1-REC
INVALID KEY
MOVE "CUSTOMER ALREADY EXISTS" TO WS-ERRMSG
PERFORM 008-SHOW-ERROR
MOVE ZEROS TO FS-KEY
END-WRITE.
GO 002-INCLUDE-LOOP.
002-INCLUDE-END.

*> -----------------------------------
003-CONSULT.
MOVE "CONSULT" TO WS-OP.
MOVE "ESC TO EXIT" TO WS-STATUS.
DISPLAY SS-CLS.
003-CONSULT-LOOP.
MOVE SPACES TO FILE1-REC.
DISPLAY SS-RECORD-SCREEN.
PERFORM 006-READ-CUSTOMER THRU 006-READ-CUSTOMER-END.
IF FS-CANCEL
GO 003-CONSULT-END
END-IF
IF FS-OK
DISPLAY SS-DATA
MOVE "PRESS ENTER" TO WS-ERRMSG
PERFORM 008-SHOW-ERROR
END-IF.
GO 003-CONSULT-LOOP.
003-CONSULT-END.

*> -----------------------------------
004-UPDATE.
MOVE "UPDATE" TO WS-OP.
MOVE "ESC TO EXIT" TO WS-STATUS.
DISPLAY SS-CLS.
004-UPDATE-LOOP.
MOVE SPACES TO FILE1-REC.
DISPLAY SS-RECORD-SCREEN.
PERFORM 006-READ-CUSTOMER THRU 006-READ-CUSTOMER-END.
IF FS-CANCEL
GO TO 004-UPDATE-END
END-IF
IF FS-OK
ACCEPT SS-DATA
IF COB-CRT-STATUS = COB-SCR-ESC
GO 004-UPDATE-LOOP
END-IF
ELSE
GO 004-UPDATE-LOOP
END-IF
REWRITE FILE1-REC
INVALID KEY
MOVE "ERROR WRITING RECORD" TO WS-ERRMSG
PERFORM 008-SHOW-ERROR
NOT INVALID KEY
CONTINUE
END-REWRITE.
GO 004-UPDATE-LOOP.
004-UPDATE-END.

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 16

*> -----------------------------------
005-DELETE.
MOVE "DELETE" TO WS-OP.
MOVE "ESC TO EXIT" TO WS-STATUS.
DISPLAY SS-CLS.
MOVE SPACES TO FILE1-REC.
DISPLAY SS-RECORD-SCREEN.
PERFORM 006-READ-CUSTOMER THRU 006-READ-CUSTOMER-END.
IF FS-CANCEL
GO 005-DELETE-END
END-IF
IF NOT FS-OK
GO 005-DELETE
END-IF
DISPLAY SS-DATA.
MOVE "N" TO WS-ERROR.
MOVE "CONFIRM CUSTOMER DELETION (Y/N)?" TO WS-ERRMSG.
ACCEPT SS-ERROR.
IF NOT E-YES
GO 005-DELETE-END
END-IF
DELETE FILE1
INVALID KEY
MOVE "ERROR DELETING RECORD" TO WS-ERRMSG
PERFORM 008-SHOW-ERROR
END-DELETE.
005-DELETE-END.

*> -----------------------------------
*> READS CUSTOMER AND SHOWS ERROR MESSAGE IF KEY DOESN'T EXIST
006-READ-CUSTOMER.
ACCEPT SS-KEY.
IF NOT COB-CRT-STATUS = COB-SCR-ESC
READ FILE1
INVALID KEY
MOVE "CUSTOMER NOT FOUND" TO WS-ERRMSG
PERFORM 008-SHOW-ERROR
END-READ
ELSE
MOVE 99 to FS-STAT
END-IF.
006-READ-CUSTOMER-END.

*> -----------------------------------
*> OPENS FILES FOR INPUT AND OUTPUT
007-OPEN-FILES.
OPEN I-O FILE1
IF FS-NOT-EXIST THEN
OPEN OUTPUT FILE1
CLOSE FILE1
OPEN I-O FILE1
END-IF.

*> -----------------------------------
*> SHOWS MESSAGE, WAITS FOR ENTER, UPDATES STATUS BAR
008-SHOW-ERROR.
DISPLAY SS-ERROR
ACCEPT SS-ERROR
DISPLAY SS-STATUS.

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023


DOCUMENT MODULE:
USING COBGDB FOR GnuCOBOL PAGE GnuCOBOL
CODE xxxxxxxxxx

GC-901 GC-XXXXXX Author: Eugenio Di Lorenzo 17

4. Document Change Log

CHANGE LOG

Version1 of 2023.12.12.
First release

- File: “GnuCOBOL-DEBUGGER-V01-20231212.odt” - Saved: 21/12/2023

You might also like