Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

GETTING RID OF BLL-CELS AND SERVICE RELOAD 1

Status
Not open for further replies.

OGOROD

Programmer
Jun 6, 2005
3
0
0
US
I am converting CICS pgm's to cobol II in order to migrate from cics\vse 2.3 to cics\vse 2.7.

eventhough i replace bll-cells with pointers and use set address of command, i am getting ASRA in two places: MOVE 'P' TO PCICSS(defined as alphanum in linkage section);
move EIBDATE to CWAYYDDD(linkage section item fld).

OLD CODE

LINKAGE SECTION.
01 DFHCOMMAREA PIC X(04).
01 BLL-CELLS.
05 FILLER PIC S9(08) COMP.
05 CSSCWABR PIC S9(08) COMP.
05 CSSTWABR PIC S9(08) COMP.
05 CSSPCIBR PIC S9(08) COMP.
05 CSSTFLBR PIC S9(08) COMP.
COPY CSCCWARC.
EJECT
COPY CSCTWARC.
EJECT
COPY CSCPCIRC.
EJECT
COPY CSCTFLRC.
PROCEDURE DIVISION.

SERVICE RELOAD BLL-CELLS.
EXEC CICS ADDRESS
CWA (CSSCWABR)
TWA (CSSTWABR)
END-EXEC.
SERVICE RELOAD CWA-AREA.
SERVICE RELOAD TWA-AREA.

*SET CWAYYDDD IN CASE 1ST SIGNON AND MAP DISPLAY
IF CWAYYDDD NOT NUMERIC
MOVE EIBDATE TO CWAYYDDD.

EXEC CICS
GETMAIN
LENGTH (GBL-PCI-LENGTH)
SET (CSSPCIBR)
INITIMG (GBL-BINARY-00)
END-EXEC.
SERVICE RELOAD PCI.
IF WSRD-TRAN = 'PURC'
MOVE 'P' TO PCICSS
MOVE 'PURC' TO WS-TRANCODE.

new code
LINKAGE SECTION.
77 CSSCWABR USAGE IS POINTER.
77 CSSTWABR USAGE IS POINTER.
77 CSSPCIBR USAGE IS POINTER.
77 CSSTFLBR USAGE IS POINTER.
COPY CSCCWARC.
EJECT
COPY CSCTWARC.
EJECT
COPY CSCPCIRC.
EJECT
COPY CSCTFLRC.
PROCEDURE DIVISION.

SET ADDRESS OF TWA-AREA TO CSSTWABR.
SET ADDRESS OF CWA-AREA TO CSSCWABR.
SET ADDRESS OF T-TFL TO CSSTFLBR.
SET ADDRESS OF PCI TO CSSPCIBR.

EXEC CICS ADDRESS
CWA (ADDRESS OF CSSCWABR)
TWA (ADDRESS OF CSSTWABR)
END-EXEC.

SET ADDRESS OF TWA-AREA TO CSSTWABR.
SET ADDRESS OF CWA-AREA TO CSSCWABR.

*SET CWAYYDDD IN CASE 1ST SIGNON AND MAP DISPLAY
IF CWAYYDDD NOT NUMERIC
MOVE EIBDATE TO CWAYYDDD.

EXEC CICS
GETMAIN
LENGTH (GBL-PCI-LENGTH)
SET (ADDRESS OF CSSPCIBR)
INITIMG (GBL-BINARY-00)
END-EXEC.
SET ADDRESS OF PCI TO CSSPCIBR.

IF WSRD-TRAN = 'PURC'
MOVE 'P' TO PCICSS
MOVE 'PURC' TO WS-TRANCODE.

What am i missing? And this only one out of 100+ pgms that require changes.
 
Haven't used VSE since 1988, but the principles are the same. When a CICS program gets called, it is (normally) passed a parameter list of DFHEIBLK and DFHCOMMAREA. Imagine CALL myprog USING DFHEIBLK DFHCOMMAREA. So these have to be first in your linkage section. Note that most programs don't specify DFHEIBLK as it gets inserted by the translator.

These parameters get mapped by COBOL onto 01 or 77 levels in your linkage section. In the same order. So the translator will insert the entry for DFHEIBLK (the EIB), and the next thing in your linkage section should be DFHCOMMAREA.

Any subsequent 01 or 77 levels in your linkage section are just DSECTs, and won't be mapped to any storage unless you do it yourself. In your second example, the ADDRESS of the four byte pointer CSSCWABR is being set to the addrees of the COMMAREA. And the rest of the 77 levels don't map to anything. So for example, we can map the CWA with
Code:
EXEC CICS ADDRESS CWA(ADDRESS OF CSCCWARC) END-EXEC
assuming that the 01-level in the CSCCWARC copybook is actually called CSCCWARC - if not, change the ADDRESS OF CSCCWARC to something else. Once we have done this, any reference to fileds in the CSCCWARC copybook will actually affect the real CICS CWA.

Similarly, your GETMAIN example
Code:
EXEC CICS                                  
          GETMAIN                          
          LENGTH (GBL-PCI-LENGTH)          
          SET (CSSPCIBR)                   
          INITIMG (GBL-BINARY-00)          
          END-EXEC.
can be changed to
Code:
EXEC CICS                                  
          GETMAIN                          
          FLENGTH (LENGTH OF [i]pci-01-level[/i])          
          SET (ADDRESS OF [i]pci-01-level[/i])                            
          INITIMG (X'00')          
          END-EXEC
Note that we can get rid of the global constant values, and replace them with the COBOL2 LENGTH OF statement, and use the hexadecimal constant facilities too. Note that LENGTH OF returns a fullword, hence the FLENGTH rather than LENGTH.

In summary, then, you only get automatic addressability to the EIB and COMMAREA. Everything else, it's up to you to map it to a piece of real storage, either by getting its address from somewhere, or GETMAINing it for yourself.

Does this help at all?
 
thanks stevexff for input.

i used your suggestions. i am getting IGYSC2025-W for addressing CWA and TWA ponters while compiling:
IGYSC2025-W "CSSCWABR" or one of its subordinates was referenced, but "CSSCWABR" was a "LINKAGE SECTION" item that did not have addressability. This reference will not be resolved successfully at execution. Same for "CSSTWABR".
i think this is the main reason pgm abends with ASRA at execution.

Also when i code 1010-GETMAIN-PCI.
EXEC CICS
GETMAIN
FLENGTH (LENGHT OF PCI)
SET (ADDRESS OF PCI)
INITIMG (GBL-BINARY-00)
END-EXEC.
SET ADDRESS OF PCI TO CSSPCIBR
I get IGYPS2121-S "LENGHT OF PCI" WAS NOT DEFINED AS A DATA-NAME. THE STATEMENT WAS DISCARDED.

i belive LENGHT OF is defined implicitly under the CALL stmt in COBOL II.
what else could be missing? some additional cbl compiler options?
 
That's partly because LENGHT is normally spelled LENGTH, and partly because the 77 levels in your code don't map to any real storage.

VSCOBOL used BLL (base locator for linkage) cells to provide addressability to linkage. COBOL2/COBOL370 uses what are called special registers, i.e. ADDRESS OF something. You don't have to reserve space for them in your linkage section like the old BLL cells. In VSCOBOL you had to put the address of the CWA into the BLL cell, and the SERVICE RELOAD to make COBOL re-map CWA-AREA to the new address. Under COBOL2, just using SET ADDRESS OF CWA-AREA performs both steps. So
Code:
LINKAGE SECTION.
01 DFHCOMMAREA PIC X(4)          [red]from old code[/red] 
       COPY CSCCWARC.
EJECT         
COPY CSCTWARC.
EJECT         
COPY CSCPCIRC.
EJECT         
COPY CSCTFLRC.
PROCEDURE DIVISION. [red](using DFHEIBLK DFHCOMMAREA added by translator)[/red]

* address CWA and TWA

EXEC CICS ADDRESS                  
   CWA (ADDRESS OF CWA-AREA)
   TWA (ADDRESS OF TWA-AREA)
END-EXEC.                

*SET CWAYYDDD IN CASE 1ST SIGNON AND MAP DISPLAY
  IF CWAYYDDD NOT NUMERIC                     
     MOVE EIBDATE             TO  CWAYYDDD.   

EXEC CICS                                  
          GETMAIN                          
          FLENGTH (LENGTH OF PCI)          
          SET (ADDRESS OF PCI)
          INITIMG (X'00')          
          END-EXEC.                        

IF WSRD-TRAN        =  'PURC'               
   MOVE 'P'                 TO  PCICSS      
   MOVE 'PURC'              TO  WS-TRANCODE.
Also, the TFL (whatever that is) doesn't have addressability at this point. I'm assuming this gets set further on in the program? If not, expect an ASRA as soon as you try to write to it...
 
It might make it easier to see what's going on if you print the output of the translate step - then you can see the modifications made to the code by the translator.
 
thanks stevexff, it helps , i am moving now.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top