FLICONV-API
FLAM Character Conversion Interface
Functions

Functions

const char * fliconv_version (void)
 Retrieves version information.
 
const char * fliconv_about (void)
 Retrieves about information.
 
const char * fliconv_license (void)
 Retrieves the license text.
 
const char * fliconv_zusmode (void *pvHdl)
 Returns string describing use of IBM Unicode Services.
 
void fliconv_list (TfDoOneList *do_one, void *data)
 
void * fliconv_open (const char *pcTo_Code, const char *pcFrmCode)
 Open character conversion module.
 
int fliconv_close (void *hdl)
 Close character conversion module.
 
size_t fliconv (void *cd, char **inbuf, size_t *inbytesleft, char **outbuf, size_t *outbytesleft)
 Convert a data block.
 
void fliconv_seterrno (const int err)
 Set error number.
 
int fliconv_geterrno (void)
 Get error number.
 
int fliconv_chkerrno (const int err, const int val)
 Check error number.
 
const char * fliconv_strerror (int err)
 Get error message.
 
const char * fliconv_error_trace (void)
 Get error trace.
 
const char * fliconv_error_msg (void *cd)
 Get error message.
 
int fliconv_expansion (void *cd)
 Get expansion factor.
 
int64_t fliconv_position (void *cd)
 Get position.
 

Detailed Description

Function Documentation

◆ fliconv_version()

const char * fliconv_version ( void )
extern

Retrieves version information.

Returns a string with version information for each component used. This should be used in a support case.

Example for C:

printf("Version: %s\n",fliconv_version();

Example in Cobol:

*
 DATA DIVISION.
*
 FILE SECTION.
 FD  OUTDAT  BLOCK CONTAINS 0 CHARACTERS
             RECORDING MODE V
             RECORD IS VARYING FROM 1 TO 240 CHARACTERS
                    DEPENDING ON OUTREC-LEN
             LABEL  RECORD IS STANDARD.
 01  OUTDAT-RECORD.
     02 FILLER   PIC X(240).
*
 FD  INDAT   BLOCK CONTAINS 0 CHARACTERS
             RECORDING MODE F
             RECORD CONTAINS 80 CHARACTERS
             LABEL  RECORD IS STANDARD.
 01  INDAT-RECORD.
     02 FILLER   PIC X(80).

*
 WORKING-STORAGE SECTION.
*
.......
77  RET-PTR        USAGE IS POINTER.
77  MSGLEN         PIC  9(8) BINARY VALUE ZERO.
01  DISPAREA       PIC  X(8120)     VALUE SPACES.
01  MSGAREA        PIC  X(256).
.......

*
PROCEDURE DIVISION.
.......
GET-VERSION SECTION.
GET-VERSION-01.
.......
     CALL  'fliconv_version' RETURNING RET-PTR
     SET ADDRESS OF MSGAREA  TO RET-PTR
     UNSTRING MSGAREA  DELIMITED BY X'00'
                       INTO DISPAREA COUNT MSGLEN
     DISPLAY 'Version Message:'
     DISPLAY  DISPAREA(1:MSGLEN).
*
GET-VERSION-EX.
    EXIT.
.......

Example in PL/1:

.......
/-------------------------------------------------------------------
/   DECLARATIONS FOR USED C FUNCTIONS
/-------------------------------------------------------------------
.......
    DCL FLICONV_VERSION       EXT('fliconv_version')
                              ENTRY()
                              RETURNS (POINTER BYVALUE)
                              OPTIONS (NODESCRIPTOR);
.......
/-------------------------------------------------------------------
/                        E N T R I E S
/-------------------------------------------------------------------
    DCL SYSOUT FILE STREAM OUTPUT PRINT ENV (FB RECSIZE (132));
    DCL INPUT  FILE RECORD INPUT  ENV (FB RECSIZE (80));
    DCL OUTPUT FILE RECORD OUTPUT ENV (VB RECSIZE (244));

/-------------------------------------------------------------------
/              O T H E R    V A R I A B L E S
/-------------------------------------------------------------------
.......
DCL  1  RET_PTR             POINTER;
DCL  1  MSGAREA             CHAR(256) BASED (RET_PTR);
DCL  1  MSGLEN              BIN FIXED(31,0) INIT (0);
.......

.......
GET_VERSION:
PROCEDURE;
          CALL PLIFILL (ADDR(MSGAREA), '00'X, SIZE(MSGAREA));
          RET_PTR = FLICONV_VERSION();
          MSGLEN = INDEX(MSGAREA, '00'X, 1);
          PUT FILE(SYSOUT) SKIP EDIT('VERSION MESSAGE:')(A);
          PUT FILE(SYSOUT) SKIP EDIT
          (SUBSTR(MSGAREA, 1, MSGLEN)) (A);
.......
END GET_VERSION;
.......
Returns
a pointer to a static area containing the zero-terminated version string

◆ fliconv_about()

const char * fliconv_about ( void )
extern

Retrieves about information.

Returns a string with about information for this library on multiple lines and license information if external libraries are used.

Example for C:

printf("About:\n%s\n",fliconv_about();

Example in Cobol:

*
 DATA DIVISION.
*
 WORKING-STORAGE SECTION.
*
.......
 77  RET-PTR        USAGE IS POINTER.
 77  MSGLEN         PIC  9(8) BINARY VALUE ZERO.
 01  DISPAREA       PIC  X(8120)     VALUE SPACES.
 01  MSGAREA        PIC  X(256).
.......

*
PROCEDURE DIVISION.
.......
    CALL  'fliconv_about' RETURNING RET-PTR
    SET ADDRESS OF MSGAREA  TO RET-PTR
    UNSTRING MSGAREA  DELIMITED BY X'00'
                      INTO DISPAREA COUNT MSGLEN
    DISPLAY 'About Message:'
    DISPLAY  DISPAREA(1:MSGLEN)
.......
Returns
a pointer to a static area containing the zero-terminated about string

◆ fliconv_license()

const char * fliconv_license ( void )
extern

Retrieves the license text.

This function can be used to get the current license text on multiple lines. The license text defines the permissible use of this library.

Example for C:

printf("License:\n%s\n",fliconv_license();

Example in Cobol:

*
 DATA DIVISION.
*
 WORKING-STORAGE SECTION.
*
.......
77  RET-PTR        USAGE IS POINTER.
77  MSGLEN         PIC  9(8) BINARY VALUE ZERO.
01  DISPAREA       PIC  X(8120)     VALUE SPACES.
01  MSGAREA        PIC  X(256).
.......

*
PROCEDURE DIVISION.
.......
    CALL  'fliconv_license' RETURNING RET-PTR.
    SET ADDRESS OF MSGAREA  TO RET-PTR.
DISP-MSGS.
    MOVE ZERO  TO MSGLEN.
    UNSTRING MSGAREA  DELIMITED BY X'15' OR X'00'
                      INTO DISPAREA
                      DELIMITER DISP-DLIM COUNT MSGLEN
                      WITH POINTER DISP-PTR.
    IF  DISP-DLIM = X'15'
       THEN
          DISPLAY DISPAREA(1:MSGLEN)
          GO TO DISP-MSGS
    END-IF.
.......
Returns
a pointer to a static area with a zero-terminated string containing the current license text.

◆ fliconv_zusmode()

const char * fliconv_zusmode ( void * pvHdl)
extern

Returns string describing use of IBM Unicode Services.

Parameters
pvHdlPointer to the handle
Returns
Static pointer to Zero terminated string

◆ fliconv_list()

void fliconv_list ( TfDoOneList * do_one,
void * data )
extern

This function corresponds to the iconvlist() function of libiconv and can be used to get a list of supported CCSIDs, CHARSETs and encoding strings. The formatting can be defined by passing a function pointer of type TfDoOneList. If this function pointer is NULL, a default formatting function is used. This default formatting function writes to STDERR if the data pointer is also NULL. If the data pointer is non-NULL and the function pointer is NULL, the data pointer must point to a buffer that is at least FLICONV_LISTBYTES bytes long. The default formatting function writes the list this buffer. If the buffer is shorter than FLICONV_LISTBYTES bytes, behavior is undefined (risk of segmentation fault).

For example:

  • fliconv_list(NULL,NULL) writes the CCSID list to stderr
  • fliconv_list(NULL,data) writes the CCSID list to the data buffer

When specifying a custom callback function (fliconv_list(myone,mydata)) the data pointer is passed to the function on each call. In contrast to other fliconv_list() implementations, the namescount is at least 3 and the index has the meaning below:

  • 0 CCSID
  • 1 CHARSET (not valid as input for fliconv_open())
  • 2 Main encoding string
  • >2 Alias encoding strings (currently not supported)

The default formatting function writes lines (delimiter='
') of the following format to STDERR or the specified buffer. If using the buffer version, the resulting string is null-terminated.

'CCSID' CHRSET (encoding string)

The character sets below are currently supported:

  • ASCII all single byte ASCII code pages (CP1252)
  • EBCDIC all single byte EBCDIC code pages (IBM1141)
  • UTF8 for UTF-8
  • UTF16BE for UTF-16BE
  • UTF16LE for UTF-16LE
  • UTF32BE for UTF-32BE
  • UTF32LE for UTF-32LE
  • UCS1 for UCS-1
  • UCS2BE for UCS-2BE
  • UCS2LE for UCS-2LE
  • UCS4BE for UCS-4BE
  • UCS4LE for UCS-4LE

NOTE: UCS(*)- subset of UTF(*) with first 65536 codepoints, mostly enough for usual applications

The function may set the errno values below:

  • EINVAL error in do_one function

Below you can find an example of a do_one function:

static int oneFwrite(unsigned int         namescount,
                     const char* const*   names,
                     void*                data){
   int i;
   if(namescount<3){ return -1; }

   fprintf((FILE*)data,"'%s' %7s (%s",names[0],names[1],names[2]);
   for(i=3;i<namescount;i++){
      fprintf((FILE*)data,"/%s",names[i]);
   }
   fprintf((FILE*)data,")\n");

   return 0;
}

Example in Cobol:

*
 DATA DIVISION.
*
 FILE SECTION.
 FD  OUTDAT  BLOCK CONTAINS 0 CHARACTERS
             RECORDING MODE V
             RECORD IS VARYING FROM 1 TO 240 CHARACTERS
                    DEPENDING ON OUTREC-LEN
             LABEL  RECORD IS STANDARD.
 01  OUTDAT-RECORD.
     02 FILLER   PIC X(240).
*
 FD  INDAT   BLOCK CONTAINS 0 CHARACTERS
             RECORDING MODE F
             RECORD CONTAINS 80 CHARACTERS
             LABEL  RECORD IS STANDARD.
 01  INDAT-RECORD.
     02 FILLER   PIC X(80).
*
 WORKING-STORAGE SECTION.
*
.......
01  DISPAREA       PIC  X(8120)   VALUE SPACES.
77  MSGLEN         PIC  9(8) BINARY VALUE ZERO.
01  DISP-CCSID     PIC  X(80).
77  DISP-DLIM      PIC  X.
77  DISP-PTR       PIC  9(8) COMP VALUE 1.
.......

*
PROCEDURE DIVISION.
.......
GET-CCSID-LIST SECTION.
GET-CCSID-LIST-01.
.......
     CALL 'fliconv_list' USING OMITTED,
                               DISPAREA.
     DISPLAY 'Supported CCSIDs:'.
 GET-CCSID-LIST-02.
     MOVE ZERO  TO MSGLEN.
     UNSTRING DISPAREA DELIMITED BY X'15' OR X'00'
                       INTO DISP-CCSID
                       DELIMITER DISP-DLIM COUNT MSGLEN
                       WITH POINTER DISP-PTR.
     IF  DISP-DLIM = X'15'
       THEN
          DISPLAY DISP-CCSID(1:MSGLEN)
          GO TO GET-CCSID-LIST-02
     END-IF.
*
GET-CCSID-LIST-EX.
    EXIT.
.......

Example in PL/1:

.......
/-------------------------------------------------------------------
/   DECLARATIONS FOR USED C FUNCTIONS
/-------------------------------------------------------------------
.......
    DCL FLICONV_LIST          EXT('fliconv_list')
                              ENTRY(POINTER    BYADDR,
                                    CHAR(8120) BYADDR)
                              OPTIONS (NODESCRIPTOR);
.......

/-------------------------------------------------------------------
/              O T H E R    V A R I A B L E S
/-------------------------------------------------------------------
.......
DCL  1  DISPAREA            CHAR(8120)      INIT(' ');
DCL  1  MSGLEN              BIN FIXED(31,0) INIT (0);
DCL  1  DISP_DLIM           CHAR(01)        INIT(' ');
DCL  1  LIST_PTR            POINTER;
DCL  1  PRINT_AREA          CHAR(80)        INIT (' ');
DCL  1  REMAINDER_LEN       BIN FIXED(31,0) INIT (256);
.......

.......
GET_CCSID_LIST:
PROCEDURE;
          CALL PLIFILL (ADDR(DISPAREA), '00'X, SIZE(PRINT_AREA));
          CALL FLICONV_LIST(LIST_PTR, DISPAREA);
          PUT FILE(SYSOUT) SKIP EDIT('SUPPORTED CCSIDS:') (A);
GET_CCSID_LIST_01:
    MSGLEN = 0;
    CALL PLIFILL (ADDR(PRINT_AREA), '00'X, SIZE(PRINT_AREA));
    MSGLEN = INDEX(DISPAREA, '15'X, 1);
    IF MSGLEN = 0
       THEN
          MSGLEN = INDEX(DISPAREA, '00'X, 1);
    DISP_DLIM    = SUBSTR(DISPAREA, MSGLEN, 1);
    IF DISP_DLIM = '15'X
       THEN
          DO;
           PRINT_AREA=SUBSTR(DISPAREA, 1, (MSGLEN - 1));
           PUT FILE(SYSOUT) SKIP EDIT(PRINT_AREA)(A);
           REMAINDER_LEN = REMAINDER_LEN - MSGLEN;
           DISPAREA =
            SUBSTR(DISPAREA, (MSGLEN + 1), REMAINDER_LEN);
           GO TO GET_CCSID_LIST_01;
          END;
END GET_CCSID_LIST;
.......
Parameters
[in]do_oneNULL for default formatting or function pointer to an own formatting function
[in]dataPointer passed to the callback function specified by do_one

◆ fliconv_open()

void * fliconv_open ( const char * pcTo_Code,
const char * pcFrmCode )
extern

Open character conversion module.

Opens the character conversion module. A target and a source encoding string is required. The target encoding string defines to which character set the data is converted. The source encoding string defines from which character set the input data is converted.

Both strings can be enhanced to use the features below:

Input encoding string enhancements:

  • //BOM Manage byte order change
  • //NL2LF Convert EBCDIC new line (0x15) to line feed (0x0A)

Output encoding string enhancements:

  • //BOM Write byte order mark
  • //LF2NL Convert EBCDIC line feed (0x0A) to new line (0x15)
  • //TOUPPER Upper case mapping
  • //TOLOWER Lower case mapping
  • //TOSUPPER Special upper case mapping
  • //TOSLOWER Special lower case mapping
  • //TOFOLD Special case folding
  • //TOUSER User module/table defined case mapping
  • //IGNORE Ignore invalid characters
  • //TRANSLIT['('[systab]')'] Transliterate invalid characters [ICONV]
  • //SUBSTITUTE['('[codepoint_list]')'] Substitute invalid characters [0x1A]
  • //USRMOD'('module_name')' Use a predefined user table module
  • //USRTAB'('file_name')' Use a custom user table text file
  • //REPORT['('[file_name]')'] Write a report file [STDERR]
  • //NFD Normalisation Form D (Canonical Decomposition)
  • //NFC Normalisation Form D (Canonical Decomposition, followed by Canonical Composition)
  • //COMBINED Character conversion with combined character support

Currently supported system transliteration tables:

  • ICONV Transliteration table of libiconv

Currently supported user table module names:

  • CCUTNPAS UCS subset for String-Latin (XOEV/NPA, with best fit mapping and case folding)
  • CCUTSPEA UCS subset for SEPA (all valid UTF-8 character < 128, with transliteration)
  • CCUTDELA UCS subset of IBM1141, CP1252 and ISO8859-15 (only CP check)
  • CCUTDLAX UCS Subset of IBM1141, CP1252, ISO8859-15 and XOEF (only CP check)

For more information about custom user table text files please refer to the FLCL user manual.

Example for C:

h=fliconv_open("UTF16LE//BOM","1141//ELF2NL//IGNORE//TRANSLIT//REPORT(report.txt)");
if (h==NULL) return(fliconv_geterrno());

Example in Cobol:

*
 DATA DIVISION.
*
 FILE SECTION.
 FD  OUTDAT  BLOCK CONTAINS 0 CHARACTERS
             RECORDING MODE V
             RECORD IS VARYING FROM 1 TO 240 CHARACTERS
                    DEPENDING ON OUTREC-LEN
             LABEL  RECORD IS STANDARD.
 01  OUTDAT-RECORD.
     02 FILLER   PIC X(240).
*
 FD  INDAT   BLOCK CONTAINS 0 CHARACTERS
             RECORDING MODE F
             RECORD CONTAINS 80 CHARACTERS
             LABEL  RECORD IS STANDARD.
 01  INDAT-RECORD.
     02 FILLER   PIC X(80).

*
 WORKING-STORAGE SECTION.
*
.......
77  RET-PTR        USAGE IS POINTER.
77  FLICV-HDL      PIC  9(8) COMP VALUE ZERO.
77  FLICV-ERRNO    PIC  9(8) COMP.
77  MSGLEN         PIC  9(8) BINARY VALUE ZERO.
01  DISPAREA       PIC  X(8120)   VALUE SPACES.
01  FLICONV-PARAMETER.
  05 FLICV-FROM.
     10 CCSID-FROM PIC X(8) VALUE 'IBM-1141'.
     10 FILLER     PIC X(8) VALUE '//IGNORE'.
     10 FILLER     PIC X(1) VALUE LOW-VALUE.
  05 FLICV-TO.
     10 CCSID-TO   PIC X(4) VALUE 'UTF8'.
     10 FILLER     PIC X(1) VALUE LOW-VALUE.
01  MSGAREA     PIC X(256).
.......

*
PROCEDURE DIVISION.
.......
OPEN-FLICONV SECTION.
OPEN-FLICONV-01.
.......
    CALL 'fliconv_open'  USING FLICV-TO, FLICV-FROM
                         RETURNING FLICV-HDL
    IF  FLICV-HDL = ZERO THEN error-handling ...
.......
OPEN-FLICONV-EX.
    EXIT.
.......

Example for error handling:

    CALL 'fliconv_geterrno' RETURNING FLICV-ERRNO
    CALL 'fliconv_strerror' USING BY VALUE FLICV-ERRNO
                            RETURNING RET-PTR
    SET ADDRESS OF MSGAREA  TO RET-PTR
    UNSTRING MSGAREA  DELIMITED BY X'00'
                      INTO DISPAREA COUNT MSGLEN
    DISPLAY 'Error Message:'
    DISPLAY  DISPAREA(1:MSGLEN).

Example in PL/1:

.......
/-------------------------------------------------------------------
/   DECLARATIONS FOR USED C FUNCTIONS
/-------------------------------------------------------------------
.......
    DCL FLICONV_OPEN          EXT('fliconv_open')
                              ENTRY(CHAR(*) VARYINGZ NONASGN BYADDR,
                                    CHAR(*) VARYINGZ NONASGN BYADDR )
                              RETURNS (BIN FIXED(31,0) BYVALUE)
                              OPTIONS (NODESCRIPTOR);
.......
/-------------------------------------------------------------------
/              O T H E R    V A R I A B L E S
/-------------------------------------------------------------------
.......
   DCL  1  MSGLEN              BIN FIXED(31,0) INIT (0);
   DCL  1  FLICV_HDL           BIN FIXED(31,0) INIT (0) ALIGNED;
   DCL  1  FLICV_ERRNO         BIN FIXED(31,0) INIT (0);
   DCL  1   FLICV_FROM,
            10 CCSID_FROM      CHAR(8) INIT ('IBM-1141'),
            10 CCSID_FROM_1    CHAR(8) INIT ('//IGNORE'),
            10 CCSID_FROM_2    CHAR(1) INIT ('00'X);
   DCL  1   FLICV_TO,
            10 CCSID_TO        CHAR(4) INIT ('UTF8'),
            10 CCSID_TO_2      CHAR(1) INIT ('00'X);
   DCL  1   FLICV_FROM_K       CHAR(17);
   DCL  1   FLICV_TO_K         CHAR(5);
   DCL  1  RET_PTR             POINTER;
   DCL  1  MSGAREA             CHAR(256) BASED (RET_PTR);
.......

 .......
OPEN_FLICONV:
PROCEDURE;
          FLICV_TO_K   = CCSID_TO   || CCSID_TO_2;
          FLICV_FROM_K = CCSID_FROM || CCSID_FROM_1 || CCSID_FROM_2;
          FLICV_HDL = FLICONV_OPEN(FLICV_TO_K, FLICV_FROM_K);
          IF FLICV_HDL = ZERO THEN error-handling ...
.......
END OPEN_FLICONV;
 .......

Example for error-handling:

          FLICV_ERRNO = FLICONV_GETERRNO();
          CALL PLIFILL (ADDR(MSGAREA), '00'X, SIZE(MSGAREA));
          RET_PTR = FLICONV_STRERROR(FLICV_ERRNO);
          MSGLEN = INDEX(MSGAREA, '00'X, 1);
          PUT FILE(SYSOUT) SKIP EDIT('Error Message:') (A);
          PUT FILE(SYSOUT) SKIP EDIT(SUBSTR(MSGAREA, 1, MSGLEN))(A);

The function may set the errno values below:

  • EINVAL parameter wrong or not supported
  • ENOMEM allocation failed, not enough space left
  • UTFAIL loading the user table failed
  • MAXEXP maximum expansion reached
  • LICVIL license violation
  • WITSPC Output whitespace handling
  • IBMUCS Error from IBM Unicode Services
  • REREST Remaining rest

You can use fliconv_strerror() to get a corresponding error message and fliconv_error_trace() to get more error information.

Parameters
[in]pcTo_CodeTarget encoding string
[in]pcFrmCodeSource encoding string
Returns
a pointer to a handle to manage character conversion, must be passed to subsequent functions, NULL in case of an error.

◆ fliconv_close()

int fliconv_close ( void * hdl)
extern

Close character conversion module.

The module must be closed through this function after conversion is finished. All allocated resources are released.

You can use fliconv_strerror() to get an corresponding error message and fliconv_error_trace() to get more error information.

Example for C:

fliconv_close(h);

Example in Cobol:

*
 DATA DIVISION.
*
 WORKING-STORAGE SECTION.
*
.......
  77  FLICV-HDL      PIC  9(8) COMP VALUE ZERO.
.......

*
PROCEDURE DIVISION.
.......
CLOSE-FLICONV SECTION.
CLOSE-FLICONV-01.
.......
    CALL 'fliconv_close' USING BY VALUE  FLICV-HDL
.......
CLOSE-FLICONV-EX.
    EXIT.
 .......

Example in PL/1:

 .......
/-------------------------------------------------------------------
/   DECLARATIONS FOR USED C FUNCTIONS
/-------------------------------------------------------------------
.......
   DCL FLICONV_CLOSE          EXT('fliconv_close')
                              ENTRY(BIN FIXED(31,0) byvalue)
                              RETURNS (BIN FIXED(31,0) byvalue)
                              OPTIONS (NODESCRIPTOR);
.......

/-------------------------------------------------------------------
/              O T H E R    V A R I A B L E S
/-------------------------------------------------------------------
.......
  DCL  1   FLICV_HDL          BIN FIXED(31,0) INIT (0) ALIGNED;
.......

.......
CLOSE_FLICONV:
PROCEDURE;
          FLICV_HDL = FLICONV_CLOSE(FLICV_HDL);
END CLOSE_FLICONV;
.......
Parameters
[in]hdlHandle from fliconv_open()
Returns
Upon successful completion 0 is returned. Otherwise, -1 is returned.

◆ fliconv()

size_t fliconv ( void * cd,
char ** inbuf,
size_t * inbytesleft,
char ** outbuf,
size_t * outbytesleft )
extern

Convert a data block.

Converts at most *inbytesleft bytes starting at *inbuf, writing at most *outbytesleft bytes starting at *outbuf. The function decrements *inbytesleft and increments *inbuf by the same amount. On the other side, it also decrements *outbytesleft and increments *outbuf by the same amount.

If *inbytesleft multiplied by the maximum expansion factor is greater than *outbytesleft, no data is converted, errno is set to E2BIG and -1 is returned. You have to reallocate *outbuf in order to provide enough space for conversion.

If *inbytesleft is not 0, an incomplete multi-byte character might have been found at the end of the input data block (return code = -1, errno = EINVAL). If the input block was the last block to be processed, the input data is incomplete. Otherwise, the rest (pointed to by *inbuf must be at the beginning of the next input block.

To save memory for Unicode character sets the pre-calculated tables are first limit to to 64k entries. If a multibyte character encountered which requires more than 16 bit, then a reopen is done to pre-calculate bigger (1.1M) tables. If not enought memory available the reopen can fail.

The function may set the errno values below:

  • EILSEQ invalid byte sequence
  • ENOMSG malformed encoding
  • EINVAL incomplete byte sequence
  • REOPEN reopen failed
  • BOMCHG byte order changed
  • E2BIG out buffer smaller than input_length*expansion
  • E2BIG after reopen, expansion factor changed
  • MAXEXP in reopen, max expansion reached

You can use fliconv_strerror() to get a corresponding error message and fliconv_error_trace() to get more error information.

Example for C:

r=iconv(h,&inDat,&inLen,&outDat,&outLen);

Example in Cobol:

*
 DATA DIVISION.
*
 WORKING-STORAGE SECTION.
*
.......
77  FLICV-HDL      PIC  9(8) COMP VALUE ZERO.
77  IN-PTR         USAGE IS POINTER.
77  INLEFT         PIC  9(8) COMP.
77  OUT-PTR        USAGE IS POINTER.
77  OUTLEFT        PIC  9(8) COMP.
77  FLICV-RC       PIC S9(8) COMP VALUE ZERO.
.......

*
PROCEDURE DIVISION.
.......
*
DO-CONVERSION SECTION.
DO-CONVERSION-01.
.......
    CALL  'fliconv'      USING BY VALUE     FLICV-HDL,
                               BY REFERENCE IN-PTR,
                               BY REFERENCE INLEFT,
                               BY REFERENCE OUT-PTR,
                               BY REFERENCE OUTLEFT
                         RETURNING FLICV-RC
.......
DO-CONVERSION-EX.
    EXIT.
.......

Example in PL/1:

/-------------------------------------------------------------------
/   DECLARATIONS FOR USED C FUNCTIONS
/-------------------------------------------------------------------
.......
    DCL FLICONV               EXT('fliconv')
                              ENTRY
                                   (BIN FIXED(31,0) BYVALUE,
                                    POINTER         BYADDR,
                                    BIN FIXED(31,0) BYADDR,
                                    POINTER         BYADDR,
                                    BIN FIXED(31,0) BYADDR)
                              RETURNS (BIN FIXED(31,0) BYVALUE)
                              OPTIONS (NODESCRIPTOR);
.......
/-------------------------------------------------------------------
/              O T H E R    V A R I A B L E S
/-------------------------------------------------------------------
.......
DCL  1  FLICV_HDL           BIN FIXED(31,0) INIT (0) ALIGNED;
DCL  1  IN_PTR              POINTER;
DCL  1  INLEFT              BIN FIXED(31,0) INIT (0) ALIGNED;
DCL  1  OUT_PTR             POINTER;
DCL  1  OUTLEFT             BIN FIXED(31,0) INIT (0) ALIGNED;
DCL  1  FLICV_RC            BIN FIXED(31,0) INIT (0);
.......

.......
DO_CONVERSION:
PROCEDURE;
.......
          FLICV_RC = FLICONV( FLICV_HDL,
                              IN_PTR,
                              INLEFT,
                              OUT_PTR,
                              OUTLEFT);
.......
DO_CONVERSION_EX:
.......
Parameters
[in]cdHandle from fliconv_open()
[in,out]inbufPointer to the input data buffer
[in,out]inbytesleftInput data length
[in,out]outbufPointer to the output data buffer
[in,out]outbytesleftOutput buffer size
Returns
The function returns the number of characters converted in a non-reversible way (ignored, substituted or transliterated) during this call; reversible conversions are not counted. If the return code > 0, then entries in the report file can be found. A positive return code is a warning that an internal error handling was done. In case of error, it sets errno and returns (size_t) -1.

◆ fliconv_seterrno()

void fliconv_seterrno ( const int err)
extern

Set error number.

Use this function in non C programming languages to set the global variable errno of the c runtime library. For error handling you must set errno in front of a call to 0, to check after the call the value.

Example for C:

fliconv_seterrno(0);
r=fliconv(...);
if (r==-1) {
   if (fliconv_chkerrno(fliconv_geterrno(),FLICONV_EINVAL)) {
    ...
   }
}

Example in Cobol:

CALL  'fliconv_seterrno'   USING BY VALUE ERRNO.
Parameters
[in]errError number (mainly only 0 make sense)

◆ fliconv_geterrno()

int fliconv_geterrno ( void )
extern

Get error number.

Use this function in non C programming languages to get the global variable errno of the c runtime library. For error handling you need access to the errno after a call. Attention: This integer contains platform dependent values. You can use the function fliconv_chkerrno() to verify the errno against the predefined platform independent values above.

Example for C:

if (fliconv_chkerrno(fliconv_geterrno(),FLICONV_E2BIG)) ...

Example in Cobol:

*
 DATA DIVISION.
*
 WORKING-STORAGE SECTION.
*
.......
 77  FLICV-ERRNO    PIC  9(8) COMP.
 77  RET-PTR        USAGE IS POINTER.
 01  MSGAREA        PIC  X(256).
 01  DISPAREA       PIC  X(8120)   VALUE SPACES.
 77  MSGLEN         PIC  9(8) BINARY VALUE ZERO.
.......

*
PROCEDURE DIVISION.
.......
*
ERROR-FOUND SECTION.
ERROR-FOUND-01.
    CALL 'fliconv_geterrno' RETURNING FLICV-ERRNO
    DISPLAY FLICV-ERRNO
*
    CALL 'fliconv_strerror' USING BY VALUE FLICV-ERRNO
                            RETURNING RET-PTR
*
    SET ADDRESS OF MSGAREA  TO RET-PTR
*
    UNSTRING MSGAREA  DELIMITED BY X'00'
                      INTO DISPAREA COUNT MSGLEN
*
    DISPLAY 'Error Message:'.
    DISPLAY  DISPAREA(1:MSGLEN).
*
ERROR-FOUND-EX.
    EXIT.

Example in PL/1:

.......
/-------------------------------------------------------------------
/   DECLARATIONS FOR USED C FUNCTIONS
/-------------------------------------------------------------------
.......
    DCL FLICONV_GETERRNO      EXT('fliconv_geterrno')
                              ENTRY()
                              RETURNS (BIN FIXED(31,0) BYVALUE)
                              OPTIONS (NODESCRIPTOR);
*
    DCL FLICONV_STRERROR      EXT('fliconv_strerror')
                              ENTRY(BIN FIXED(31,0) BYVALUE)
                              RETURNS (POINTER BYVALUE)
                              OPTIONS (NODESCRIPTOR);
.......
/-------------------------------------------------------------------
/              O T H E R    V A R I A B L E S
/-------------------------------------------------------------------
.......
    DCL  1  RET_PTR             POINTER;
    DCL  1  MSGAREA             CHAR(256) BASED (RET_PTR);
    DCL  1  FLICV_ERRNO         BIN FIXED(31,0) INIT (0);
    DCL  1  MSGLEN              BIN FIXED(31,0) INIT (0);
.......

.......
ERROR_FOUND:
PROCEDURE;
.......
         FLICV_ERRNO = FLICONV_GETERRNO();
*
         PUT FILE(SYSOUT) SKIP EDIT
         (FLICV_ERRNO) (P'99999999');
*
         CALL PLIFILL (ADDR(MSGAREA), '00'X, SIZE(MSGAREA));
*
         RET_PTR = FLICONV_STRERROR(FLICV_ERRNO);
*
         MSGLEN = INDEX(MSGAREA, '00'X, 1);
*
         PUT FILE(SYSOUT) SKIP EDIT
         ('Error Message:') (A);
*
         PUT FILE(SYSOUT) SKIP EDIT(SUBSTR(MSGAREA, 1, MSGLEN))(A);
*
END ERROR_FOUND;
.......
Returns
Error number

◆ fliconv_chkerrno()

int fliconv_chkerrno ( const int err,
const int val )
extern

Check error number.

Use this function in non C programming languages to check the global variable errno of the C runtime environment. The value err is provided by function fliconv_geterrno() and the value val is one of the predefined constants above.

Example for C:

if (fliconv_chkerrno(fliconv_geterrno(),FLICONV_E2BIG)) ...
Parameters
errError number
valError value (see defined values above)
Returns
1 if match, 0 don't match or unknown

◆ fliconv_strerror()

const char * fliconv_strerror ( int err)
extern

Get error message.

This function can be used to retrieve a human-readable error message using the errno set by fliconv functions.

Example for C:

printf("Error message: %s\n",fliconv_strerror(fliconv_geterrno());

Example in Cobol:

*
 DATA DIVISION.
*
 WORKING-STORAGE SECTION.
*
.......
 77  FLICV-ERRNO    PIC  9(8) COMP.
 77  RET-PTR        USAGE IS POINTER.
 01  MSGAREA        PIC  X(256).
 01  DISPAREA       PIC  X(8120)   VALUE SPACES.
 77  MSGLEN         PIC  9(8) BINARY VALUE ZERO.
.......

*
PROCEDURE DIVISION.
.......
*
ERROR-FOUND SECTION.
ERROR-FOUND-01.
    CALL 'fliconv_geterrno' RETURNING FLICV-ERRNO
    DISPLAY FLICV-ERRNO
*
    CALL 'fliconv_strerror' USING BY VALUE FLICV-ERRNO
                            RETURNING RET-PTR
*
    SET ADDRESS OF MSGAREA  TO RET-PTR
*
    UNSTRING MSGAREA  DELIMITED BY X'00'
                      INTO DISPAREA COUNT MSGLEN
*
    DISPLAY 'Error Message:'.
    DISPLAY  DISPAREA(1:MSGLEN).
*
ERROR-FOUND-EX.
    EXIT.

Example in PL/1:

.......
/-------------------------------------------------------------------
/   DECLARATIONS FOR USED C FUNCTIONS
/-------------------------------------------------------------------
.......
    DCL FLICONV_GETERRNO      EXT('fliconv_geterrno')
                              ENTRY()
                              RETURNS (BIN FIXED(31,0) BYVALUE)
                              OPTIONS (NODESCRIPTOR);
*
    DCL FLICONV_STRERROR      EXT('fliconv_strerror')
                              ENTRY(BIN FIXED(31,0) BYVALUE)
                              RETURNS (POINTER BYVALUE)
                              OPTIONS (NODESCRIPTOR);
.......
/-------------------------------------------------------------------
/              O T H E R    V A R I A B L E S
/-------------------------------------------------------------------
.......
    DCL  1  RET_PTR             POINTER;
    DCL  1  MSGAREA             CHAR(256) BASED (RET_PTR);
    DCL  1  FLICV_ERRNO         BIN FIXED(31,0) INIT (0);
    DCL  1  MSGLEN              BIN FIXED(31,0) INIT (0);
.......

.......
ERROR_FOUND:
PROCEDURE;
.......
         FLICV_ERRNO = FLICONV_GETERRNO();
*
         PUT FILE(SYSOUT) SKIP EDIT
         (FLICV_ERRNO) (P'99999999');
*
         CALL PLIFILL (ADDR(MSGAREA), '00'X, SIZE(MSGAREA));
*
         RET_PTR = FLICONV_STRERROR(FLICV_ERRNO);
*
         MSGLEN = INDEX(MSGAREA, '00'X, 1);
*
         PUT FILE(SYSOUT) SKIP EDIT
         ('Error Message:') (A);
*
         PUT FILE(SYSOUT) SKIP EDIT(SUBSTR(MSGAREA, 1, MSGLEN))(A);
*
END ERROR_FOUND;
.......
Parameters
[in]errA valid error code
Returns
A pointer to a static area with a zero-terminated string containing a FLAM error message matching the passed error code as one line. (no LF)

◆ fliconv_error_trace()

const char * fliconv_error_trace ( void )
extern

Get error trace.

This function can be used to get an error trace after a call to fliconv_open(), fliconv() or fliconv_close(). The error trace contains the FLAM error stack.

Example for C:

printf("Error message: %s\n",fliconv_strerror(fliconv_geterrno());
printf("Error trace:\n%s\n" ,fliconv_error_trace());
Returns
a pointer to a static area with a zero-terminated string containing the current FLAM error trace on several lines

◆ fliconv_error_msg()

const char * fliconv_error_msg ( void * cd)
extern

Get error message.

This function can be used to get the last error message after a call to fliconv(). The message contains information about the last error of the FLAM ICV module.

Example for C:

printf("ICV Error message:\n%s\n", fliconv_error_msg(hdl));
Parameters
[in]cdConversion descriptor (the handle returned from fliconv_open())
Returns
a pointer to a static area with a zero-terminated string containing the last FLAM ICV error message

◆ fliconv_expansion()

int fliconv_expansion ( void * cd)
extern

Get expansion factor.

Returns the maximum expansion factor. This should be used to allocate enough memory for the output buffer. You must pass a valid descriptor obtained from fliconv_open(). This function must be used after fliconv_open() and if you get errno==E2BIG.

Example for C:

 outlen=inlen*fliconv_expansion(h);
 outbuf=(unsigned char*)realloc(outbuf,outlen);
 

Example in Cobol:

 *
  DATA DIVISION.
 *
  WORKING-STORAGE SECTION.
 *
 .......
  77  FLICV-HDL      PIC  9(8) COMP VALUE ZERO.
  77  BUFFEXP        PIC  9(8) COMP VALUE ZERO.
 .......

 *
 PROCEDURE DIVISION.
 .......
 *
 CHECK-BUFFER-SPACE SECTION.
 CHECK-BUFFER-SPACE-01.
.......
     CALL 'fliconv_expansion' USING BY VALUE FLICV-HDL
                              RETURNING BUFFEXP
 *
     DISPLAY 'Expansion factor: ' BUFFEXP
 ......
 CHECK-BUFFER-SPACE-EX.
     EXIT
 .......
 

Example in PL/1l:

 .......
 /-------------------------------------------------------------------
 /   DECLARATIONS FOR USED C FUNCTIONS
 /-------------------------------------------------------------------
 .......
     DCL FLICONV_EXPANSION     EXT('fliconv_expansion')
                               ENTRY(BIN FIXED(31,0) BYVALUE)
                               RETURNS (BIN FIXED(31,0) BYVALUE)
                               OPTIONS (NODESCRIPTOR);
 .......
 /-------------------------------------------------------------------
 /              O T H E R    V A R I A B L E S
 /-------------------------------------------------------------------
 .......
     DCL  1  FLICV_HDL  BIN FIXED(31,0) INIT (0) ALIGNED;
     DCL  1  BUFFEXP    BIN FIXED(31,0) INIT (0);
 .......

 .......
 CHECK_BUFFER_SPACE:
 PROCEDURE;
 .......
          BUFFEXP = FLICONV_EXPANSION(FLICV_HDL);
 *
          PUT FILE(SYSOUT) SKIP EDIT
          EDIT('EXPANSION FACTOR: ', BUFFEXP) (A,P'999999999');
 .......
 END CHECK_BUFFER_SPACE;
 .......
 
Parameters
[in]cdConversion descriptor
Returns
Expansion factor (0 in case of an error)

◆ fliconv_position()

int64_t fliconv_position ( void * cd)
extern

Get position.

Return the current position as byte offset. This is mainly for error handling or statistics (before close). The position is the amount of processed bytes. To point to the wrong byte in the case of an error an addition of 1 is required.

Example for C:

printf("Error at byte %"PRIi64"\n",fliconv_position()+1);
printf("Statistics: Processed %"PRIi64" bytes\n",fliconv_position());
Parameters
[in]cdConversion descriptor
Returns
Current position or 0 if no position available