[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

HTTPAPI and COBOL



   Hi, Alain.
   Thanks for your help.
   I am compiling the program using the command CRTBNDCBL and then
   CRTPGM.
   Whatever, I have compiled the program using CRTCBLPGM but the compiler
   doesn´t accept the Linkage procedure... in Special names and
   eliminated all sentences until it found the PROCEDURE DIVISION.
   I don´t know what is happening.
   Thanks.
   ______________________________________________________________________

   De: "Alain RUAS" <alain.ruas@xxxxxxxxxxxxx>
   Enviado: jueves, 11 de diciembre de 2008 7:26
   Para: "HTTPAPI and FTPAPI Projects" <ftpapi@xxxxxxxxxxxxxxxxxxxxxx>
   Asunto: RE : HTTPAPI and COBOL
   Hi Luis,
   When you compile your program, what command are you using :
   CRTCBLPGM
   Or
   CRTBNDCBL
   Let us know.
   There is no option to compile with long procedure names.
   You only have to be sure that your program is CBLLE and not CBL.
   Alain RUAS
   Technical Manager
   (33) 562 747 500
   -----Message d'origine-----
   De : ftpapi-bounces@xxxxxxxxxxxxxxxxxxxxxx
   [mailto:ftpapi-bounces@xxxxxxxxxxxxxxxxxxxxxx] De la part de
   lescobar@xxxxxxxxxxxxxxxxx
   Envoyé : jeu. 11 décembre 2008 12:21
   À : ftpapi@xxxxxxxxxxxxxxxxxxxxxx
   Objet : Re: HTTPAPI and COBOL
   Hi, Titus.
   Thanks for your help.
   When I compile the program, I have error for the program name too
   long.
   I want to know, What options I have to add for compiling without
   errors when I call long procedure name?
   Again, thanks a lot.
   Luis.
   ----------------------------------------
   De: "Titus Aguilar"
   Enviado: miércoles, 10 de diciembre de 2008 20:32
   Para: "HTTPAPI and FTPAPI Projects"
   Asunto: Re: HTTPAPI and COBOL
   Hi Luis,
   I can confirm to you that the long procedure name is valid in V5R3. I
   successfully created an ILE Cobol calling HTTPAPI last year running in
   V5R3. Make sure that your source type is CBLLE and the proper compile
   options are used. The link that Scott provided earlier should be a
   very good example.
   Hth,
   Titus
   On 12/10/08, Mike Krebs wrote:
   > Someone familiar with V5R3 COBOL probably has to answer that one.
   "Programs"
   > being objects are limited to 10 characters. But I think we've had
   long
   > procedure name support for a while. I scanned the V5R3 manuals
   tonight and
   > saw nothing either way.
   >
   > I did scan a number of V5R3 COBOL messages on midrange.com that
   seemed to be
   > using long procedure names. Maybe you could post your program code
   and I
   > will let you know if it compiles on V5R4.
   >
   > Mike Krebs
   >
   > -----Original Message-----
   > From: ftpapi-bounces@xxxxxxxxxxxxxxxxxxxxxx
   > [mailto:ftpapi-bounces@xxxxxxxxxxxxxxxxxxxxxx] On Behalf Of
   > lescobar@xxxxxxxxxxxxxxxxx
   > Sent: Tuesday, December 09, 2008 3:26 PM
   > To: ftpapi@xxxxxxxxxxxxxxxxxxxxxx
   > Subject: RE: HTTPAPI and COBOL
   >
   >
   > Hi Mike, thanks again.
   >
   > I think my problem is the version of Cobol 5.3. You are running in
   V5.R4,
   > isn't it?
   >
   > The error really is the name too long, version 5.3 accepts up to 10
   > characters, even without special characters like "_".
   >
   > What do you think about this?
   >
   > Ok, thanks for your help.
   >
   > Luis
   >
   > ----------------------------------------
   >
   > De: "Mike Krebs"
   > Enviado: martes, 09 de diciembre de 2008 13:52
   > Para: "'HTTPAPI and FTPAPI Projects'"
   > Asunto: RE: HTTPAPI and COBOL
   >
   > Luis,
   >
   > I think you probably have some error in the code that is causing the
   error
   > you are seeing.
   >
   > I copied the example18 and example18p code from the forum post to
   our system
   > today. Made a few changes to try to get the warnings cleared up and
   compiled
   > and ran the program. Here is the code I used. I hope it doesn't wrap
   too
   > badly in the email. It compiles fine following the instructions on
   V5R4. I
   > didn't see much in the V5R4 COBOL manual about any changes that
   adversely
   > affect this program, but I admit I haven't looked at COBOL for
   almost 20
   > years. And looking at it now, I don't remember what I liked about
   it!
   >
   > The changes I made include changing the ' to " and double quoting
   the ".
   > Changed the LSAA-AMOUNT field to PIC S9(10)V9(5).
   > Added a period or two where they seemed to be missing.
   > Changed the END PROGRAM statement on EXAMPLE18.
   >
   > Actually running the example, the service is unavailable once again.
   This
   > means I didn't get a "successful" run, but both the RPG version and
   the
   > COBOL return the same error (server is too busy). Maybe later today,
   it will
   > run successfully.
   >
   > Good luck,
   > Mike Krebs
   >
   > EXAMPLE18
   >
   > IDENTIFICATION DIVISION.
   > PROGRAM-ID. EXAMPLE18.
   > *
   > * Version 1.0 Mick O'Hea November 2007
   > *
   > * Conversion of Scott's RPG example call to a SOAP web service
   > * using HTTPAPI.
   > *
   > * This sample calls the Currency Exchange Rate Web service
   > * provided by WebserviceX.net. For more info, search for it
   > * at http://www.WebserviceX.net
   > *
   > * To Run:
   > * CALL EXAMPLE18 PARM('USD' 'JPY' 12.00)
   > *
   > * (This shows the value of USD 12.00 in Japanese currency.)
   > *
   > * Note: This program is ILE Cobol, hence the member type is
   > * CBLLE. It uses commands not available in OPM COBOL.
   > *
   > * Compile with:
   > * CRTCBLMOD MODULE(LIBHTTP/EXAMPLE18) SRCFILE(LIBHTTP/QCBLLESRC)
   > * OPTION(*NOMONOPRC *NOSTDTRUNC) DBGVIEW(*LIST)
   > * *NOMONOPRC is needed so we can call mixed-case RPG procedures
   > * *NOSTDTRUNC is needed to correctly pass binary numeric fields
   > * to RPG
   >
   > * Compile the XML parsing module the same way, then link them:
   > * CRTPGM PGM(LIBHTTP/EXAMPLE18)
   > * MODULE(LIBHTTP/EXAMPLE18 LIBHTTP/EXAMPLE18P)
   > * BNDDIR(LIBHTTP/HTTPAPI QSYS/QC2LE)
   > *
   > * The APIs we need to call are located in HTTPAPI and QC2LE, so
   > * we need to include those in the BNDDIR parameter.
   > * The DBGVIEW isn't necessary, but is handy for debugging.
   > *
   > ENVIRONMENT DIVISION.
   > CONFIGURATION SECTION.
   > SOURCE-COMPUTER. IBM-AS400.
   > OBJECT-COMPUTER. IBM-AS400.
   >
   > SPECIAL-NAMES.
   > LINKAGE TYPE IS PROCEDURE FOR "HTTP_URL_POST_XML"
   > USING ALL ARE DESCRIBED.
   >
   > * LINKAGE TYPE is needed for calls from COBOL to RPG procedures
   > * which have optional arguments, otherwise the RPG procedure
   > * doesn't correctly count the number of parameters it receives.
   >
   > *
   > DATA DIVISION.
   > WORKING-STORAGE SECTION.
   > *
   > 01 WSAA-URL-POINTER POINTER.
   > *
   > 01 WSAA-STARTPROC-POINTER PROCEDURE-POINTER.
   > 01 WSAA-ENDPROC-POINTER PROCEDURE-POINTER.
   > 01 WSAA-RETURN-CODE PIC S9(9) BINARY.
   > 01 WSAA-SOAP-POINTER USAGE IS POINTER.
   > 01 WSAA-OUTPUT-POINTER USAGE IS POINTER.
   >
   > * Because the RPG requires a variable length string for the URL,
   > * it doesn't seem to work if we pass a group item. So we build
   > * it up in WSAA-URL-SPLIT, then move is to WSAA-URL and pass that
   > * The length is stored in the first two bytes so RPG knows how
   > * long it is.
   >
   > 01 WSAA-URL-SPLIT.
   > 03 WSAA-URL-LEN PIC S9(4) BINARY.
   > 03 WSAA-URL-BODY PIC X(100) VALUE
   > "http://www.webservicex.net/CurrencyConvertor.asmx";.
   > 01 WSAA-URL PIC X(102).
   >
   > * NB: WSAA-URL must be the length of WSAA-URL-BODY + 2
   >
   > 01 WSAA-SOAP-ENVELOPE.
   > 03 FILLER PIC X(20) VALUE
   > "".
   > 03 FILLER PIC X(18) VALUE
   > " ".
   > 03 FILLER PIC X(26) VALUE
   > " ".
   > 03 FILLER PIC X(18) VALUE
   > "".
   > 03 WSAA-FROM-CURR PIC X(3).
   > 03 FILLER PIC X(25) VALUE
   > " ".
   > 03 FILLER PIC X(16) VALUE
   > "".
   > 03 WSAA-TO-CURR PIC X(3).
   > 03 FILLER PIC X(19) VALUE
   > " ".
   > 03 FILLER PIC X(21) VALUE
   > "".
   > 03 FILLER PIC X(12) VALUE
   > "".
   > 03 FILLER PIC X(16) VALUE
   > "".
   >
   > 01 WSAA-SOAP-ENVELOPE-SEND PIC X(371).
   > /
   > 01 WSAA-SOAP-LEN PIC S9(9) COMP-4.
   > 01 WSAA-TIMEOUT PIC S9(9) COMP-4 VALUE 60.
   > 01 WSAA-USER-AGENT PIC X(64) VALUE "http-api/1.23".
   > 01 WSAA-CONTENT-TYPE PIC X(64) VALUE "text/xml".
   > 01 WSAA-SOAP-ACTION PIC X(64)
   > VALUE "http://www.webserviceX.NET/ConversionRate";.
   >
   > 01 WSAA-RATE PIC 9(4)V9(5) external.
   > 01 WSAA-RESULT PIC S9(10)V9(2).
   >
   > LINKAGE SECTION.
   >
   > 01 LSAA-FROM-CURR PIC X(3).
   > 01 LSAA-TO-CURR PIC X(3).
   > 01 LSAA-AMOUNT PIC S9(10)V9(5).
   > /
   > PROCEDURE DIVISION USING LSAA-FROM-CURR
   > LSAA-TO-CURR
   > LSAA-AMOUNT.
   > *
   > /
   > 1000-MAIN SECTION.
   > ***********************
   > *
   > 1000-MAIN-START.
   > *
   > MOVE LSAA-FROM-CURR TO WSAA-FROM-CURR.
   > MOVE LSAA-TO-CURR TO WSAA-TO-CURR.
   > *** If you had a case where whitespace in the parameters caused
   > *** problems, you'd need to do something like this instead:
   > *** STRING '' DELIMITED BY SIZE
   > *** LSAA-FROM-CURR DELIMITED BY SPACES
   > *** '' DELIMITED BY SIZE
   > *** INTO WSAA-FROM-CURR.
   >
   > * Handier to use LENGTH function here in case we need to change
   > * the size of the URL parameter in future
   > MOVE LENGTH OF WSAA-URL-BODY TO WSAA-URL-LEN.
   > MOVE WSAA-URL-SPLIT TO WSAA-URL.
   >
   > MOVE WSAA-SOAP-ENVELOPE TO WSAA-SOAP-ENVELOPE-SEND.
   > SET WSAA-SOAP-POINTER TO ADDRESS OF WSAA-SOAP-ENVELOPE-SEND.
   > MOVE LENGTH OF WSAA-SOAP-ENVELOPE-SEND TO WSAA-SOAP-LEN.
   > **** display wsaa-soap-envelope.
   >
   > * We need to pass to the RPG details of the procedure to call
   > * whenever the end of an XML element is found by the parser.
   > * For COBOL, this procedure will be in a separate module which
   > * will be linked in at compile time.
   > * We don't care about the start of an element so STARTPROC = null
   >
   > SET WSAA-STARTPROC-POINTER TO NULL.
   > SET WSAA-ENDPROC-POINTER TO ENTRY
   > LINKAGE PROCEDURE "EXAMPLE18P".
   > * We point WSAA-OUTPUT-POINTER to the variable we want to pass
   > * back the return value in.
   > ** NB - this does not appear to work correctly **
   > ** EXTERNAL variable used instead **
   > SET WSAA-OUTPUT-POINTER TO ADDRESS OF WSAA-RATE.
   >
   > * Call the RPG procedure to pass the request to the web service
   > * and receive the response.
   > * The URL is a variable length string, and must be passed by
   > * reference.
   > CALL PROCEDURE
   > "HTTP_URL_POST_XML" USING BY REFERENCE WSAA-URL
   > BY value WSAA-SOAP-POINTER
   > BY VALUE WSAA-SOAP-LEN
   > BY value WSAA-STARTPROC-POINTER
   > BY value WSAA-ENDPROC-POINTER
   > BY value WSAA-OUTPUT-POINTER
   > BY VALUE WSAA-TIMEOUT
   > BY reference WSAA-USER-AGENT
   > BY REFERENCE WSAA-CONTENT-TYPE
   > BY REFERENCE WSAA-SOAP-ACTION
   > RETURNING WSAA-RETURN-CODE.
   >
   > * In case of error, call HTTP_CRASH to parse the error message
   > * an proceed to the error section
   > IF WSAA-RETURN-CODE NOT = 1
   > CALL PROCEDURE "HTTP_CRASH"
   > GO TO 1050-ERROR
   > END-IF.
   >
   > * A dummy exchange rate means that we didn't get a valid value
   > * back from the web service
   > IF WSAA-RATE = -9999.99999
   > GO TO 1050-ERROR
   > END-IF.
   >
   > * Populate any return parameters here.
   > COMPUTE WSAA-RESULT = LSAA-AMOUNT * WSAA-RATE.
   > DISPLAY WSAA-FROM-CURR " " LSAA-AMOUNT " = "
   > WSAA-TO-CURR " " WSAA-RESULT.
   >
   > GO TO 1090-EXIT.
   >
   > 1050-ERROR.
   >
   > DISPLAY "!!!Error obtaining exchange rate!!!".
   >
   > 1090-EXIT.
   > EXIT PROGRAM.
   >
   > END PROGRAM EXAMPLE18.
   >
   > EXAMPLE18P
   >
   > IDENTIFICATION DIVISION.
   > PROGRAM-ID. EXAMPLE18P.
   > *
   > * Version 1.0 Mick O'Hea November 2007
   > *
   > * This is not a standalone program, but a module to be linked to
   > * EXAMPLE18. EXAMPLE18 will call a web service through HTTPAPI
   > * convert a currency amount. The API will parse the XML passed
   > * back from the web service, and call this module each time it
   > * finds the end of an element.
   > * If the element is the one we are interested in, we pass its
   > * value back by moving it to WSAA-RATE, which is defined as
   > * EXTERNAL both here and in EXAMPLE18, meaning that
   > * any value given to it here will be seen when control passes
   > * back to EXAMPLE18.
   > *
   > * Compile with:
   > * CRTCBLMOD MODULE(LIBHTTP/EXAMPLE18P) SRCFILE(LIBHTTP/QCBLLESRC)
   > * OPTION(*NOMONOPRC *NOSTDTRUNC) DBGVIEW(*LIST)
   > *
   > * Then link it with the EXAMPLE18 module (see comments there)
   > *
   > * The parameters defined here are those expected by HTTPAPI, so
   > * should not be changed. Any further information we need to pass
   > * back can be done by adding further EXTERNAL variables.
   > *
   > *
   > ENVIRONMENT DIVISION.
   > CONFIGURATION SECTION.
   > SOURCE-COMPUTER. IBM-AS400.
   > OBJECT-COMPUTER. IBM-AS400.
   > *
   > DATA DIVISION.
   > WORKING-STORAGE SECTION.
   > *
   > * I'm assuming here that the rate returned will be < 10000
   > * with a maximum of 5 decimal places
   >
   > 01 WSAA-RATE PIC 9(4)V9(5) EXTERNAL.
   > 01 WSAA-DIGIT PIC 9.
   > 01 WSAA-DIVISOR PIC 9(5).
   > 01 WSAA-INDEX PIC S9(4) COMP-3.
   >
   > LINKAGE SECTION.
   >
   > 01 LSAA-DUMMY pointer.
   > 01 LSAA-DEPTH-XML PIC S9(9) COMP-4.
   >
   > * Each of these will be a variable length parameter with the
   > * length in the first two bytes
   >
   > 01 LSAA-NAME.
   > 03 LSAA-NAME-LEN PIC S9(4) BINARY.
   > 03 LSAA-NAME-BODY PIC X(1024).
   > 01 LSAA-PATH.
   > 03 LSAA-PATH-LEN PIC S9(4) BINARY.
   > 03 LSAA-PATH-BODY PIC X(24576).
   > 01 LSAA-VALUE.
   > 03 LSAA-VALUE-LEN PIC S9(4) BINARY.
   > 03 LSAA-VALUE-BODY PIC X(32767).
   > 01 LSAA-ATTRS POINTER.
   > /
   > PROCEDURE DIVISION USING LSAA-DUMMY
   > LSAA-DEPTH-XML
   > LSAA-NAME
   > LSAA-PATH
   > LSAA-VALUE
   > LSAA-ATTRS.
   > *
   > * This is the section that will deal with the information
   > * returned from the web service.
   > * It will be called every time the XML parser reaches the end
   > * of an element.
   > * It will be passed the element name, path and value.
   > * As each of these is a variable length, possibly null, string,
   > * the length will be passed in the first two bytes of the
   > * parameter. Care must be taken to only use this much of the
   > * field, as data beyond the length is undefined and may cause
   > * an abend.
   >
   > *
   > /
   > 2000-INCOMING SECTION.
   > 2000-IN.
   >
   > * DISPLAY 'Name: ' LSAA-NAME-BODY(1:LSAA-NAME-LEN).
   > * if lsaa-value-len > 0
   > * DISPLAY 'Value: ' LSAA-VALUE-BODY(1:LSAA-VALUE-LEN).
   >
   > * If we have a name, and it's the right one, and we have a value,
   > * move the value to the output variable.
   >
   > IF LSAA-NAME-LEN > 0
   > IF LSAA-NAME-BODY(1:LSAA-NAME-LEN)
   > = "ConversionRateResult"
   >
   > * If the field is empty we need to pass back an error value
   > IF LSAA-VALUE-LEN = 0
   > MOVE -9999.99999 TO WSAA-RATE
   > ELSE
   > * We need to convert the character data 1234.56789 to 9(4)v9(5)
   > MOVE 0 TO WSAA-RATE
   > MOVE 1 TO WSAA-DIVISOR
   > PERFORM VARYING WSAA-INDEX FROM 1 BY 1
   > UNTIL WSAA-INDEX > LSAA-VALUE-LEN
   > OR LSAA-VALUE-BODY(WSAA-INDEX:1) = "."
   > MOVE LSAA-VALUE-BODY(WSAA-INDEX:1) TO WSAA-DIGIT
   > COMPUTE WSAA-RATE = WSAA-RATE * 10 + WSAA-DIGIT
   > END-PERFORM
   > * Now the decimal portion, if any
   > ADD 1 TO WSAA-INDEX
   > IF WSAA-INDEX < LSAA-VALUE-LEN
   > PERFORM VARYING WSAA-INDEX
   > FROM WSAA-INDEX BY 1
   > UNTIL WSAA-INDEX > LSAA-VALUE-LEN
   > OR LSAA-VALUE-BODY(WSAA-INDEX:1) = " "
   > MOVE LSAA-VALUE-BODY(WSAA-INDEX:1) TO WSAA-DIGIT
   > COMPUTE WSAA-DIVISOR= WSAA-DIVISOR * 10
   > COMPUTE WSAA-RATE = WSAA-RATE +
   > (WSAA-DIGIT / WSAA-DIVISOR)
   > END-PERFORM
   > END-IF
   >
   > *** If we were just dealing with a text field we could extract
   > *** it easily:
   > *** MOVE LSAA-VALUE-BODY(1:LSAA-VALUE-LEN)
   > *** TO WSAA-VALID-BANK-DETAILS
   > END-IF
   > END-IF
   > END-IF.
   >
   > 2090-EXIT.
   > EXIT PROGRAM.
   >
   > END PROGRAM EXAMPLE18P.
   >
   >
   ----------------------------------------------------------------------
   -
   > This is the FTPAPI mailing list. To unsubscribe, please go to:
   > http://www.scottklement.com/mailman/listinfo/ftpapi
   >
   ----------------------------------------------------------------------
   -
   >
   >
   >
   >
   ----------------------------------------------------------------------
   -
   > This is the FTPAPI mailing list. To unsubscribe, please go to:
   > http://www.scottklement.com/mailman/listinfo/ftpapi
   >
   ----------------------------------------------------------------------
   -
   >
   ----------------------------------------------------------------------
   -
   This is the FTPAPI mailing list. To unsubscribe, please go to:
   http://www.scottklement.com/mailman/listinfo/ftpapi
   ----------------------------------------------------------------------
   -
   ----------------------------------------------------------------------
   -
   This is the FTPAPI mailing list. To unsubscribe, please go to:
   http://www.scottklement.com/mailman/listinfo/ftpapi
   ----------------------------------------------------------------------
   -
-----------------------------------------------------------------------
This is the FTPAPI mailing list.  To unsubscribe, please go to:
http://www.scottklement.com/mailman/listinfo/ftpapi
-----------------------------------------------------------------------