Skip to main content

[Migrated content. Thread originally posted on 21 December 2011]

Hello,

I have this program that works correctly in RM/COBOL. It generates an XML document with the XML extensions libraries.


       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROVAXML2.
       AUTHOR. mossa.
       DATE-WRITTEN. 20080304.
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. LEVEL-6.
       OBJECT-COMPUTER. LEVEL-6.
       SPECIAL-NAMES.
           DECIMAL-POINT COMMA.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 VAR-PROGRAMA.
          03 url                          pic x(100).
          03 xmlrespuesta                 pic x(50).           
          03  request-payload             usage pointer.
          03  response-payload            usage pointer.
          03  response-error              usage pointer.
          03  response-status             pic 9(3) value zero.
          03  response-len                pic s9(4).
          03  a-single-char               pic x.
          03  longrequest.
              05 filler                   pic x occurs 1 to 65000
                                         times depending on counters.
          03 counters                     pic 9(5).

          03 Returned-text                pic x(1031).
          03 RUTA-MODELO                  PIC X(150).
          03 RUTA-PLANTILLA               PIC X(150).
          03 IDJOB                        PIC X(100).
          03 RESULTAT-WEBSERVICE          PIC X(10).
          03 STAT-TRABAJO PIC X(2).
          03 LOC-TRABAJO  PIC X(100).     
         
       01 XML-RESPUESTA.
          03 returnResult pic x(100).               
             
       01 PATH-MODELO PIC X(100)
               VALUE "/MNG/DESA/XML/".                     
       01 PATH-PLANTILLA PIC X(100)
               VALUE "/MNG/DESA/XML/".               
               
           Copy "lixmlall.cpy".         
       
       01 parametros-ws001.                     
           02 ws001-parametres-entrada.
                03 ws001-indata.
                   04  ws001-remoteurl        pic x(30).
                   04  ws001-pcontenttype     pic x(50).
                   04  ws001-attachmentid     pic x(50).
                   04  ws001-binarydata       pic X(99999).
                   
      /
       PROCEDURE DIVISION.
       INICIO SECTION.
       INI-1.           


           INITIALIZE VAR-PROGRAMA.
           INITIALIZE parametros-ws001.           
           
           xml initialize.
           if not xml-ok then             
              DISPLAY "ERROR XML INITIALIZE"
              GO TO FIN-PROGRAMA
           end-if.
      **           
           INITIALIZE ws001-parametres-entrada.
           MOVE "12345" TO ws001-binarydata.
             
           MOVE SPACES TO RUTA-MODELO
           STRING
               PATH-MODELO
                DELIMITED BY SPACES
               "BASE0085-WS1"
                DELIMITED BY SIZE
           INTO RUTA-MODELO.
             
           MOVE SPACES TO RUTA-PLANTILLA
           STRING
               PATH-PLANTILLA
                DELIMITED BY SPACES
               "BASE0085-WS1PL.XSL"
                DELIMITED BY SIZE
           INTO RUTA-PLANTILLA.
                       
           DISPLAY "RUTA-MODEL: ", RUTA-MODELO
           DISPLAY "RUTA-PLANTILLA: ", RUTA-PLANTILLA
           XML EXPORT TEXT
               ws001-parametres-entrada
               request-payload
               RUTA-MODELO
               RUTA-PLANTILLA.
               
           if not XML-OK then
               DISPLAY "ERROR EXPORT"
           end-if.
      **     
           xml put text
               request-payload
               "./P1".
           if not xml-ok then             
              DISPLAY  "ERROR " XML-STATUS " EN XML PUT"
              stop run
           else
              DISPLAY  "OK. THE PROGRAM HAS GENERATED: ./P1.xml"
           end-if.
      **     
           XML TERMINATE.
       
       FIN-PROGRAMA.                         
           GOBACK.


But when I want to compile/build it with Visual Cobol I receive the next error:

os.init:

os.init.windows:

os.init.unix:

init:

pre.build.cfg.New_Configuration:

os.init:

os.init.windows:

os.init.unix:

init:

cfg.New_Configuration:
    [cobol]
    [cobol] Compiling (64-bit) PROVAXML2.cbl...
    [cobol] * 019-C Program checked with non-optimal alignment. Optimal alignment is 8
    [cobol] * 013-R Illegal intermediate code (at 0X349 in seg 0)
    [cobol] cob64: error(s) in code generation: /MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/outEcl/PROVAXML2.int
    [cobol] Compilation complete with 0 errors, 0 warnings, 0 notices and an exit code of 1
[cobollink] Linking (64-bit) PROVAXML2.so...
[cobollink] cob64: error opening: PROVAXML2.o
[cobollink] Link complete with errors
[cobollink]


BUILD FAILED
Build finished with 1 errors, 0 warnings, 0 notices and a maximum exit code of 1

/MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/.cobolBuild:142: Build errors have occurred

Total time: 0 seconds




The program resides on a remote AIX server. I've tried to compile the program from the same remote server using the "cob" command, and also from Eclipse (Windows), and in both cases I get the same error.

I've used the next compiler directives

SHOW-DIR
CALLFH(ACUFH)
RM "GIVING"
RM "ANSI"
NOOPTIONAL-FILE
REMOVE"TIMEOUT"



I think maybe I have to attach a library of XML Extensions but I do not know how ..


Where can be the problem?


Thanks in advance

[Migrated content. Thread originally posted on 21 December 2011]

Hello,

I have this program that works correctly in RM/COBOL. It generates an XML document with the XML extensions libraries.


       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROVAXML2.
       AUTHOR. mossa.
       DATE-WRITTEN. 20080304.
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. LEVEL-6.
       OBJECT-COMPUTER. LEVEL-6.
       SPECIAL-NAMES.
           DECIMAL-POINT COMMA.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 VAR-PROGRAMA.
          03 url                          pic x(100).
          03 xmlrespuesta                 pic x(50).           
          03  request-payload             usage pointer.
          03  response-payload            usage pointer.
          03  response-error              usage pointer.
          03  response-status             pic 9(3) value zero.
          03  response-len                pic s9(4).
          03  a-single-char               pic x.
          03  longrequest.
              05 filler                   pic x occurs 1 to 65000
                                         times depending on counters.
          03 counters                     pic 9(5).

          03 Returned-text                pic x(1031).
          03 RUTA-MODELO                  PIC X(150).
          03 RUTA-PLANTILLA               PIC X(150).
          03 IDJOB                        PIC X(100).
          03 RESULTAT-WEBSERVICE          PIC X(10).
          03 STAT-TRABAJO PIC X(2).
          03 LOC-TRABAJO  PIC X(100).     
         
       01 XML-RESPUESTA.
          03 returnResult pic x(100).               
             
       01 PATH-MODELO PIC X(100)
               VALUE "/MNG/DESA/XML/".                     
       01 PATH-PLANTILLA PIC X(100)
               VALUE "/MNG/DESA/XML/".               
               
           Copy "lixmlall.cpy".         
       
       01 parametros-ws001.                     
           02 ws001-parametres-entrada.
                03 ws001-indata.
                   04  ws001-remoteurl        pic x(30).
                   04  ws001-pcontenttype     pic x(50).
                   04  ws001-attachmentid     pic x(50).
                   04  ws001-binarydata       pic X(99999).
                   
      /
       PROCEDURE DIVISION.
       INICIO SECTION.
       INI-1.           


           INITIALIZE VAR-PROGRAMA.
           INITIALIZE parametros-ws001.           
           
           xml initialize.
           if not xml-ok then             
              DISPLAY "ERROR XML INITIALIZE"
              GO TO FIN-PROGRAMA
           end-if.
      **           
           INITIALIZE ws001-parametres-entrada.
           MOVE "12345" TO ws001-binarydata.
             
           MOVE SPACES TO RUTA-MODELO
           STRING
               PATH-MODELO
                DELIMITED BY SPACES
               "BASE0085-WS1"
                DELIMITED BY SIZE
           INTO RUTA-MODELO.
             
           MOVE SPACES TO RUTA-PLANTILLA
           STRING
               PATH-PLANTILLA
                DELIMITED BY SPACES
               "BASE0085-WS1PL.XSL"
                DELIMITED BY SIZE
           INTO RUTA-PLANTILLA.
                       
           DISPLAY "RUTA-MODEL: ", RUTA-MODELO
           DISPLAY "RUTA-PLANTILLA: ", RUTA-PLANTILLA
           XML EXPORT TEXT
               ws001-parametres-entrada
               request-payload
               RUTA-MODELO
               RUTA-PLANTILLA.
               
           if not XML-OK then
               DISPLAY "ERROR EXPORT"
           end-if.
      **     
           xml put text
               request-payload
               "./P1".
           if not xml-ok then             
              DISPLAY  "ERROR " XML-STATUS " EN XML PUT"
              stop run
           else
              DISPLAY  "OK. THE PROGRAM HAS GENERATED: ./P1.xml"
           end-if.
      **     
           XML TERMINATE.
       
       FIN-PROGRAMA.                         
           GOBACK.


But when I want to compile/build it with Visual Cobol I receive the next error:

os.init:

os.init.windows:

os.init.unix:

init:

pre.build.cfg.New_Configuration:

os.init:

os.init.windows:

os.init.unix:

init:

cfg.New_Configuration:
    [cobol]
    [cobol] Compiling (64-bit) PROVAXML2.cbl...
    [cobol] * 019-C Program checked with non-optimal alignment. Optimal alignment is 8
    [cobol] * 013-R Illegal intermediate code (at 0X349 in seg 0)
    [cobol] cob64: error(s) in code generation: /MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/outEcl/PROVAXML2.int
    [cobol] Compilation complete with 0 errors, 0 warnings, 0 notices and an exit code of 1
[cobollink] Linking (64-bit) PROVAXML2.so...
[cobollink] cob64: error opening: PROVAXML2.o
[cobollink] Link complete with errors
[cobollink]


BUILD FAILED
Build finished with 1 errors, 0 warnings, 0 notices and a maximum exit code of 1

/MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/.cobolBuild:142: Build errors have occurred

Total time: 0 seconds




The program resides on a remote AIX server. I've tried to compile the program from the same remote server using the "cob" command, and also from Eclipse (Windows), and in both cases I get the same error.

I've used the next compiler directives

SHOW-DIR
CALLFH(ACUFH)
RM "GIVING"
RM "ANSI"
NOOPTIONAL-FILE
REMOVE"TIMEOUT"



I think maybe I have to attach a library of XML Extensions but I do not know how ..


Where can be the problem?


Thanks in advance
The RM COBOL XML Extensions are currently only supported in native code under Windows platforms and not on Unix platforms.

I am unsure as to the current plan for implementing XML Extensions under Unix/Linux.

Perhaps Product Management could chime in here and enlighten us?

[Migrated content. Thread originally posted on 21 December 2011]

Hello,

I have this program that works correctly in RM/COBOL. It generates an XML document with the XML extensions libraries.


       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROVAXML2.
       AUTHOR. mossa.
       DATE-WRITTEN. 20080304.
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. LEVEL-6.
       OBJECT-COMPUTER. LEVEL-6.
       SPECIAL-NAMES.
           DECIMAL-POINT COMMA.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 VAR-PROGRAMA.
          03 url                          pic x(100).
          03 xmlrespuesta                 pic x(50).           
          03  request-payload             usage pointer.
          03  response-payload            usage pointer.
          03  response-error              usage pointer.
          03  response-status             pic 9(3) value zero.
          03  response-len                pic s9(4).
          03  a-single-char               pic x.
          03  longrequest.
              05 filler                   pic x occurs 1 to 65000
                                         times depending on counters.
          03 counters                     pic 9(5).

          03 Returned-text                pic x(1031).
          03 RUTA-MODELO                  PIC X(150).
          03 RUTA-PLANTILLA               PIC X(150).
          03 IDJOB                        PIC X(100).
          03 RESULTAT-WEBSERVICE          PIC X(10).
          03 STAT-TRABAJO PIC X(2).
          03 LOC-TRABAJO  PIC X(100).     
         
       01 XML-RESPUESTA.
          03 returnResult pic x(100).               
             
       01 PATH-MODELO PIC X(100)
               VALUE "/MNG/DESA/XML/".                     
       01 PATH-PLANTILLA PIC X(100)
               VALUE "/MNG/DESA/XML/".               
               
           Copy "lixmlall.cpy".         
       
       01 parametros-ws001.                     
           02 ws001-parametres-entrada.
                03 ws001-indata.
                   04  ws001-remoteurl        pic x(30).
                   04  ws001-pcontenttype     pic x(50).
                   04  ws001-attachmentid     pic x(50).
                   04  ws001-binarydata       pic X(99999).
                   
      /
       PROCEDURE DIVISION.
       INICIO SECTION.
       INI-1.           


           INITIALIZE VAR-PROGRAMA.
           INITIALIZE parametros-ws001.           
           
           xml initialize.
           if not xml-ok then             
              DISPLAY "ERROR XML INITIALIZE"
              GO TO FIN-PROGRAMA
           end-if.
      **           
           INITIALIZE ws001-parametres-entrada.
           MOVE "12345" TO ws001-binarydata.
             
           MOVE SPACES TO RUTA-MODELO
           STRING
               PATH-MODELO
                DELIMITED BY SPACES
               "BASE0085-WS1"
                DELIMITED BY SIZE
           INTO RUTA-MODELO.
             
           MOVE SPACES TO RUTA-PLANTILLA
           STRING
               PATH-PLANTILLA
                DELIMITED BY SPACES
               "BASE0085-WS1PL.XSL"
                DELIMITED BY SIZE
           INTO RUTA-PLANTILLA.
                       
           DISPLAY "RUTA-MODEL: ", RUTA-MODELO
           DISPLAY "RUTA-PLANTILLA: ", RUTA-PLANTILLA
           XML EXPORT TEXT
               ws001-parametres-entrada
               request-payload
               RUTA-MODELO
               RUTA-PLANTILLA.
               
           if not XML-OK then
               DISPLAY "ERROR EXPORT"
           end-if.
      **     
           xml put text
               request-payload
               "./P1".
           if not xml-ok then             
              DISPLAY  "ERROR " XML-STATUS " EN XML PUT"
              stop run
           else
              DISPLAY  "OK. THE PROGRAM HAS GENERATED: ./P1.xml"
           end-if.
      **     
           XML TERMINATE.
       
       FIN-PROGRAMA.                         
           GOBACK.


But when I want to compile/build it with Visual Cobol I receive the next error:

os.init:

os.init.windows:

os.init.unix:

init:

pre.build.cfg.New_Configuration:

os.init:

os.init.windows:

os.init.unix:

init:

cfg.New_Configuration:
    [cobol]
    [cobol] Compiling (64-bit) PROVAXML2.cbl...
    [cobol] * 019-C Program checked with non-optimal alignment. Optimal alignment is 8
    [cobol] * 013-R Illegal intermediate code (at 0X349 in seg 0)
    [cobol] cob64: error(s) in code generation: /MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/outEcl/PROVAXML2.int
    [cobol] Compilation complete with 0 errors, 0 warnings, 0 notices and an exit code of 1
[cobollink] Linking (64-bit) PROVAXML2.so...
[cobollink] cob64: error opening: PROVAXML2.o
[cobollink] Link complete with errors
[cobollink]


BUILD FAILED
Build finished with 1 errors, 0 warnings, 0 notices and a maximum exit code of 1

/MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/.cobolBuild:142: Build errors have occurred

Total time: 0 seconds




The program resides on a remote AIX server. I've tried to compile the program from the same remote server using the "cob" command, and also from Eclipse (Windows), and in both cases I get the same error.

I've used the next compiler directives

SHOW-DIR
CALLFH(ACUFH)
RM "GIVING"
RM "ANSI"
NOOPTIONAL-FILE
REMOVE"TIMEOUT"



I think maybe I have to attach a library of XML Extensions but I do not know how ..


Where can be the problem?


Thanks in advance
Hello Chris,

You mean that the RM COBOL XML Extensions aren't supported in native code under linux plataforms in VisualCobol system, isnt'it?

I have tested the previous program (native code) under linux plataforms but in a RM/COBOL system, and it works correctly..

Thank you

[Migrated content. Thread originally posted on 21 December 2011]

Hello,

I have this program that works correctly in RM/COBOL. It generates an XML document with the XML extensions libraries.


       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROVAXML2.
       AUTHOR. mossa.
       DATE-WRITTEN. 20080304.
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. LEVEL-6.
       OBJECT-COMPUTER. LEVEL-6.
       SPECIAL-NAMES.
           DECIMAL-POINT COMMA.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 VAR-PROGRAMA.
          03 url                          pic x(100).
          03 xmlrespuesta                 pic x(50).           
          03  request-payload             usage pointer.
          03  response-payload            usage pointer.
          03  response-error              usage pointer.
          03  response-status             pic 9(3) value zero.
          03  response-len                pic s9(4).
          03  a-single-char               pic x.
          03  longrequest.
              05 filler                   pic x occurs 1 to 65000
                                         times depending on counters.
          03 counters                     pic 9(5).

          03 Returned-text                pic x(1031).
          03 RUTA-MODELO                  PIC X(150).
          03 RUTA-PLANTILLA               PIC X(150).
          03 IDJOB                        PIC X(100).
          03 RESULTAT-WEBSERVICE          PIC X(10).
          03 STAT-TRABAJO PIC X(2).
          03 LOC-TRABAJO  PIC X(100).     
         
       01 XML-RESPUESTA.
          03 returnResult pic x(100).               
             
       01 PATH-MODELO PIC X(100)
               VALUE "/MNG/DESA/XML/".                     
       01 PATH-PLANTILLA PIC X(100)
               VALUE "/MNG/DESA/XML/".               
               
           Copy "lixmlall.cpy".         
       
       01 parametros-ws001.                     
           02 ws001-parametres-entrada.
                03 ws001-indata.
                   04  ws001-remoteurl        pic x(30).
                   04  ws001-pcontenttype     pic x(50).
                   04  ws001-attachmentid     pic x(50).
                   04  ws001-binarydata       pic X(99999).
                   
      /
       PROCEDURE DIVISION.
       INICIO SECTION.
       INI-1.           


           INITIALIZE VAR-PROGRAMA.
           INITIALIZE parametros-ws001.           
           
           xml initialize.
           if not xml-ok then             
              DISPLAY "ERROR XML INITIALIZE"
              GO TO FIN-PROGRAMA
           end-if.
      **           
           INITIALIZE ws001-parametres-entrada.
           MOVE "12345" TO ws001-binarydata.
             
           MOVE SPACES TO RUTA-MODELO
           STRING
               PATH-MODELO
                DELIMITED BY SPACES
               "BASE0085-WS1"
                DELIMITED BY SIZE
           INTO RUTA-MODELO.
             
           MOVE SPACES TO RUTA-PLANTILLA
           STRING
               PATH-PLANTILLA
                DELIMITED BY SPACES
               "BASE0085-WS1PL.XSL"
                DELIMITED BY SIZE
           INTO RUTA-PLANTILLA.
                       
           DISPLAY "RUTA-MODEL: ", RUTA-MODELO
           DISPLAY "RUTA-PLANTILLA: ", RUTA-PLANTILLA
           XML EXPORT TEXT
               ws001-parametres-entrada
               request-payload
               RUTA-MODELO
               RUTA-PLANTILLA.
               
           if not XML-OK then
               DISPLAY "ERROR EXPORT"
           end-if.
      **     
           xml put text
               request-payload
               "./P1".
           if not xml-ok then             
              DISPLAY  "ERROR " XML-STATUS " EN XML PUT"
              stop run
           else
              DISPLAY  "OK. THE PROGRAM HAS GENERATED: ./P1.xml"
           end-if.
      **     
           XML TERMINATE.
       
       FIN-PROGRAMA.                         
           GOBACK.


But when I want to compile/build it with Visual Cobol I receive the next error:

os.init:

os.init.windows:

os.init.unix:

init:

pre.build.cfg.New_Configuration:

os.init:

os.init.windows:

os.init.unix:

init:

cfg.New_Configuration:
    [cobol]
    [cobol] Compiling (64-bit) PROVAXML2.cbl...
    [cobol] * 019-C Program checked with non-optimal alignment. Optimal alignment is 8
    [cobol] * 013-R Illegal intermediate code (at 0X349 in seg 0)
    [cobol] cob64: error(s) in code generation: /MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/outEcl/PROVAXML2.int
    [cobol] Compilation complete with 0 errors, 0 warnings, 0 notices and an exit code of 1
[cobollink] Linking (64-bit) PROVAXML2.so...
[cobollink] cob64: error opening: PROVAXML2.o
[cobollink] Link complete with errors
[cobollink]


BUILD FAILED
Build finished with 1 errors, 0 warnings, 0 notices and a maximum exit code of 1

/MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/.cobolBuild:142: Build errors have occurred

Total time: 0 seconds




The program resides on a remote AIX server. I've tried to compile the program from the same remote server using the "cob" command, and also from Eclipse (Windows), and in both cases I get the same error.

I've used the next compiler directives

SHOW-DIR
CALLFH(ACUFH)
RM "GIVING"
RM "ANSI"
NOOPTIONAL-FILE
REMOVE"TIMEOUT"



I think maybe I have to attach a library of XML Extensions but I do not know how ..


Where can be the problem?


Thanks in advance
Yes, that is correct, the XML Extensions are not currently supported in Visual COBOL on Unix platforms.

[Migrated content. Thread originally posted on 21 December 2011]

Hello,

I have this program that works correctly in RM/COBOL. It generates an XML document with the XML extensions libraries.


       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROVAXML2.
       AUTHOR. mossa.
       DATE-WRITTEN. 20080304.
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. LEVEL-6.
       OBJECT-COMPUTER. LEVEL-6.
       SPECIAL-NAMES.
           DECIMAL-POINT COMMA.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 VAR-PROGRAMA.
          03 url                          pic x(100).
          03 xmlrespuesta                 pic x(50).           
          03  request-payload             usage pointer.
          03  response-payload            usage pointer.
          03  response-error              usage pointer.
          03  response-status             pic 9(3) value zero.
          03  response-len                pic s9(4).
          03  a-single-char               pic x.
          03  longrequest.
              05 filler                   pic x occurs 1 to 65000
                                         times depending on counters.
          03 counters                     pic 9(5).

          03 Returned-text                pic x(1031).
          03 RUTA-MODELO                  PIC X(150).
          03 RUTA-PLANTILLA               PIC X(150).
          03 IDJOB                        PIC X(100).
          03 RESULTAT-WEBSERVICE          PIC X(10).
          03 STAT-TRABAJO PIC X(2).
          03 LOC-TRABAJO  PIC X(100).     
         
       01 XML-RESPUESTA.
          03 returnResult pic x(100).               
             
       01 PATH-MODELO PIC X(100)
               VALUE "/MNG/DESA/XML/".                     
       01 PATH-PLANTILLA PIC X(100)
               VALUE "/MNG/DESA/XML/".               
               
           Copy "lixmlall.cpy".         
       
       01 parametros-ws001.                     
           02 ws001-parametres-entrada.
                03 ws001-indata.
                   04  ws001-remoteurl        pic x(30).
                   04  ws001-pcontenttype     pic x(50).
                   04  ws001-attachmentid     pic x(50).
                   04  ws001-binarydata       pic X(99999).
                   
      /
       PROCEDURE DIVISION.
       INICIO SECTION.
       INI-1.           


           INITIALIZE VAR-PROGRAMA.
           INITIALIZE parametros-ws001.           
           
           xml initialize.
           if not xml-ok then             
              DISPLAY "ERROR XML INITIALIZE"
              GO TO FIN-PROGRAMA
           end-if.
      **           
           INITIALIZE ws001-parametres-entrada.
           MOVE "12345" TO ws001-binarydata.
             
           MOVE SPACES TO RUTA-MODELO
           STRING
               PATH-MODELO
                DELIMITED BY SPACES
               "BASE0085-WS1"
                DELIMITED BY SIZE
           INTO RUTA-MODELO.
             
           MOVE SPACES TO RUTA-PLANTILLA
           STRING
               PATH-PLANTILLA
                DELIMITED BY SPACES
               "BASE0085-WS1PL.XSL"
                DELIMITED BY SIZE
           INTO RUTA-PLANTILLA.
                       
           DISPLAY "RUTA-MODEL: ", RUTA-MODELO
           DISPLAY "RUTA-PLANTILLA: ", RUTA-PLANTILLA
           XML EXPORT TEXT
               ws001-parametres-entrada
               request-payload
               RUTA-MODELO
               RUTA-PLANTILLA.
               
           if not XML-OK then
               DISPLAY "ERROR EXPORT"
           end-if.
      **     
           xml put text
               request-payload
               "./P1".
           if not xml-ok then             
              DISPLAY  "ERROR " XML-STATUS " EN XML PUT"
              stop run
           else
              DISPLAY  "OK. THE PROGRAM HAS GENERATED: ./P1.xml"
           end-if.
      **     
           XML TERMINATE.
       
       FIN-PROGRAMA.                         
           GOBACK.


But when I want to compile/build it with Visual Cobol I receive the next error:

os.init:

os.init.windows:

os.init.unix:

init:

pre.build.cfg.New_Configuration:

os.init:

os.init.windows:

os.init.unix:

init:

cfg.New_Configuration:
    [cobol]
    [cobol] Compiling (64-bit) PROVAXML2.cbl...
    [cobol] * 019-C Program checked with non-optimal alignment. Optimal alignment is 8
    [cobol] * 013-R Illegal intermediate code (at 0X349 in seg 0)
    [cobol] cob64: error(s) in code generation: /MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/outEcl/PROVAXML2.int
    [cobol] Compilation complete with 0 errors, 0 warnings, 0 notices and an exit code of 1
[cobollink] Linking (64-bit) PROVAXML2.so...
[cobollink] cob64: error opening: PROVAXML2.o
[cobollink] Link complete with errors
[cobollink]


BUILD FAILED
Build finished with 1 errors, 0 warnings, 0 notices and a maximum exit code of 1

/MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/.cobolBuild:142: Build errors have occurred

Total time: 0 seconds




The program resides on a remote AIX server. I've tried to compile the program from the same remote server using the "cob" command, and also from Eclipse (Windows), and in both cases I get the same error.

I've used the next compiler directives

SHOW-DIR
CALLFH(ACUFH)
RM "GIVING"
RM "ANSI"
NOOPTIONAL-FILE
REMOVE"TIMEOUT"



I think maybe I have to attach a library of XML Extensions but I do not know how ..


Where can be the problem?


Thanks in advance
Hello,

I believed that Xml Extensions were supported on Unix systems since version 2.0 (this is the version I am evaluating under an AIX right now).

I am trying to follow these instructions:
Building from your COBOL development system

This requires that you put additional code into your program that specifies use of the XML preprocessor.

Before you build your XML-enabled COBOL, you must insert the following code on the first line of your program before the Identification Division:

$set {preprocess | p}(prexml) [{out | o} (outname)] [warn]
[{preprocess | p} (ppname)] endp

where the parameters are:

{preprocess | p}
The pre-processor to be used.
{out | o} outname
The fully preprocessed output source file, outname. This output source file contains native COBOL processed from the XML syntax.
warn
Cause diagnostic warnings on parsing to be presented by PREXML.
ppname
The preprocessor name you want to use to read source files and process COPY statements. Preprocessors can be nested.

For example:

$set p(prexml) warn endp

But I am obtainig the following error:
[03500309@aixlab0102]:>VC_COMPI2 PROVA8                                         
/swmango/visualcobol2.0/devhub/bin/cob -z PROVA8.CBL -U -P                     
     2$set p(prexml) warn endp                                                 
*  53-S*****                                                           (   0)**
**    Directive P invalid or not allowed here                                   
cob64: error(s) in compilation: PROVA8.CBL                                     

I was also dealing with cbl2xml without that directive, but I got these errors after using the generated copy:
[03500309@aixlab0102]:>/swmango/visualcobol2.0/devhub/bin/cbl2xml PROVA8.CBL   
Micro Focus CBL2XML Version 7.0.3.0                                             
Copyright (C) Micro Focus 1984-2012. All rights reserved.                       
                                                                               
Checking PROVA8.CBL for errors                                                 
    16  01 rootItem identified by "rootItem" count in rootItem-count.           
* 781-S***********************                                               **
**    01 Group item must have the EXTERNAL-FORM clause.                         

[Migrated content. Thread originally posted on 21 December 2011]

Hello,

I have this program that works correctly in RM/COBOL. It generates an XML document with the XML extensions libraries.


       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROVAXML2.
       AUTHOR. mossa.
       DATE-WRITTEN. 20080304.
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. LEVEL-6.
       OBJECT-COMPUTER. LEVEL-6.
       SPECIAL-NAMES.
           DECIMAL-POINT COMMA.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 VAR-PROGRAMA.
          03 url                          pic x(100).
          03 xmlrespuesta                 pic x(50).           
          03  request-payload             usage pointer.
          03  response-payload            usage pointer.
          03  response-error              usage pointer.
          03  response-status             pic 9(3) value zero.
          03  response-len                pic s9(4).
          03  a-single-char               pic x.
          03  longrequest.
              05 filler                   pic x occurs 1 to 65000
                                         times depending on counters.
          03 counters                     pic 9(5).

          03 Returned-text                pic x(1031).
          03 RUTA-MODELO                  PIC X(150).
          03 RUTA-PLANTILLA               PIC X(150).
          03 IDJOB                        PIC X(100).
          03 RESULTAT-WEBSERVICE          PIC X(10).
          03 STAT-TRABAJO PIC X(2).
          03 LOC-TRABAJO  PIC X(100).     
         
       01 XML-RESPUESTA.
          03 returnResult pic x(100).               
             
       01 PATH-MODELO PIC X(100)
               VALUE "/MNG/DESA/XML/".                     
       01 PATH-PLANTILLA PIC X(100)
               VALUE "/MNG/DESA/XML/".               
               
           Copy "lixmlall.cpy".         
       
       01 parametros-ws001.                     
           02 ws001-parametres-entrada.
                03 ws001-indata.
                   04  ws001-remoteurl        pic x(30).
                   04  ws001-pcontenttype     pic x(50).
                   04  ws001-attachmentid     pic x(50).
                   04  ws001-binarydata       pic X(99999).
                   
      /
       PROCEDURE DIVISION.
       INICIO SECTION.
       INI-1.           


           INITIALIZE VAR-PROGRAMA.
           INITIALIZE parametros-ws001.           
           
           xml initialize.
           if not xml-ok then             
              DISPLAY "ERROR XML INITIALIZE"
              GO TO FIN-PROGRAMA
           end-if.
      **           
           INITIALIZE ws001-parametres-entrada.
           MOVE "12345" TO ws001-binarydata.
             
           MOVE SPACES TO RUTA-MODELO
           STRING
               PATH-MODELO
                DELIMITED BY SPACES
               "BASE0085-WS1"
                DELIMITED BY SIZE
           INTO RUTA-MODELO.
             
           MOVE SPACES TO RUTA-PLANTILLA
           STRING
               PATH-PLANTILLA
                DELIMITED BY SPACES
               "BASE0085-WS1PL.XSL"
                DELIMITED BY SIZE
           INTO RUTA-PLANTILLA.
                       
           DISPLAY "RUTA-MODEL: ", RUTA-MODELO
           DISPLAY "RUTA-PLANTILLA: ", RUTA-PLANTILLA
           XML EXPORT TEXT
               ws001-parametres-entrada
               request-payload
               RUTA-MODELO
               RUTA-PLANTILLA.
               
           if not XML-OK then
               DISPLAY "ERROR EXPORT"
           end-if.
      **     
           xml put text
               request-payload
               "./P1".
           if not xml-ok then             
              DISPLAY  "ERROR " XML-STATUS " EN XML PUT"
              stop run
           else
              DISPLAY  "OK. THE PROGRAM HAS GENERATED: ./P1.xml"
           end-if.
      **     
           XML TERMINATE.
       
       FIN-PROGRAMA.                         
           GOBACK.


But when I want to compile/build it with Visual Cobol I receive the next error:

os.init:

os.init.windows:

os.init.unix:

init:

pre.build.cfg.New_Configuration:

os.init:

os.init.windows:

os.init.unix:

init:

cfg.New_Configuration:
    [cobol]
    [cobol] Compiling (64-bit) PROVAXML2.cbl...
    [cobol] * 019-C Program checked with non-optimal alignment. Optimal alignment is 8
    [cobol] * 013-R Illegal intermediate code (at 0X349 in seg 0)
    [cobol] cob64: error(s) in code generation: /MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/outEcl/PROVAXML2.int
    [cobol] Compilation complete with 0 errors, 0 warnings, 0 notices and an exit code of 1
[cobollink] Linking (64-bit) PROVAXML2.so...
[cobollink] cob64: error opening: PROVAXML2.o
[cobollink] Link complete with errors
[cobollink]


BUILD FAILED
Build finished with 1 errors, 0 warnings, 0 notices and a maximum exit code of 1

/MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/.cobolBuild:142: Build errors have occurred

Total time: 0 seconds




The program resides on a remote AIX server. I've tried to compile the program from the same remote server using the "cob" command, and also from Eclipse (Windows), and in both cases I get the same error.

I've used the next compiler directives

SHOW-DIR
CALLFH(ACUFH)
RM "GIVING"
RM "ANSI"
NOOPTIONAL-FILE
REMOVE"TIMEOUT"



I think maybe I have to attach a library of XML Extensions but I do not know how ..


Where can be the problem?


Thanks in advance
XML Extensions are available for RM/COBOL compatibility.

This is something completely different than the XMLIO preprocessor that you are referencing in your post.
This comes from Net Express/Server Express.

The XML IO preprocessor that you are trying to use is supported in Visual COBOL 2.0 Dev Hub.

We tested here and it worked fine:
>cob -v test-xml.cbl
cob64 -C nolist -v test-xml.cbl
* Micro Focus COBOL V2.0 revision 001 Compiler
* Copyright (C) Micro Focus 1984-2012. All rights reserved.
* Accepted - verbose
* Accepted - nolist
* Compiling test-xml.cbl
Micro Focus Embedded XML/HTML Preprocessor
Version a.b.cc Copyright (C) Micro Focus 1984-2012. All rights reserved.
* Total Messages: 0
* Data: 2072 Code: 321

So, the XML preprocessor is available and working in the Dev Hub.

The strange output you’re seeing:

cob -z PROVA8.CBL -U –P
2$set p(prexml) warn endp
* 53-S***** ( 0)**
** Directive P invalid or not allowed here

is caused by a syntax error in the “cob” command line.
It seems “VC_COMPI2” is issuing a “cob” command line that includes syntax errors.

Is the $set p(prexml) warn endp statement the first line in your source program or are you trying to pass this on the command line? It should be the first line in your source program.

On you second issue I am not sure what you are trying to do with CBL2XML.
This utility takes a COBOL file description as input (in a copybook) and will generate an XML enabled version of that copybook as output.

The input must be standard COBOL, not XML enabled COBOL.

This is why you are seeing those errors when you run it against a generated xml-enabled copyfile.

[Migrated content. Thread originally posted on 21 December 2011]

Hello,

I have this program that works correctly in RM/COBOL. It generates an XML document with the XML extensions libraries.


       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROVAXML2.
       AUTHOR. mossa.
       DATE-WRITTEN. 20080304.
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. LEVEL-6.
       OBJECT-COMPUTER. LEVEL-6.
       SPECIAL-NAMES.
           DECIMAL-POINT COMMA.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 VAR-PROGRAMA.
          03 url                          pic x(100).
          03 xmlrespuesta                 pic x(50).           
          03  request-payload             usage pointer.
          03  response-payload            usage pointer.
          03  response-error              usage pointer.
          03  response-status             pic 9(3) value zero.
          03  response-len                pic s9(4).
          03  a-single-char               pic x.
          03  longrequest.
              05 filler                   pic x occurs 1 to 65000
                                         times depending on counters.
          03 counters                     pic 9(5).

          03 Returned-text                pic x(1031).
          03 RUTA-MODELO                  PIC X(150).
          03 RUTA-PLANTILLA               PIC X(150).
          03 IDJOB                        PIC X(100).
          03 RESULTAT-WEBSERVICE          PIC X(10).
          03 STAT-TRABAJO PIC X(2).
          03 LOC-TRABAJO  PIC X(100).     
         
       01 XML-RESPUESTA.
          03 returnResult pic x(100).               
             
       01 PATH-MODELO PIC X(100)
               VALUE "/MNG/DESA/XML/".                     
       01 PATH-PLANTILLA PIC X(100)
               VALUE "/MNG/DESA/XML/".               
               
           Copy "lixmlall.cpy".         
       
       01 parametros-ws001.                     
           02 ws001-parametres-entrada.
                03 ws001-indata.
                   04  ws001-remoteurl        pic x(30).
                   04  ws001-pcontenttype     pic x(50).
                   04  ws001-attachmentid     pic x(50).
                   04  ws001-binarydata       pic X(99999).
                   
      /
       PROCEDURE DIVISION.
       INICIO SECTION.
       INI-1.           


           INITIALIZE VAR-PROGRAMA.
           INITIALIZE parametros-ws001.           
           
           xml initialize.
           if not xml-ok then             
              DISPLAY "ERROR XML INITIALIZE"
              GO TO FIN-PROGRAMA
           end-if.
      **           
           INITIALIZE ws001-parametres-entrada.
           MOVE "12345" TO ws001-binarydata.
             
           MOVE SPACES TO RUTA-MODELO
           STRING
               PATH-MODELO
                DELIMITED BY SPACES
               "BASE0085-WS1"
                DELIMITED BY SIZE
           INTO RUTA-MODELO.
             
           MOVE SPACES TO RUTA-PLANTILLA
           STRING
               PATH-PLANTILLA
                DELIMITED BY SPACES
               "BASE0085-WS1PL.XSL"
                DELIMITED BY SIZE
           INTO RUTA-PLANTILLA.
                       
           DISPLAY "RUTA-MODEL: ", RUTA-MODELO
           DISPLAY "RUTA-PLANTILLA: ", RUTA-PLANTILLA
           XML EXPORT TEXT
               ws001-parametres-entrada
               request-payload
               RUTA-MODELO
               RUTA-PLANTILLA.
               
           if not XML-OK then
               DISPLAY "ERROR EXPORT"
           end-if.
      **     
           xml put text
               request-payload
               "./P1".
           if not xml-ok then             
              DISPLAY  "ERROR " XML-STATUS " EN XML PUT"
              stop run
           else
              DISPLAY  "OK. THE PROGRAM HAS GENERATED: ./P1.xml"
           end-if.
      **     
           XML TERMINATE.
       
       FIN-PROGRAMA.                         
           GOBACK.


But when I want to compile/build it with Visual Cobol I receive the next error:

os.init:

os.init.windows:

os.init.unix:

init:

pre.build.cfg.New_Configuration:

os.init:

os.init.windows:

os.init.unix:

init:

cfg.New_Configuration:
    [cobol]
    [cobol] Compiling (64-bit) PROVAXML2.cbl...
    [cobol] * 019-C Program checked with non-optimal alignment. Optimal alignment is 8
    [cobol] * 013-R Illegal intermediate code (at 0X349 in seg 0)
    [cobol] cob64: error(s) in code generation: /MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/outEcl/PROVAXML2.int
    [cobol] Compilation complete with 0 errors, 0 warnings, 0 notices and an exit code of 1
[cobollink] Linking (64-bit) PROVAXML2.so...
[cobollink] cob64: error opening: PROVAXML2.o
[cobollink] Link complete with errors
[cobollink]


BUILD FAILED
Build finished with 1 errors, 0 warnings, 0 notices and a maximum exit code of 1

/MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/.cobolBuild:142: Build errors have occurred

Total time: 0 seconds




The program resides on a remote AIX server. I've tried to compile the program from the same remote server using the "cob" command, and also from Eclipse (Windows), and in both cases I get the same error.

I've used the next compiler directives

SHOW-DIR
CALLFH(ACUFH)
RM "GIVING"
RM "ANSI"
NOOPTIONAL-FILE
REMOVE"TIMEOUT"



I think maybe I have to attach a library of XML Extensions but I do not know how ..


Where can be the problem?


Thanks in advance
Chris Glazier originally wrote:
XML Extensions are available for RM/COBOL compatibility.

This is something completely different than the XMLIO preprocessor that you are referencing in your post.
This comes from Net Express/Server Express.

The XML IO preprocessor that you are trying to use is supported in Visual COBOL 2.0 Dev Hub.

We tested here and it worked fine:
>cob -v test-xml.cbl
cob64 -C nolist -v test-xml.cbl
* Micro Focus COBOL V2.0 revision 001 Compiler
* Copyright (C) Micro Focus 1984-2012. All rights reserved.
* Accepted - verbose
* Accepted - nolist
* Compiling test-xml.cbl
Micro Focus Embedded XML/HTML Preprocessor
Version a.b.cc Copyright (C) Micro Focus 1984-2012. All rights reserved.
* Total Messages: 0
* Data: 2072 Code: 321

So, the XML preprocessor is available and working in the Dev Hub.

The strange output you’re seeing:

cob -z PROVA8.CBL -U –P
2$set p(prexml) warn endp
* 53-S***** ( 0)**
** Directive P invalid or not allowed here

is caused by a syntax error in the “cob” command line.
It seems “VC_COMPI2” is issuing a “cob” command line that includes syntax errors.

Is the $set p(prexml) warn endp statement the first line in your source program or are you trying to pass this on the command line? It should be the first line in your source program.

Yes, the set directive is the first line in my program.

Chris Glazier originally wrote:

On you second issue I am not sure what you are trying to do with CBL2XML.
This utility takes a COBOL file description as input (in a copybook) and will generate an XML enabled version of that copybook as output.

The input must be standard COBOL, not XML enabled COBOL.

This is why you are seeing those errors when you run it against a generated xml-enabled copyfile.

I use cbl2xml to generate the Xml version of the copybook and then I substitute mine by the generated one.

[Migrated content. Thread originally posted on 21 December 2011]

Hello,

I have this program that works correctly in RM/COBOL. It generates an XML document with the XML extensions libraries.


       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROVAXML2.
       AUTHOR. mossa.
       DATE-WRITTEN. 20080304.
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. LEVEL-6.
       OBJECT-COMPUTER. LEVEL-6.
       SPECIAL-NAMES.
           DECIMAL-POINT COMMA.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 VAR-PROGRAMA.
          03 url                          pic x(100).
          03 xmlrespuesta                 pic x(50).           
          03  request-payload             usage pointer.
          03  response-payload            usage pointer.
          03  response-error              usage pointer.
          03  response-status             pic 9(3) value zero.
          03  response-len                pic s9(4).
          03  a-single-char               pic x.
          03  longrequest.
              05 filler                   pic x occurs 1 to 65000
                                         times depending on counters.
          03 counters                     pic 9(5).

          03 Returned-text                pic x(1031).
          03 RUTA-MODELO                  PIC X(150).
          03 RUTA-PLANTILLA               PIC X(150).
          03 IDJOB                        PIC X(100).
          03 RESULTAT-WEBSERVICE          PIC X(10).
          03 STAT-TRABAJO PIC X(2).
          03 LOC-TRABAJO  PIC X(100).     
         
       01 XML-RESPUESTA.
          03 returnResult pic x(100).               
             
       01 PATH-MODELO PIC X(100)
               VALUE "/MNG/DESA/XML/".                     
       01 PATH-PLANTILLA PIC X(100)
               VALUE "/MNG/DESA/XML/".               
               
           Copy "lixmlall.cpy".         
       
       01 parametros-ws001.                     
           02 ws001-parametres-entrada.
                03 ws001-indata.
                   04  ws001-remoteurl        pic x(30).
                   04  ws001-pcontenttype     pic x(50).
                   04  ws001-attachmentid     pic x(50).
                   04  ws001-binarydata       pic X(99999).
                   
      /
       PROCEDURE DIVISION.
       INICIO SECTION.
       INI-1.           


           INITIALIZE VAR-PROGRAMA.
           INITIALIZE parametros-ws001.           
           
           xml initialize.
           if not xml-ok then             
              DISPLAY "ERROR XML INITIALIZE"
              GO TO FIN-PROGRAMA
           end-if.
      **           
           INITIALIZE ws001-parametres-entrada.
           MOVE "12345" TO ws001-binarydata.
             
           MOVE SPACES TO RUTA-MODELO
           STRING
               PATH-MODELO
                DELIMITED BY SPACES
               "BASE0085-WS1"
                DELIMITED BY SIZE
           INTO RUTA-MODELO.
             
           MOVE SPACES TO RUTA-PLANTILLA
           STRING
               PATH-PLANTILLA
                DELIMITED BY SPACES
               "BASE0085-WS1PL.XSL"
                DELIMITED BY SIZE
           INTO RUTA-PLANTILLA.
                       
           DISPLAY "RUTA-MODEL: ", RUTA-MODELO
           DISPLAY "RUTA-PLANTILLA: ", RUTA-PLANTILLA
           XML EXPORT TEXT
               ws001-parametres-entrada
               request-payload
               RUTA-MODELO
               RUTA-PLANTILLA.
               
           if not XML-OK then
               DISPLAY "ERROR EXPORT"
           end-if.
      **     
           xml put text
               request-payload
               "./P1".
           if not xml-ok then             
              DISPLAY  "ERROR " XML-STATUS " EN XML PUT"
              stop run
           else
              DISPLAY  "OK. THE PROGRAM HAS GENERATED: ./P1.xml"
           end-if.
      **     
           XML TERMINATE.
       
       FIN-PROGRAMA.                         
           GOBACK.


But when I want to compile/build it with Visual Cobol I receive the next error:

os.init:

os.init.windows:

os.init.unix:

init:

pre.build.cfg.New_Configuration:

os.init:

os.init.windows:

os.init.unix:

init:

cfg.New_Configuration:
    [cobol]
    [cobol] Compiling (64-bit) PROVAXML2.cbl...
    [cobol] * 019-C Program checked with non-optimal alignment. Optimal alignment is 8
    [cobol] * 013-R Illegal intermediate code (at 0X349 in seg 0)
    [cobol] cob64: error(s) in code generation: /MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/outEcl/PROVAXML2.int
    [cobol] Compilation complete with 0 errors, 0 warnings, 0 notices and an exit code of 1
[cobollink] Linking (64-bit) PROVAXML2.so...
[cobollink] cob64: error opening: PROVAXML2.o
[cobollink] Link complete with errors
[cobollink]


BUILD FAILED
Build finished with 1 errors, 0 warnings, 0 notices and a maximum exit code of 1

/MNG/DESA/FUENTES/EQBASE/visual_cobol/provaRemot6_XML/.cobolBuild:142: Build errors have occurred

Total time: 0 seconds




The program resides on a remote AIX server. I've tried to compile the program from the same remote server using the "cob" command, and also from Eclipse (Windows), and in both cases I get the same error.

I've used the next compiler directives

SHOW-DIR
CALLFH(ACUFH)
RM "GIVING"
RM "ANSI"
NOOPTIONAL-FILE
REMOVE"TIMEOUT"



I think maybe I have to attach a library of XML Extensions but I do not know how ..


Where can be the problem?


Thanks in advance
Chris Glazier originally wrote:
XML Extensions are available for RM/COBOL compatibility.

This is something completely different than the XMLIO preprocessor that you are referencing in your post.
This comes from Net Express/Server Express.

The XML IO preprocessor that you are trying to use is supported in Visual COBOL 2.0 Dev Hub.

We tested here and it worked fine:
>cob -v test-xml.cbl
cob64 -C nolist -v test-xml.cbl
* Micro Focus COBOL V2.0 revision 001 Compiler
* Copyright (C) Micro Focus 1984-2012. All rights reserved.
* Accepted - verbose
* Accepted - nolist
* Compiling test-xml.cbl
Micro Focus Embedded XML/HTML Preprocessor
Version a.b.cc Copyright (C) Micro Focus 1984-2012. All rights reserved.
* Total Messages: 0
* Data: 2072 Code: 321

So, the XML preprocessor is available and working in the Dev Hub.

The strange output you’re seeing:

cob -z PROVA8.CBL -U –P
2$set p(prexml) warn endp
* 53-S***** ( 0)**
** Directive P invalid or not allowed here

is caused by a syntax error in the “cob” command line.
It seems “VC_COMPI2” is issuing a “cob” command line that includes syntax errors.

Is the $set p(prexml) warn endp statement the first line in your source program or are you trying to pass this on the command line? It should be the first line in your source program.

Yes, the set directive is the first line in my program.

Chris Glazier originally wrote:

On you second issue I am not sure what you are trying to do with CBL2XML.
This utility takes a COBOL file description as input (in a copybook) and will generate an XML enabled version of that copybook as output.

The input must be standard COBOL, not XML enabled COBOL.

This is why you are seeing those errors when you run it against a generated xml-enabled copyfile.

I use cbl2xml to generate the Xml version of the copybook and then I substitute mine by the generated one.