ASG
IBM
Zystems
Cressida
Icon
Netflexity
 
  MQSeries.net
Search  Search       Tech Exchange      Education      Certifications      Library      Info Center      SupportPacs      LinkedIn  Search  Search                                                                   FAQ  FAQ   Usergroups  Usergroups
 
Register  ::  Log in Log in to check your private messages
 
RSS Feed - WebSphere MQ Support RSS Feed - Message Broker Support

MQSeries.net Forum Index » IBM MQ API Support » Problem using MQCONNX COBOL OPENVMS MQClient

Post new topic  Reply to topic
 Problem using MQCONNX COBOL OPENVMS MQClient « View previous topic :: View next topic » 
Author Message
biker30
PostPosted: Thu Dec 21, 2006 9:39 am    Post subject: Problem using MQCONNX COBOL OPENVMS MQClient Reply with quote

Newbie

Joined: 23 May 2006
Posts: 7
Location: Chile

Hello:

I need some help with using MQCONNX in COBOL language, principally with set structure MQCNO-CLIENTCONNOFFSET.

how set this structure?
I search for sample MQCONNX in manual programming guide with COBOL but without result.

if set environment variable MQSERVER with values connection the same of the code, this program read message of a queue.

please helpme, thanks!

attached extract of code and copy structure of OPENVMS:
Code:

**extract of WORKING-STORAGE SECTION.****************
      ** Options that control the action of MQCONNX
       01 CONEXION.
          05 CONNECTOPTS.
             COPY "MQS_INCLUDE:CMQCNOV".
          05 CANAL.
             COPY "MQS_INCLUDE:CMQCDV".
             
**extract of PROCEDURE DIVISION.*********************

           MOVE "MY.QM" TO QM-NAME.
           MOVE "SYSTEM.ADMIN.SVRCONN" TO MQCD-CHANNELNAME.
           MOVE "127.0.0.1" TO MQCD-CONNECTIONNAME.
           
           MOVE 0 TO MQCNO-CLIENTCONNOFFSET.
         
           CALL 'MQCONNX' USING QM-NAME, CONNECTOPTS, HCONN,
                 COMPLETION-CODE, CON-REASON.           

      *      report reason and stop if it failed
           IF COMPLETION-CODE IS EQUAL TO MQCC-FAILED
             DISPLAY 'MQCONN ended with reason code '  CON-REASON
             MOVE CON-REASON TO RETURN-CODE
             STOP RUN
             END-IF.
***end of extract*******************************

***COPY  extract CMQCNOV *******************************
 
       **   MQCNO structure
         10 MQCNO.
       **    Structure identifier
          15 MQCNO-STRUCID          PIC X(4) VALUE 'CNO '.
       **    Structure version number
          15 MQCNO-VERSION          PIC S9(9) BINARY VALUE 1.
       **    Options that control the action of MQCONNX
          15 MQCNO-OPTIONS          PIC S9(9) BINARY VALUE 0.
       **    Offset of MQCD structure for client connection
          15 MQCNO-CLIENTCONNOFFSET PIC S9(9) BINARY VALUE 0.
       **    Address of MQCD structure for client connection
          15 MQCNO-CLIENTCONNPTR    POINTER VALUE 0.
***COPY end of extract*******************************



Greetings and Merry Christmas!!!
_________________
_____________
Back to top
View user's profile Send private message
wschutz
PostPosted: Thu Dec 21, 2006 10:15 am    Post subject: Reply with quote

Jedi Knight

Joined: 02 Jun 2005
Posts: 3316
Location: IBM (retired)

Quote:
ClientConnOffset (MQLONG)

This is the offset in bytes of an MQCD channel definition structure from the start of the MQCNO structure. The offset can be positive or negative.

Use ClientConnOffset only when the application issuing the MQCONNX call is running as a WebSphere MQ client. For information on how to use this field, see the description of the ClientConnPtr field.

This is an input field. The initial value of this field is 0. This field is ignored if Version is less than MQCNO_VERSION_2.

I've highlighted the two things that are important here.
_________________
-wayne
Back to top
View user's profile Send private message Send e-mail AIM Address
biker30
PostPosted: Thu Dec 21, 2006 12:33 pm    Post subject: Reply with quote

Newbie

Joined: 23 May 2006
Posts: 7
Location: Chile

Indeed we have reviewed the Application Programming Guide of MQ and we already checked the sent extract of the ClientConnOffset, with the emphasized two points.

But then, which would to be value of offset for this Cobol code?.

We have test values from the 1 to the 26, and compiles but when executing it gives an error of violation of memory at level of SO.

Somebody will have an example of setting the parameters for the structures of the MQCONNX for COBOL to validate?
_________________
_____________
Back to top
View user's profile Send private message
tleichen
PostPosted: Thu Dec 21, 2006 1:11 pm    Post subject: Reply with quote

Yatiri

Joined: 11 Apr 2005
Posts: 663
Location: Center of the USA

Not sure what the rest of your code is like, but I'm not sure where you're defining your MQCD structure, nor are you populating the MQCNO-CLIENTCONNPTR.
_________________
IBM Certified MQSeries Specialist
IBM Certified MQSeries Developer
Back to top
View user's profile Send private message
biker30
PostPosted: Thu Dec 21, 2006 1:53 pm    Post subject: Reply with quote

Newbie

Joined: 23 May 2006
Posts: 7
Location: Chile

I can copy all the code, you need it?
_________________
_____________
Back to top
View user's profile Send private message
wschutz
PostPosted: Thu Dec 21, 2006 3:46 pm    Post subject: Reply with quote

Jedi Knight

Joined: 02 Jun 2005
Posts: 3316
Location: IBM (retired)

You should use LENGTH OF on CONNECTOPTS to set the offset.
Show us the entire code please.
_________________
-wayne
Back to top
View user's profile Send private message Send e-mail AIM Address
biker30
PostPosted: Fri Dec 22, 2006 10:56 am    Post subject: Reply with quote

Newbie

Joined: 23 May 2006
Posts: 7
Location: Chile

wayne,
thanks for its answer, I added the code function LENGTH, but persist the problem. I send the entire code and error when executing the program:

Code:
       IDENTIFICATION DIVISION.
       PROGRAM-ID. AMQ0GBR0.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
      **  Declare MQI structures needed
      * MQI named constants
       01 MY-MQ-CONSTANTS.
           COPY "MQS_INCLUDE:CMQV".
      * Object Descriptor
       01 OBJECT-DESCRIPTOR.
          COPY "MQS_INCLUDE:CMQODV".
      * Message Descriptor
       01 MESSAGE-DESCRIPTOR.
          COPY "MQS_INCLUDE:CMQMDV".
      * Get message options
       01 GMOPTIONS.
          COPY "MQS_INCLUDE:CMQGMOV".
      ** note, sample uses defaults where it can
       01 QM-NAME                    PIC X(48) VALUE SPACES.
       01 HCONN                      PIC S9(9) BINARY.
       01 Q-HANDLE                   PIC S9(9) BINARY.
       01 OPTIONS                    PIC S9(9) BINARY.
       01 COMPLETION-CODE            PIC S9(9) BINARY.
       01 OPEN-CODE                  PIC S9(9) BINARY.
       01 CON-REASON                 PIC S9(9) BINARY.
       01 REASON                     PIC S9(9) BINARY.
       01 BUFFER                     PIC X(60).
       01 BUFFER-LENGTH              PIC S9(9) BINARY.
       01 DATA-LENGTH                PIC S9(9) BINARY.
       01 MSG-COUNT                  PIC 9999.
       01 TARGET-QUEUE               PIC X(48).
       
      ** Options that control the action of MQCONNX
       01 CONEXION.
          05 CONNECTOPTS.
             COPY "MQS_INCLUDE:CMQCNOV".
          05 CANAL.
             COPY "MQS_INCLUDE:CMQCDV".

       PROCEDURE DIVISION.
       P0.
           
           MOVE "MY.QM" TO QM-NAME.
           MOVE "SYSTEM.ADMIN.SVRCONN" TO MQCD-CHANNELNAME.
           MOVE "127.0.0.1" TO MQCD-CONNECTIONNAME.

           MOVE FUNCTION LENGTH(CONNECTOPTS) TO MQCNO-CLIENTCONNOFFSET.

           move 2 to MQCNO-VERSION.
           
           CALL 'MQCONNX' USING QM-NAME, CONNECTOPTS, HCONN,
                 COMPLETION-CODE, CON-REASON.           

      *      report reason and stop if it failed
           IF COMPLETION-CODE IS EQUAL TO MQCC-FAILED
             DISPLAY 'MQCONN ended with reason code '
             DISPLAY CON-REASON
             MOVE CON-REASON TO RETURN-CODE
             STOP RUN
             END-IF.
       OPENS.
           MOVE "TEST.IN" TO TARGET-QUEUE.
           MOVE TARGET-QUEUE TO MQOD-OBJECTNAME.
           ADD MQOO-BROWSE MQOO-FAIL-IF-QUIESCING
                     GIVING OPTIONS.
           CALL 'MQOPEN'
            USING HCONN, OBJECT-DESCRIPTOR,
            OPTIONS, Q-HANDLE,
            OPEN-CODE, REASON.

      *      report reason, if any; stop if failed
           IF REASON IS NOT EQUAL TO MQRC-NONE
             DISPLAY 'MQOPEN ended with reason code ' REASON
             END-IF.

           IF OPEN-CODE IS EQUAL TO MQCC-FAILED
             DISPLAY 'unable to open server queue for output'
             MOVE REASON TO RETURN-CODE
             STOP RUN
             END-IF.
       GETS.
           MOVE OPEN-CODE TO COMPLETION-CODE.
           MOVE 0 TO MSG-COUNT.
           PERFORM GETR THRU DISPR WITH TEST BEFORE
             UNTIL COMPLETION-CODE IS EQUAL TO MQCC-FAILED.

       CLOSES.
           MOVE MQCO-NONE TO OPTIONS.
           CALL 'MQCLOSE'
            USING HCONN, Q-HANDLE, OPTIONS,
            COMPLETION-CODE, REASON.

      *      report reason, if any
           IF REASON IS NOT EQUAL TO MQRC-NONE
             DISPLAY 'MQCLOSE ended with reason code ' REASON
             END-IF.
       DISCS.
           IF CON-REASON IS NOT EQUAL TO MQRC-ALREADY-CONNECTED
             CALL 'MQDISC'
              USING HCONN, COMPLETION-CODE, REASON

      *      report reason, if any
             IF REASON IS NOT EQUAL TO MQRC-NONE
               DISPLAY 'MQDISC ended with reason code ' REASON
             END-IF
           END-IF.

       OVER.
      ** indicate that sample program has finished
           DISPLAY 'AMQ0GBR0 end'.
           MOVE ZERO TO RETURN-CODE.
           STOP RUN.
       GETR.
           MOVE MQMI-NONE TO MQMD-MSGID.
           MOVE MQCI-NONE TO MQMD-CORRELID.
           MOVE SPACES TO BUFFER.
           ADD MQGMO-NO-WAIT MQGMO-BROWSE-NEXT
               MQGMO-ACCEPT-TRUNCATED-MSG
                     GIVING MQGMO-OPTIONS.
           MOVE 15000 TO MQGMO-WAITINTERVAL.
           MOVE 60 to BUFFER-LENGTH.

           CALL 'MQGET'
            USING HCONN, Q-HANDLE,
            MESSAGE-DESCRIPTOR, GMOPTIONS,
            BUFFER-LENGTH, BUFFER, DATA-LENGTH,
            COMPLETION-CODE, REASON.
       DISPM.
           IF COMPLETION-CODE IS NOT EQUAL TO MQCC-FAILED
             IF MSG-COUNT IS EQUAL TO 0
               DISPLAY 'Messages in ' MQGMO-RESOLVEDQNAME
             END-IF
             ADD 1 TO MSG-COUNT
             DISPLAY MSG-COUNT ' <' BUFFER '>'
           END-IF.
       DISPR.
           IF REASON IS NOT EQUAL TO MQRC-NONE
             IF REASON IS EQUAL TO MQRC-NO-MSG-AVAILABLE
               DISPLAY 'no more messages'
             ELSE
               IF DATA-LENGTH IS GREATER THAN BUFFER-LENGTH
                 DISPLAY '   --- truncated'
               ELSE
                 DISPLAY 'MQGET ended with reason code ' REASON
               END-IF
             END-IF
           END-IF.



view dum error of run process.

Quote:


SERVER_MQ]> runMQCONNX.EXE

%SYSTEM-F-ACCVIO, accessviolation, reason mask=00, virtual address=FFFFFFFFFFFFFFFF,PC=0000000000092044, PS=0000001B

%TRACE-F-TRACEBACK, symbolicstack dump follows

image module routine line rel PC abs PC

MQICB AMQZSJBX MQCLOSE 263 0000000000000044 0000000000092044

MQICB AMQRMSSA rriFreeSess 76427 0000000000001F9C 00000000000A5FDC

MQICB AMQRREQA DoConnect 70308 0000000000000EDC 000000000009321C

MQCONNX AMQ0GBR0 AMQ0GBR0 2003 00000000000000E4 00000000000300E4

MQCONNX 0 0000000000030AC0 0000000000030AC0

PTHREAD$RTL 0 0000000000055D58 000000007BD23D58

PTHREAD$RTL 0 0000000000030404 000000007BCFE404

0FFFFFFFF80269ED4 FFFFFFFF80269ED4

_________________
_____________
Back to top
View user's profile Send private message
biker30
PostPosted: Fri Dec 29, 2006 9:21 am    Post subject: Reply with quote

Newbie

Joined: 23 May 2006
Posts: 7
Location: Chile

hi all,

perhaps it is a problem or "bugs" of the MQ API for Cobol?

So can you help me for this problem.
Thanks in Advance
_________________
_____________
Back to top
View user's profile Send private message
wdunnahoo
PostPosted: Fri Mar 16, 2007 5:40 am    Post subject: Reply with quote

Newbie

Joined: 14 Mar 2007
Posts: 1
Location: Dallas, TX

I'm having some of the same problems. Did anyone come up with a way handle this?

Also, I can't seem to tell if my program is actually sending out packets. On the MXCONNX, I get error 2058 or 2059.

I'm working with MQ Client 5.3 on OpenVMS trying to communicate with Severs on Windows XP and IBM MVX mainframe. I developing on OpenVMS is 7.3-2 using HP's TCP/IP stack. I'm new to Websphere and have been given the job of getting MQ implemented by April (!), using TCPIP. I'm using HP COBOL on an Alpha machine.

Thanks
Back to top
View user's profile Send private message
Vitor
PostPosted: Fri Mar 16, 2007 6:09 am    Post subject: Reply with quote

Grand High Poobah

Joined: 11 Nov 2005
Posts: 26093
Location: Texas, USA

wdunnahoo wrote:
Also, I can't seem to tell if my program is actually sending out packets. On the MXCONNX, I get error 2058 or 2059.


Are you able to achieve a connection with amqsputc? It may be a problem with the client definition rather than your code & you should eliminate this possibility.

(And MQ applications don't send packets, they send messages. That's sort of the point of the software).

wdunnahoo wrote:
I'm new to Websphere and have been given the job of getting MQ implemented by April (!), using TCPIP.


You've got your work cut out for you!

I trust you've been given copious training to prepare you for this task...
_________________
Honesty is the best policy.
Insanity is the best defence.
Back to top
View user's profile Send private message
Vitor
PostPosted: Fri Mar 16, 2007 6:13 am    Post subject: Reply with quote

Grand High Poobah

Joined: 11 Nov 2005
Posts: 26093
Location: Texas, USA

Before someone else clarifies me:

2058 errors probably are an error in the program - queue name misspelt or in the wrong case (all MQ object names are case sensitive).

2059 errors can come from a wide variety of sources many of which are not code related. A search of this forum (see top right of this page) for 2059 will yield a number of discussions, possible causes and potential solutions.

Try the utility & see what you get.
_________________
Honesty is the best policy.
Insanity is the best defence.
Back to top
View user's profile Send private message
kevinf2349
PostPosted: Fri Mar 16, 2007 6:49 pm    Post subject: Reply with quote

Grand Master

Joined: 28 Feb 2003
Posts: 1311
Location: USA

Quote:
I'm working with MQ Client 5.3 on OpenVMS trying to communicate with Severs on Windows XP and IBM MVX mainframe.


If you mean MVS you had better check that you have CAF installed on MVS or it ain't happening (to MVS)...ever.
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic  Reply to topic Page 1 of 1

MQSeries.net Forum Index » IBM MQ API Support » Problem using MQCONNX COBOL OPENVMS MQClient
Jump to:  



You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum
Protected by Anti-Spam ACP
 
 


Theme by Dustin Baccetti
Powered by phpBB © 2001, 2002 phpBB Group

Copyright © MQSeries.net. All rights reserved.