Inserting PIC N data into an NCHAR column results in incorrect data held in the database.

 
0 Likes

Problem

Using COBSQL to pre-compile an Oracle SQL program which inserts PIC N data into a column defined as NCHAR  results in incorrect data held in the database.

Resolution


For PIC N variables and NCHAR columns you need to set the Oracle NLS_NCHAR environment variable to match the NLS_NCHAR_CHARACTERSET for the database.

So assuming a UTF-16 setting for the database of NLS_NCHAR_CHARACTERSET=AL16UTF16, set NLS_NCHAR=AL16UTF16 on the client.

Then recompile using only default Pro*COBOL directives and the NSYMBOL(NATIONAL) Micro Focus compiler directive.  Running the test program (see below), resulted in the following inserted in the COL1 column when running on Linux:

"346C200020002000200020002000200020002000"

As you can see, the byte ordering appears to be reversed.  This can be changed if needed using UNICODE(PORTABLE) instead of the default UNICODE(NATIVE) directive, which gives:

"6C34002000200020002000200020002000200020"

In the above string you have 1 unicode character U 6C34 followed by 9 spaces (U 0020).


Demo program:

      $SET NSYMBOL(NATIONAL)
      $SET UNICODE(PORTABLE)
      $SET P(COBSQL) END-C CHARSET_PICN=NCHAR_CHARSET ENDP
      
       IDENTIFICATION DIVISION.
       PROGRAM-ID.    TESTN.

       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.

       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
       DATA DIVISION.
       FILE SECTION.
       WORKING-STORAGE SECTION.
           exec sql begin declare section end-exec.
       01 ws-char pic x(40).
       01  N1                          PIC  N(10).
       77  DB-STRING                   PIC  X(10)  VALUE "orcl1g".
       77  USERNAME                    PIC  X(10)  VALUE "scott".
       77  PASSWD                      PIC  X(20)  VALUE "tiger".
           exec sql end declare section end-exec.

           EXEC SQL INCLUDE SQLCA    END-EXEC.

       PROCEDURE DIVISION.
           MOVE NX'6C34'               TO N1.
           DISPLAY N1.

           EXEC SQL CONNECT :USERNAME IDENTIFIED BY :PASSWD
                    USING :DB-STRING
           END-EXEC.
           DISPLAY "connect sqlcode: " SQLCODE.
      *
           exec sql
             CREATE TABLE TESTNCHAR
             (COL1 NCHAR(10) DEFAULT(' ') NOT NULL)
           end-exec.

           display "create sqlcode: " sqlcode

           EXEC SQL
               INSERT INTO TESTNCHAR
                      ( COL1 )
               VALUES ( :N1 )
           END-EXEC.

           DISPLAY "insert sqlcode: " SQLCODE.

           exec sql
               select rawtohex(COL1)
               into :ws-char
               from TESTNCHAR
           end-exec.
           display "select sqlcode: " sqlcode " data: " ws-char

           exec sql drop table TESTNCHAR end-exec.
      *
           EXEC SQL COMMIT
           END-EXEC.
      *
           STOP RUN.

Comment List
Related
Recommended