Skip to main content
Question

Function NATIONAL-OF on linux

  • November 24, 2025
  • 4 replies
  • 19 views

M Carmen De Paz
Forum|alt.badge.img+2
Hello, we are migrating our Visual COBOL development for Eclipse from a AIX server to a Linux server. We have a utility to convert text from ASCII to UTF-8, but it has stopped working because the NATIONAL-OF function does not recognize UTF-8 characters in linux.

 the locale data are 

----AIX 

LANG=C
LC_COLLATE="C"
LC_CTYPE="C"
LC_MONETARY="C"
LC_NUMERIC="C"
LC_TIME="C"
LC_MESSAGES="C"
LC_ALL=

-----Linux

LANG=C
LC_CTYPE="C"
LC_NUMERIC="C"
LC_TIME="C"
LC_COLLATE="C"
LC_MONETARY="C"
LC_MESSAGES="C"
LC_PAPER="C"
LC_NAME="C"
LC_ADDRESS="C"
LC_TELEPHONE="C"
LC_MEASUREMENT="C"
LC_IDENTIFICATION="C"
LC_ALL=

And the code of the utility is :

       PROGRAM-ID. anook2
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       INPUT-OUTPUT SECTION.
       file-control.
           select futf8 assign to f-utf8
                  organization line sequential
                  status is io-estado.
           select fascii assign to f-ascii
                  organization line sequential
                  status is io-estado.
       DATA DIVISION.
       file section.
       fd  fascii.
       01  rascii pic x(50).
       fd  futf8.
       01  rutf8  pic x(150).
       WORKING-STORAGE SECTION.
       01  io-estado   pic xx.
           88 io-ok value zeros.
       01  l-cmd    pic x(250).
       01  rnat     pic n(50)   usage national.
       01  f-ascii   pic x(120) value spaces.
       01  f-utf8    pic x(120) value spaces.
       PROCEDURE DIVISION.
           accept l-cmd from command-line
           unstring l-cmd delimited all ' '
               into f-ascii  f-utf8

           open output futf8
           if not io-ok
              display '!! error fichero de salida->' f-utf8
              stop run
           end-if
           open input fascii
           perform until not io-ok
              read fascii
              if not io-ok exit perform end-if
              move function national-of(rascii, 819)     to rnat
              move function display-of(rnat, 1208) to rutf8
              write rutf8
           end-perform
           close fascii, futf8
           stop run.
 

We have a file in /tmp/ whose content is ó ( hexadecimal valueF3)

if we runs de program anook2 /tmp/fich_ent /tmp/fich_sal on AIX  the out file  has a hexadecimal value of C3B3(which is OK), but if uns de program anook2 /tmp/fich_ent /tmp/fich_sal on linux the out file  has a hexadecimal value of   E280 (error).

 

Any clues as to what the problem might be? Are we missing an environment variable? 
Any compilation options?


 


 

4 replies

Chris Glazier
Forum|alt.badge.img+2

According to the documentation for national-of here:
“Full support for a CCSID value other than 1208 (UTF-8) requires the installation of the appropriate IBM CCSID conversion table; see Installing CCSID Tables for more information”

It seems like you are specifying ccsid 819 which means you would have to install this codeset in order for it to be used. Instructions on how to do this can be found here:


M Carmen De Paz
Forum|alt.badge.img+2
  • Author
  • Participating Frequently
  • November 24, 2025
Is there a way to convert ASCII strings to UTF-8 with this version of Micro Focus COBOL on Linux without using the code pages?cob -V version @(#)cob.c 8.0.0.135PRN=KXCSU/AAF:Ao.U4.13.04PTI=64 bitPTI=Micro Focus Visual COBOL Development Hub 8.0 - Patch Update 22PTI=Patch Update 22PTI=pkg_372373PTI=MFInstaller

M Carmen De Paz
Forum|alt.badge.img+2
  • Author
  • Participating Frequently
  • November 24, 2025

i have try with this code 

              *> CONVERSIÓN ASCII  UNICODE (PIC N)
              MOVE function NATIONAL-OF(rascii)   TO rnat

              *> CONVERSIÓN UNICODE  UTF-8 (PIC X)
              MOVE function DISPLAY-OF(rnat)      TO rutf8
but the result is de same  hexadecimal F3 is convert to hexadecimal E280 inteasd of C3B3.

 

I read somewhere that this version of Micro Focus on Linux is converting to UTF-8 but using canonical/long form UTF-8 encoding, not standard UTF-8. Is this correct?

Chris Glazier
Forum|alt.badge.img+2
  • Moderator
  • November 25, 2025

The following appears to do what you want as long as you have the locale set to support the ASCII extended character set:

export LC_ALL=en_US.ISO-8859-1


identification division.
program-id. Program1.

environment division.
configuration section.

data division.
working-storage section.
01 my-ascii pic x(5) value X"F3".
01 my-utf8 pic u(5).
01 out-length pic x(4) comp-x value 2.
01 reserved pic x(4) comp-x value 0.
01 status-code pic x(4) comp-5 value 0.
procedure division.
call "CBL_STRING_CONVERT" using by reference my-ascii
by value 1
by value 3
by reference my-utf8
by reference out-length
by value 0
by value 0
by reference reserved
returning status-code.
display function hex-of(my-utf8)
goback.