Re: straight c grid example with ncurses not drawing grid ...any idea?

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

 



You'll get better results using GnuCOBOL 3.3-dev and the line drawing extension via the attribute - libcob will then do the conversion (with the result depending on underlying curses and terminal capabilities including font). Check the NEWS file to learn more about this.


Am 19. Oktober 2024 22:25:37 MESZ schrieb Jim McNamara <jmcnamara10001@xxxxxxxxx>:
cobc -x -o my_program init.cob $(pkg-config --cflags --libs ncurses) -static
$> ./NcursesInlineCExample.exe

this above... or this below... does not produce a grid

$> cobc -x -o NcursesInlineCExample init.cob -lncurses -static
$> ./NcursesInlineCExample.exe

it just kind of waits out there hanging around not doing anything...

IDENTIFICATION DIVISION.
PROGRAM-ID. NcursesInlineCExample.

ENVIRONMENT DIVISION.
CONFIGURATION SECTION.

DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-RETURN-CODE PIC S9(9) COMP.

LINKAGE SECTION.
01 C-RETURN-CODE PIC S9(9) COMP.

PROCEDURE DIVISION.
MAIN-PROCEDURE.
PERFORM C-INITIALIZE-NCURSES.
IF WS-RETURN-CODE < 0
DISPLAY "Failed to initialize ncurses."
ELSE
PERFORM C-SHOW-GRID
PERFORM C-WAIT-FOR-KEY
END-IF.
PERFORM C-FINALIZE-NCURSES.
STOP RUN.

C-INITIALIZE-NCURSES.
CALL 'initscr' USING C-RETURN-CODE.

C-SHOW-GRID.
CALL 'mvprintw' USING 1 1 "+---+---+".
CALL 'mvprintw' USING 2 1 "| 1 | 2 |".
CALL 'mvprintw' USING 3 1 "+---+---+".
CALL 'mvprintw' USING 4 1 "| 3 | 4 |".
CALL 'mvprintw' USING 5 1 "+---+---+".
CALL 'refresh'.

C-WAIT-FOR-KEY.
CALL 'getch'.

C-FINALIZE-NCURSES.
CALL 'endwin'.
its the call to mvprintw that isnt executing right away thanks

jim




Sent with Proton Mail secure email.


[Index of Archives]     [Gcc Help]     [Linux USB Devel]     [Linux Audio Users]     [Yosemite Info]     [Linux Kernel]     [Linux SCSI]     [Big List of Linux Books]

  Powered by Linux