MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

CICS linkage section problem

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> CICS and Middleware
View previous topic :: View next topic  
Author Message
enge
Beginner


Joined: 12 Oct 2004
Posts: 78
Topics: 39

PostPosted: Tue Mar 06, 2007 11:27 am    Post subject: CICS linkage section problem Reply with quote

friends,


calling program,
Code:

01 A0RTPROF-AREA.                         
    03 A0RTPROF-USER-BYTE       PIC  X(01).
    03 FILLER                   PIC  X(20).
    03 A0RTPROF-USER-ID         PIC  X(08).
    03 FILLER                   PIC  X(01).
    03 A0RTPROF-USER-PROFILE    PIC  X(08).

.
.
.
MOVE '$'                    TO A0RTPROF-USER-BYTE.
EXEC CICS LINK PROGRAM (A0RTPROF)                 
               COMMAREA(A0RTPROF-AREA)           
               LENGTH  (LENGTH OF A0RTPROF-AREA) 
END-EXEC.                                         


called program:
LINKAGE SECTION.                               
   01 DFHCOMMAREA.                             
      02 ACEE-AREA.                             
         03 FILLER                 PIC  X(21). 
         03 ACEE-USER-ID           PIC  X(08). 
         03 FILLER                 PIC  X(01). 
         03 ACEE-USER-PROFILE      PIC  X(08). 
.
.
EXEC CICS ADDRESS ACEE(ADDRESS OF DFHCOMMAREA)
END-EXEC.                                     
.
.

my problem is:
in the called program i see acee-user-id, acee-user-profile vars but when return at calling program commarea is always "$............................"

why?
thank in advance
Back to top
View user's profile Send private message
dbzTHEdinosauer
Supermod


Joined: 20 Oct 2006
Posts: 1411
Topics: 26
Location: germany

PostPosted: Tue Mar 06, 2007 12:17 pm    Post subject: Reply with quote

1. this should have been posted in the CICS forum.

2. you only moved data to only one field
Quote:
MOVE '$' TO A0RTPROF-USER-BYTE


in the CALLING pgm. What do you expect? Nothing was populated to the other fields. Are you saying that you populated these fields in the LINKAGE SECTION of the CALLed pgm and can not see the results in the CALLing pgm?
_________________
Dick Brenholtz
American living in Varel, Germany
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12378
Topics: 75
Location: San Jose

PostPosted: Tue Mar 06, 2007 12:34 pm    Post subject: Reply with quote

enge,

Did you know CICS translator inserts the dfheiblk for DFHCOMMAREA?

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
enge
Beginner


Joined: 12 Oct 2004
Posts: 78
Topics: 39

PostPosted: Wed Mar 07, 2007 4:06 am    Post subject: Reply with quote

i expected in calling program "$ DONALDbb DUCKbbbb " where DONALD string and DUCK string has been assigned by EXEC CICS ADDRESS statement.
in called program ,infact ,you see these values with CEDF.
below cics translator:
Code:

01   dfhc0650  pic x(65) is global.                 
01   dfhc0030  pic x(3) is global.                 
01   dfhdummy comp pic s9(4) value zero is global. 
01   dfheiv0  pic x(77) is global.                 
LINKAGE SECTION.                                   
01  dfheiblk.                                       
02    eibtime  comp-3 pic s9(7).                   
02    eibdate  comp-3 pic s9(7).                   
02    eibtrnid pic x(4).                           
02    eibtaskn comp-3 pic s9(7).                   
02    eibtrmid pic x(4).                           
02    dfheigdi comp pic s9(4).                     
02    eibcposn comp pic s9(4).                     
02    eibcalen comp pic s9(4).                     
02    eibaid   pic x(1).                           
02    eibfn    pic x(2).                           
02    eibrcode pic x(6).                           
02    eibds    pic x(8).                           
02    eibreqid pic x(8).                           
02    eibrsrce pic x(8).             
02    eibsync  pic x(1).             
02    eibfree  pic x(1).             
02    eibrecv  pic x(1).             
02    eibfil01 pic x(1).             
02    eibatt   pic x(1).             
02    eibeoc   pic x(1).             
02    eibfmh   pic x(1).             
02    eibcompl pic x(1).             
02    eibsig   pic x(1).             
02    eibconf  pic x(1).             
02    eiberr   pic x(1).             
02    eiberrcd pic x(4).             
02    eibsynrb pic x(1).             
02    eibnodat pic x(1).             
02    eibresp  comp pic s9(8).       
02    eibresp2 comp pic s9(8).       
02    eibrldbk pic x(1).             
   01 DFHCOMMAREA.                   
        02 ACEE-AREA.                             
           03 FILLER                 PIC  X(21). 
           03 ACEE-USER-ID           PIC  X(08). 
           03 FILLER                 PIC  X(01). 
           03 ACEE-USER-PROFILE      PIC  X(08). 
 * +----------------------------------------------
 * +  PROCEDURE DIVISION                         
 * +----------------------------------------------
  PROCEDURE DIVISION using dfheiblk dfhcommarea. 
  DSNSQL SECTION.                                 
  SQL-SKIP.                                       
rise COBOL for z/OS  3.3.1               A0RTPROF
-*A-1-B--+----2----+----3----+----4----+----5----+
      GO TO SQL-INIT-END.                         
  SQL-INITIAL.                                   
 

W Code from "procedure name SQL-INITIAL" to "MOVE
be executed and was therefore discarded.
Back to top
View user's profile Send private message
enge
Beginner


Joined: 12 Oct 2004
Posts: 78
Topics: 39

PostPosted: Wed Mar 07, 2007 7:01 am    Post subject: Reply with quote

eureka!
Code:

LINKAGE SECTION.                               
   01 DFHCOMMAREA               PIC  X(38).   
   01 FILLER REDEFINES DFHCOMMAREA.           
      03 COMM-BYTE              PIC  X(01).   
      03 FILLER                 PIC  X(20).   
      03 COMM-USER-ID           PIC  X(08).   
      03 FILLER                 PIC  X(01).   
      03 COMM-USER-PROFILE      PIC  X(08).   
   01 ACEE-AREA.                               
      03 FILLER                 PIC  X(21).   
      03 ACEE-USER-ID           PIC  X(08).   
      03 FILLER                 PIC  X(01).   
      03 ACEE-USER-PROFILE      PIC  X(08).   

and
MOVE ACEE-USER-ID           TO COMM-USER-ID       
MOVE ACEE-USER-PROFILE      TO COMM-USER-PROFILE 

thanks a lot!
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> CICS and Middleware All times are GMT - 5 Hours
Page 1 of 1

 
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


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group