Menu

National character sets -Hebrew

GnuCOBOL
2021-12-29
2021-12-29
  • david myers

    david myers - 2021-12-29

    Hi, Just starting out with GNUCobol (3).
    Is it possible to code the SCREEN SECTION to DISPLAY / ACCEPT Hebrew?

    My encoding is ASCII hex 80 (א) - hex 9A (ת) , in Notepad++ the character set is Hebrew > OEM 862.

    Can I enable Display / Accept for this charater set? If so how?

    Any help much appreciated.

     
  • Simon Sobisch

    Simon Sobisch - 2021-12-29

    Looks like you just have a single-byte encoding here - in this case there should be no "general" problem as long as:

    • NPP has correct encoding for the COBOL source (seems to be the case)
    • your fields use PIC X
    • your console/terminal has the same encoding (which one do you use btw, plain "cmd" - what does chcp says?)
    • plain DISPLAY / ACCEPT in a program without a SCREEN SECTION works
    • for SCREEN SECTION: the used library is not compiled with WIDE or UNICODE support (because then it also expects and returns multi-byte characters); possibly it needs to be up-to-date, too, I remember there were some changes related to extended ASCII in the last months in PDCurses / PDCursesMod

    Alternative: you use PIC N for Hebrew, change the encoding to UTF-8, have PDCurses / PDCursesMod as UNICODE build, either only DISPLAY/ACCEPT "extended" (the easiest thing would be to do a DISPLAY SPACES AT 0101 in the first program) or use a console that works with UTF-8.

    But I have no clue how RTL works in cmd.exe or PDCurses/PDCursesMod...

     

    Last edit: Simon Sobisch 2021-12-29
  • david myers

    david myers - 2021-12-29

    Hi Simon, Thanks for your reply.
    chcp says:
    Active code page: 862

    I tried this code:

           IDENTIFICATION DIVISION.
           PROGRAM-ID. DISP-ACCP.
           DATA DIVISION.
           FILE SECTION.
           WORKING-STORAGE SECTION.
               01 WS-INPUT1 PIC X(8).
               01 WS-INPUT2 PIC X(8).
           PROCEDURE DIVISION.
           MAIN-PROCEDURE.
              ACCEPT WS-INPUT1.
              DISPLAY WS-INPUT1.
              ACCEPT WS-INPUT2.
              DISPLAY WS-INPUT2.
              STOP RUN.
           END PROGRAM DISP-ACCP.
    

    cobc -x disp-accp.cbl
    compiles without error
    but when I switch to Hebrew in command prompt (before running disp-accp) I just get a framed '?' for each character - English's ok.
    So there's another problem before gnucobol - will get back to you when I've sorted that.
    Thanks

     
    • Simon Sobisch

      Simon Sobisch - 2021-12-29

      You'd want to check very first if your console is setup correctly:

      • right click on cmd's window title -> settings
      • first tab should have your codepage correctly named
      • legacy mode may not (or may?) be active [just keep that in mind and toggle it if everyhting else is fine]
      • second tab for the fonts: uses a true-type font that also supports Hebrew characters

      If you don't know if the used font supports Hebrew characters recheck in font manager (or however that is called now).

       
  • david myers

    david myers - 2021-12-29

    Hi Simon,
    Thanks very much for this, following your advice I've managed to get display / accept without the screen section to workfor hebrew text.
    I've downloaded PDCurses 3.8, and would like to check if it supports ASCII Hebrew in the Screen Section but have no idea how to do that.
    Thanks for any help

     
    • David Wall

      David Wall - 2021-12-29

      3.8 is Feb 2019 - why not look for PDCursesMod - the latest is Nov 2021.
      https://github.com/Bill-Gray/PDCursesMod

      In fact it was updated 2 days ago.

       

      Last edit: David Wall 2021-12-29
  • david myers

    david myers - 2021-12-29

    Hi David, thanks for this. I've downloaded PDCursesMod from Github.
    Any pointers on how I can use it with gnuCOBOL Screen-Section.

    Thanks

     

Log in to post a comment.