FLICONV-API
FLAM Character Conversion Interface
FLUC ICONV Interface

This module provides a libiconv-compatible interface for memory to memory character conversion. All special feature of FLUC character conversion module are provided through the TO and FROM string specification in fliconv_open() function.

Example for C:

 iconvlist(NULL,NULL);
 h=iconv_open("UTF16LE//BOM","1141//ELF2NL//IGNORE//TRANSLIT//REPORT(report.txt)");
 r=iconv(h,&inDat,&inLen,&outDat,&outLen);
 iconv_close(h);
 

Example in Cobol: (Compile with the dll-option on mainframes)

 *
  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.
 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.
   77  FLICV-HDL      PIC  9(8) COMP VALUE ZERO.
   77  FLICV-RC       PIC S9(8) COMP VALUE ZERO.
   77  IN-PTR         USAGE IS POINTER.
   77  OUT-PTR        USAGE IS POINTER.
   77  INLEFT         PIC  9(8) COMP.
   77  OUTLEFT        PIC  9(8) COMP.
 .......

 *
 PROCEDURE DIVISION.
 .......
 GET-CCSID-LIST SECTION.
 GET-CCSID-LIST-01.
 .......
     CALL 'fliconv_list'  USING OMITTED, DISPAREA
 .......
 GET-VERSION-EX.
     EXIT.
 *
 OPEN-FLICONV SECTION.
 OPEN-FLICONV-01.
 .......
     CALL 'fliconv_open'  USING FLICV-TO, FLICV-FROM
                          RETURNING FLICV-HDL
 .......
 OPEN-FLICONV-EX.
     EXIT.
 *
 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.
 *
 CLOSE-FLICONV SECTION.
 CLOSE-FLICONV-01.
 .......
     CALL 'fliconv_close' USING BY VALUE  FLICV-HDL
 .......
 CLOSE-FLICONV-EX.
     EXIT.
.......
 

Example in PL/1: (Compile with the dll-option on mainframes)

 .......
 /-------------------------------------------------------------------
 /   DECLARATIONS FOR USED C FUNCTIONS
 /-------------------------------------------------------------------
 .......
     DCL FLICONV_LIST          EXT('fliconv_list')
                               ENTRY(POINTER    BYADDR,
                                     CHAR(8120) BYADDR)
                               OPTIONS (NODESCRIPTOR);
 *
     DCL FLICONV_OPEN          EXT('fliconv_open')
                               ENTRY(CHAR(*) VARYINGZ NONASGN BYADDR,
                                     CHAR(*) VARYINGZ NONASGN BYADDR )
                               RETURNS (BIN FIXED(31,0) BYVALUE)
                               OPTIONS (NODESCRIPTOR);
 *
     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);
 *
    DCL FLICONV_CLOSE          EXT('fliconv_close')
                               ENTRY(BIN FIXED(31,0) byvalue)
                               RETURNS (BIN FIXED(31,0) 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   LIST_PTR           POINTER;
   DCL  1   DISPAREA           CHAR(8120)      INIT(' ');
   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_TO_K         CHAR(5);
   DCL  1   FLICV_FROM_K       CHAR(17);
   DCL  1   FLICV_HDL          BIN FIXED(31,0) INIT (0) ALIGNED;
   DCL  1   FLICV_RC           BIN FIXED(31,0) INIT (0);
   DCL  1   IN_PTR             POINTER;
   DCL  1   OUT_PTR            POINTER;
   DCL  1   INLEFT             BIN FIXED(31,0) INIT (0) ALIGNED;
   DCL  1   OUTLEFT            BIN FIXED(31,0) INIT (0) ALIGNED;
 .......

 .......
 GET_CCSID_LIST:
 PROCEDURE;
           CALL PLIFILL (ADDR(DISPAREA), '00'X, SIZE(PRINT_AREA));
           CALL FLICONV_LIST(LIST_PTR, DISPAREA);
 .......
 END GET_CCSID_LIST;
 *
 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);
 .......
 END OPEN_FLICONV;
 *
 DO_CONVERSION:
 PROCEDURE;
 .......
           FLICV_RC = FLICONV( FLICV_HDL,
                               IN_PTR,
                               INLEFT,
                               OUT_PTR,
                               OUTLEFT);
 .......
 DO_CONVERSION_EX:
 *
 CLOSE_FLICONV:
 PROCEDURE;
           FLICV_HDL = FLICONV_CLOSE(FLICV_HDL);
 END CLOSE_FLICONV;
.......
 

Please have a look at the FLICONV.c sample file which implements the linux like ICONV utility (fliconv) based on this library, the COBOL sample SOFLCICV or the PL/1 sample SPFLCICV for mainframe systems.

CCSID's, encoding strings and defines

The open function supports encoding strings and CCSIDS. The fliconv_list() function provides all supported CCSIDs, CHARSETs and the corresponding encoding strings.

Compatibility mode

If the compiler switch FICONV is defined, then all * fliconv* entries are also available as iconv* functions. I.e. to port your existing code you must simply replace:

 #include<iconv.h>
 

by

 #define  FICONV
 #include"FLCICV.h"
 

With this replacement you can re-build your source. To use the special features you must append one or more of the encoding string specifications (see fliconv_open()).

Improvements compared to standard iconv implementations:

  • Support of encoding strings and CCSIDs, list supported CCSIDs and encoding strings
  • EBCDIC New Line (0x15) to Line Feed (0x0A) management
  • Subset support (String.Latin, SEPA, ...) and custom user tables
  • Recursive mapping and transliteration ('U:'->'UE')
  • Case mapping, comprehensive reporting, byte order change handling
  • Reads 5 and 6 byte UTF-8 encoded characters (values with preceding zeros)
  • Slightly faster and less memory and CPU utilization

Differences to the standard iconv library:

  • Supports more errno values (mainly for user table parsing, not for conversion itself)
  • E2BIG is set if the output buffer is smaller than the input data multiplied by the provided expansion factor --> No data is converted if the output buffer is too small (increases performance significantly)
  • Functions to provide about, version, license, statistics, error and other information
  • Add a few errno-functions to manage errno in other programming languages (COBOL/PLI)
  • Byte order mark is only printed to the output file if the BOM keyword is specified in the TO string
  • The list function gets available encoding strings, the CCSID and the corresponding CHARSET (UTF/ASCII/EBCDIC) information

Sample programs

A sample program in C with name FLICONV can be found as part of the installation package for mainframe systems in the library SRCLIBC(FLICONV), with the corresponding compile and link step in JOBLIB(SBUILD). For other platforms (Windows, UNIX) the sample program source of FLICONV is located in the 'sample' directory and the compile and link procedures can be found in the Makefile of the same directory.

This sample program implements the Linux like 'iconv' utility with all features of FLAM character conversion module.

Hints for z/OS

On z/OS you must define the language level with EXTC99, as _POSIX_SOURCE and use of long names to compile this sample.

DEFINE(_POSIX_SOURCE),LANGLVL(EXTC99),LO