Why is my commarea's variable changing without reason?

100 views Asked by At

While coding an other program I was getting strange errors so I have wrote below code to see how my COMMAREA variable is changing. The intent of this program is to display var1 content and see if the value is the same:

       IDENTIFICATION DIVISION.                                
       PROGRAM-ID. MAPBROW2.                                   
       DATA DIVISION.                                          
       WORKING-STORAGE SECTION.                                
       COPY MAPBROW.                                           
       COPY DFHAID.                                            
       01 WS-COMMAREA.                                         
           05 VAR1 PIC X(15).                                  
       01 RESPCODE PIC S9(8) COMP.                             
       01 EXIT-MSG PIC X(10) VALUE 'NORMAL END'.               
       PROCEDURE DIVISION.                                     
       MAIN.                                                   
           IF EIBCALEN = 0 THEN                                
                MOVE LOW-VALUES TO MAP1O                            
                MOVE 'ABCD1234' TO VAR1                             
                MOVE VAR1 TO MSGO                                   
                PERFORM SEND-THE-MAP                 
           ELSE                                                      
               EVALUATE EIBAID                                       
               WHEN DFHENTER                                         
                    PERFORM SEND-VAR1                              
               WHEN DFHPF1                                           
                    PERFORM CLEAR-THE-MAP                            
               WHEN DFHPF3                                           
                    EXEC CICS                                        
                    SEND TEXT FROM(EXIT-MSG)                         
                    ERASE                                            
                    END-EXEC                                         
                    EXEC CICS RETURN END-EXEC                        
               WHEN OTHER                                            
                    MOVE 'INVALID KEY' TO MSGO                       
                    PERFORM SEND-THE-MAP                             
               END-EVALUATE                                          
           END-IF    
           EXEC CICS                                            
           RETURN TRANSID('TRN3') COMMAREA(WS-COMMAREA)         
           END-EXEC.                                            
       SEND-THE-MAP.                                            
           EXEC CICS                                            
           SEND MAP('MAP1') MAPSET('MAPBROW')                   
           ERASE                                                
           NOHANDLE                                             
           END-EXEC                                             
           EXIT.                                                
       SEND-VAR1.                                             
           MOVE LOW-VALUES TO MAP1O                             
           MOVE VAR1 TO MSGO                                    
           PERFORM SEND-THE-MAP                                 
           EXIT.                                                
       CLEAR-THE-MAP.                                           
           MOVE LOW-VALUES TO MAP1O       
           PERFORM SEND-THE-MAP         
           EXIT.                                              
                                                

The output if EIBCALEN = 0 is as should be 'ABCD1234' but later after pressing enter 'NDONIEC@ RMALN'

I am still learning and i wasn't able to find the solution myself, I am feeling like I missing something. What is wrong in that program?

Thanks in advance.

1

There are 1 answers

0
cschneid On BEST ANSWER

This is a pseudo-conversational CICS program, so...

your transaction begins for the first time

the initial program is invoked with a pointer to DFHEIBLK, a structure for which is automatically inserted into your Linkage Section by the CICS pre-compiler or the CICS co-processor

memory for Working-Storage is allocated

the program code begins executing, including code inserted by the compiler to make all your Working-Storage VALUE clauses true

since this is the first time in, EIBCALEN = 0 and 'ABCD1234' is moved into VAR1, VAR1 is moved into MSGO, the map is sent, and there is a RETURN to CICS with WS-COMMAREA and your tranID

the memory for Working-storage is freed

CICS remembers the contents of your commarea for you

DFHENTER is pressed

your transaction begins but CICS knows it is not for the first time

the initial program is invoked with a pointer to DFHEIBLK and a pointer to your commarea

memory for Working-Storage is allocated

the program code begins executing, including code inserted by the compiler to make all your Working-Storage VALUE clauses true

since this is not the first time in, EIBCALEN = 15 (the length of WS-COMMAREA), EIBAID is EVALUATEd to be DFHENTER so paragraph SEND-VAR1 is PERFORMED, the contents of VAR1 (which at this point is uninitialized storage) is moved to MSGO, the map is sent, and there is a RETURN to CICS with WS-COMMAREA and your tranID

the memory for Working-storage is freed

CICS remembers the contents of your commarea for you

...I think what you want is to code...

[...same as you have coded...]
Linkage Section.
01  DFHCOMMAREA.
    05  CA-VAR1 PIC X(15).
Procedure Division Using DFHCOMMAREA.
MAIN.                                                   
    IF EIBCALEN = 0 THEN                                
        MOVE LOW-VALUES TO MAP1O                            
        MOVE 'ABCD1234' TO VAR1                             
        MOVE VAR1 TO MSGO                                   
        PERFORM SEND-THE-MAP
        EXEC CICS
             RETURN
             TRANSID(EIBTRNID)
             COMMAREA(WS-COMMAREA)
        END-EXEC                 
    ELSE                                                      
        MOVE DFHCOMMAREA to WS-COMMAREA
        [...same as you have coded...]
    END-IF
    MOVE WS-COMMAREA TO DFHCOMMAREA
    EXEC CICS
         RETURN
         TRANSID(EIBTRNID)
         COMMAREA(DFHCOMMAREA)
    END-EXEC.
[...same as you have coded...]

...which, on second and subsequent invocations, will restore your WS-COMMAREA from the commarea CICS remembered for you because when CICS starts your program it does so with two pointers, one to DFHEIBLK (the Execute Interface Block) and one to your commarea.

First time in there is no commarea, so DFHCOMMAREA doesn't have any memory allocated for it. On subsequent invocations of your program there is a commarea because when you RETURN to CICS the first time you do so with a commarea and CICS remembers that for you in memory it allocates.

Second and subsequent times you RETURN to CICS you do so with a commarea pointing to memory in your Linkage Section, but that was initially allocated for you by CICS on your first invocation.

One important thing to remember here is that items in the Linkage Section must have memory allocated for them. In the case of DFHEIBLK, CICS does that for you. In the case of DFHCOMMAREA, that happens because you did your first RETURN to CICS with a commarea and that was copied into memory which was allocated for you by CICS.