Page 2 of 3

Re: Problem COBOL - CICS Program gives ABEND AEIP - INVREQ

PostPosted: Wed Aug 01, 2018 9:55 pm
by rogerb
Good afternoon, Mr. Robert Sample.
First of all, I thank you for your previous answer.
Today I added a record to the ESDS in RBA (Relative Byte Address) 0 with some dummy data.
When I choose option 2 to show records, it executes the command STARTBR to Start Browse.
After that, the CEDF shows RESPONSE: INVREQ.
Then it abends with ABEND AEIP.
The EIBRESP and EIBRESP2 are the same as before:

EIBRESP = 16 INVREQ
EIBRESP2 = 20

This is the current version of the Cobol Program.

Thank you.
Roger

000100 IDENTIFICATION DIVISION.                                         00010001
000200 PROGRAM-ID. CARPRG.                                              00020099
000300 AUTHOR.                    RMQB.                                 00030002
000400* ---------------------------------------------                   00040002
000500* OBJECTIVE: WRITE AND READ - SEQUENTIAL FILE                     00050099
000600* CARS INFORMATION                                                00060099
000700* ---------------------------------------------                   00070002
001700 DATA DIVISION.                                                   00170002
003400 WORKING-STORAGE SECTION.                                         00340002
003410 01  REGISTO.                                                     00341099
003420     05 CARNO               PIC 9(3).                             00342099
003430     05 DATESOLD            PIC X(10).                            00343099
003440     05 FILLER              PIC X(01).                            00344099
003450     05 CARBRAND            PIC X(10).                            00345099
003460     05 CARMODEL            PIC X(10).                            00346099
003470     05 REGISTRATION        PIC X(09).                            00347099
003480     05 CLIENTNAME          PIC X(10).                            00348099
003490     05 CONTACT             PIC 9(09).                            00349099
003491     05 FILLER              PIC X(01).                            00349199
003492     05 PRODUCTIONYEAR      PIC 9(04).                            00349299
003493     05 FILLER              PIC X(01).                            00349399
003494     05 MILEAGE             PIC 9(06).                            00349499
003495     05 FILLER              PIC X(01).                            00349599
003496     05 CARPRICE            PIC 9(05).                            00349699
003500 01  FS-CAR                 PIC X(02) VALUE SPACES.               00350099
003600     88 FS-CAR-OK                     VALUE '00'.                 00360099
003700     88 FS-CAR-EOF                    VALUE '10'.                 00370099
003800 01  WS-MESSAGE             PIC X(50).                            00380099
003900 01  WS-COMMAREA            PIC X(10) VALUE SPACES.               00390094
004000 01  OPTION-IN.                                                   00400099
004100     05 OPTION              PIC X(18).                            00410099
004200 01  FILEDATA.                                                    00420099
004300     05 DATA-WRITE          PIC X(18).                            00430099
004400     05 DATA-READ           PIC X(18).                            00440099
004500 01  WS-ABSTIME             PIC S9(15) COMP-3.                    00450099
004600 01  WS-DATE                PIC X(10).                            00460099
004700 01  WS-DAYWEEK             PIC S9(8) USAGE BINARY.               00470099
004800 01  WS-NAMEDAY             PIC X(09).                            00480099
005700 01  COUNTERS.                                                    00570099
005800     05 READ-COUNT          PIC 9(2).                             00580099
005810     05 CAR-COUNT           PIC 9(3).                             00581099
005900 01  WS-LEN                 PIC S9(4) COMP.                       00590099
005901 01  WS-KEY-LEN             PIC S9(4) COMP.                       00590199
005910 01  WS-STD-REC-KEY         PIC 9(3).                             00591099
005920 01  CH1                    PIC X(01) VALUE 'S'.                  00592099
005930 01  CH2                    PIC X(01) VALUE 'S'.                  00593099
005940 01  CH3                    PIC X(01) VALUE 'S'.                  00594099
006000 COPY CARMAP.                                                     00600099
006100 LINKAGE SECTION.                                                 00610036
006200 01  DFHCOMMAREA            PIC X(10).                            00620036
006300* TRANS(ECAR) MAPSET(CARMAP) GROUP(CARPRG)                        00630099
006400*MAP FIELDS OPT INFO MSG SALE BRAND MODEL PLATE CLIENT            00640099
006410*CONTINUED PHONE CREAT (CREATION DATE) MILES PRICE                00641099
006500 PROCEDURE DIVISION.                                              00650002
006600 000-MAIN.                                                        00660099
006700*    MOVE DFHCOMMAREA TO WS-COMMAREA.                             00670099
006800     IF EIBCALEN = 0 THEN                                         00680099
006810       MOVE DFHCOMMAREA TO WS-COMMAREA                            00681099
006900       PERFORM 010-PREPARE                                        00690099
007000       MOVE 'FIRST' TO WS-COMMAREA                                00700099
007010       MOVE SPACES TO REGISTO                                     00701099
007020       INITIALIZE REGISTO                                         00702099
007100       INITIALIZE FS-CAR READ-COUNT                               00710099
007200       INITIALIZE WS-LEN WS-STD-REC-KEY                           00720099
007300       MOVE 1 TO CAR-COUNT                                        00730099
007600     END-IF.                                                      00760099
007700*    FILLER/SEPARATOR                                             00770099
007800     IF EIBCALEN > 0 THEN                                         00780099
007900       PERFORM 010-PREPARE                                        00790099
008000     END-IF.                                                      00800099
009000     PERFORM 020-CHOICE.                                          00900099
009200     EXEC CICS                                                    00920099
009300     RETURN                                                       00930099
009400     END-EXEC.                                                    00940099
009500     GOBACK.                                                      00950099
009600 010-PREPARE.                                                     00960099
009700       MOVE LOW-VALUES TO CARMAI, CARMAO.                         00970099
009800       MOVE "PLAYER 1: INSERT NAMES IN THE NAME FIELD" TO MSGO.   00980099
009900       EXEC CICS                                                  00990099
010000         ASKTIME                                                  01000099
010100         ABSTIME(WS-ABSTIME)                                      01010099
010200       END-EXEC.                                                  01020099
010300       EXEC CICS                                                  01030099
010400         FORMATTIME                                               01040099
010500         ABSTIME(WS-ABSTIME)                                      01050099
010600         DDMMYYYY(WS-DATE)                                        01060099
010700         DATESEP('/')                                             01070099
010800       END-EXEC.                                                  01080099
010900       EXEC CICS                                                  01090099
011000         FORMATTIME                                               01100099
011100         ABSTIME(WS-ABSTIME)                                      01110099
011200         DAYOFWEEK(WS-DAYWEEK)                                    01120099
011300       END-EXEC.                                                  01130099
011400       EVALUATE WS-DAYWEEK                                        01140099
011500         WHEN 0                                                   01150099
011600           MOVE "SUNDAY" TO WS-NAMEDAY                            01160099
011700         WHEN 1                                                   01170099
011800           MOVE "MONDAY" TO WS-NAMEDAY                            01180099
011900         WHEN 2                                                   01190099
012000           MOVE "TUESDAY" TO WS-NAMEDAY                           01200099
012100         WHEN 3                                                   01210099
012200           MOVE "WEDNESDAY" TO WS-NAMEDAY                         01220099
012300         WHEN 4                                                   01230099
012400           MOVE "THURSDAY" TO WS-NAMEDAY                          01240099
012500         WHEN 5                                                   01250099
012600           MOVE "FRIDAY" TO WS-NAMEDAY                            01260099
012700         WHEN 6                                                   01270099
012800           MOVE "SATURDAY" TO WS-NAMEDAY                          01280099
012900       END-EVALUATE.                                              01290099
013000       MOVE WS-NAMEDAY TO WS-MESSAGE (1:10).                      01300099
013100       MOVE ',  ' TO WS-MESSAGE (11:3).                           01310099
013200       MOVE WS-DATE TO WS-MESSAGE (14:10).                        01320099
013300       MOVE WS-MESSAGE TO CDAYO.                                  01330099
013500*    END-IF.                                                      01350099
013600 020-CHOICE.                                                      01360099
013700*    MOVE YI TO YOUT.                                             01370099
013701     MOVE LOW-VALUES TO WS-MESSAGE.                               01370199
013702     MOVE LOW-VALUES TO CARMAI, CARMAO.                           01370299
013710     IF FS-CAR-OK                                                 01371099
013720       MOVE 'FILE OPENED OK' TO WS-MESSAGE                        01372099
013730     ELSE                                                         01373099
013740       MOVE 'FILE NOT OPENED ERROR' TO WS-MESSAGE (1:21)          01374099
013741       MOVE ': ' TO WS-MESSAGE (22:2)                             01374199
013742       MOVE FS-CAR TO WS-MESSAGE (24:2)                           01374299
013750     END-IF.                                                      01375099
013751     MOVE WS-MESSAGE TO MSGO.                                     01375199
013760     PERFORM 030-SEND-MAP.                                        01376099
013800     PERFORM UNTIL CH1 = 'N'                                      01380099
013900       MOVE LOW-VALUES TO CARMAI, CARMAO                          01390099
014000       MOVE SPACES TO CDAYI                                       01400099
014100       MOVE SPACES TO CDAYO                                       01410099
014200*    MOVE 0 TO WCOUNTDUPL.                                        01420099
014300       MOVE "OPTIONS| 0: EXIT/1: NEW RECORD/2: SHOW ALL" TO MSGO  01430099
014400       MOVE WS-NAMEDAY TO WS-MESSAGE (1:10)                       01440099
014500       MOVE ',  ' TO WS-MESSAGE (11:3)                            01450099
014600       MOVE WS-DATE TO WS-MESSAGE (14:10)                         01460099
014700       MOVE WS-MESSAGE TO CDAYO                                   01470099
014800       PERFORM 030-SEND-MAP                                       01480099
014900*      EXEC CICS                                                  01490099
015000*        SEND MAP('NAMEMA') MAPSET('NAMEMAP')                     01500099
015100*        ERASE                                                    01510099
015200*      END-EXEC                                                   01520099
015300       PERFORM 040-RECEIVE-MAP                                    01530099
015400*      EXEC CICS                                                  01540099
015500*        RECEIVE MAP('NAMEMA') MAPSET('NAMEMAP')                  01550099
015600*        ASIS                                                     01560099
015700*      END-EXEC                                                   01570099
015800       MOVE OPTI TO OPTION                                        01580099
015900       EVALUATE OPTION                                            01590099
016000         WHEN 1                                                   01600099
016100           PERFORM 050-ADD-RECORD                                 01610099
016200         WHEN 2                                                   01620099
016300           PERFORM 060-SHOW-RECORDS                               01630099
016400         WHEN 0                                                   01640099
016500           MOVE 'N' TO CH1                                        01650099
016600       END-EVALUATE                                               01660099
016610     END-PERFORM.                                                 01661099
016700 030-SEND-MAP.                                                    01670099
016800     EXEC CICS                                                    01680099
016900       SEND MAP('CARMA') MAPSET('CARMAP')                         01690099
017000       ERASE                                                      01700099
017100     END-EXEC.                                                    01710099
017200 040-RECEIVE-MAP.                                                 01720099
017300     EXEC CICS                                                    01730099
017400       RECEIVE MAP('CARMA') MAPSET('CARMAP')                      01740099
017500       ASIS                                                       01750099
017600     END-EXEC.                                                    01760099
017700 050-ADD-RECORD.                                                  01770099
017800     MOVE LOW-VALUES TO CARMAI, CARMAO.                           01780099
017900       MOVE WS-NAMEDAY TO WS-MESSAGE (1:10).                      01790099
018000       MOVE ',  ' TO WS-MESSAGE (11:3).                           01800099
018100       MOVE WS-DATE TO WS-MESSAGE (14:10).                        01810099
018200       MOVE WS-MESSAGE TO CDAYO.                                  01820099
018210       MOVE CAR-COUNT TO CARNO.                                   01821099
019600     MOVE LOW-VALUES TO CARMAI, CARMAO.                           01960099
019610     MOVE -1 TO INFOL.                                            01961099
019700     MOVE "WRITE THE DATE OF SALE (DD-MM-YYYY) IN DATA" TO MSGO.  01970099
019800     PERFORM 030-SEND-MAP.                                        01980099
019900     PERFORM 040-RECEIVE-MAP.                                     01990099
020000     MOVE INFOI TO DATESOLD.                                      02000099
020100     MOVE LOW-VALUES TO CARMAI, CARMAO.                           02010099
020200     MOVE "WRITE THE CAR BRAND IN THE DATA FIELD" TO MSGO.        02020099
020300     PERFORM 030-SEND-MAP.                                        02030099
020400     PERFORM 040-RECEIVE-MAP.                                     02040099
020500     MOVE INFOI TO CARBRAND.                                      02050099
020600     MOVE LOW-VALUES TO CARMAI, CARMAO.                           02060099
020700     MOVE "WRITE THE CAR MODEL IN THE DATA FIELD" TO MSGO.        02070099
020800     PERFORM 030-SEND-MAP.                                        02080099
020900     PERFORM 040-RECEIVE-MAP.                                     02090099
021000     MOVE INFOI TO CARMODEL.                                      02100099
021100     MOVE LOW-VALUES TO CARMAI, CARMAO.                           02110099
021200     MOVE "WRITE THE LICENSE PLATE IN DATA FIELD" TO MSGO.        02120099
021300     PERFORM 030-SEND-MAP.                                        02130099
021400     PERFORM 040-RECEIVE-MAP.                                     02140099
021500     MOVE INFOI TO REGISTRATION.                                  02150099
021600     MOVE LOW-VALUES TO CARMAI, CARMAO.                           02160099
021700     MOVE "WRITE THE NAME OF THE CLIENT IN DATA FIELD" TO MSGO.   02170099
021800     PERFORM 030-SEND-MAP.                                        02180099
021900     PERFORM 040-RECEIVE-MAP.                                     02190099
022000     MOVE INFOI TO CLIENTNAME.                                    02200099
022010     MOVE LOW-VALUES TO CARMAI, CARMAO.                           02201099
022100     MOVE "WRITE THE PHONE OF CLIENT IN THE DATA FIELD" TO MSGO.  02210099
022200     PERFORM 030-SEND-MAP.                                        02220099
022300     PERFORM 040-RECEIVE-MAP.                                     02230099
022400     MOVE INFOI TO CONTACT.                                       02240099
022410     MOVE LOW-VALUES TO CARMAI, CARMAO.                           02241099
022500     MOVE "WRITE WHICH YEAR THE CAR WAS MADE DATA FIELD" TO MSGO. 02250099
022600     PERFORM 030-SEND-MAP.                                        02260099
022700     PERFORM 040-RECEIVE-MAP.                                     02270099
022800     MOVE INFOI TO PRODUCTIONYEAR.                                02280099
022810     MOVE LOW-VALUES TO CARMAI, CARMAO.                           02281099
022900     MOVE "WRITE THE MILEAGE IN THE DATA FIELD" TO MSGO.          02290099
023000     PERFORM 030-SEND-MAP.                                        02300099
023100     PERFORM 040-RECEIVE-MAP.                                     02310099
023200     MOVE INFOI TO MILEAGE.                                       02320099
023210     MOVE LOW-VALUES TO CARMAI, CARMAO.                           02321099
023300     MOVE "WRITE THE PRICE OF THE CAR IN DATA FIELD" TO MSGO.     02330099
023400     PERFORM 030-SEND-MAP.                                        02340099
023500     PERFORM 040-RECEIVE-MAP.                                     02350099
023600     MOVE INFOI TO CARPRICE.                                      02360099
023700     EXEC CICS WRITE                                              02370099
023800       FILE('CARSDD')                                             02380099
023900       FROM(REGISTO)                                              02390099
024000       LENGTH(WS-LEN)                                             02400099
024010       RIDFLD(CARNO)                                              02401099
024100       RBA                                                        02410099
024200     END-EXEC.                                                    02420099
024210     ADD 1 TO CAR-COUNT.                                          02421099
024300*    CLOSE CAR.                                                   02430099
024400 060-SHOW-RECORDS.                                                02440099
024500*    OPEN INPUT CAR                                               02450099
024501     MOVE LOW-VALUES TO WS-MESSAGE.                               02450199
024502     MOVE LOW-VALUES TO CARMAI, CARMAO.                           02450299
024503     IF FS-CAR-OK                                                 02450399
024504       MOVE 'FILE OPENED OK' TO WS-MESSAGE                        02450499
024505     ELSE                                                         02450599
024506       MOVE 'FILE NOT OPENED ERROR' TO WS-MESSAGE (1:21)          02450699
024507       MOVE ': ' TO WS-MESSAGE (22:2)                             02450799
024508       MOVE FS-CAR TO WS-MESSAGE (24:2)                           02450899
024509     END-IF.                                                      02450999
024510     MOVE WS-MESSAGE TO MSGO.                                     02451099
024511     PERFORM 030-SEND-MAP.                                        02451199
024512     MOVE WS-LEN TO WS-KEY-LEN.                                   02451299
024520     MOVE 0 TO CARNO.                                             02452099
024600     EXEC CICS STARTBR                                            02460099
024700       FILE('CARSDD')                                             02470099
024800       RIDFLD(CARNO)                                              02480099
024810       RBA                                                        02481099
024900     END-EXEC.                                                    02490099
024910     MOVE LOW-VALUES TO WS-MESSAGE.                               02491099
024920     MOVE LOW-VALUES TO CARMAI, CARMAO.                           02492099
024930     IF FS-CAR-OK                                                 02493099
024940       MOVE 'FILE OPENED OK' TO WS-MESSAGE                        02494099
024950     ELSE                                                         02495099
024960       MOVE 'FILE NOT OPENED ERROR' TO WS-MESSAGE (1:21)          02496099
024970       MOVE ': ' TO WS-MESSAGE (22:2)                             02497099
024980       MOVE FS-CAR TO WS-MESSAGE (24:2)                           02498099
024990     END-IF.                                                      02499099
024991     MOVE WS-MESSAGE TO MSGO.                                     02499199
024992     PERFORM 030-SEND-MAP.                                        02499299
025000     PERFORM UNTIL FS-CAR-EOF                                     02500099
025100       EXEC CICS READNEXT                                         02510099
025200         FILE('CARSDD')                                           02520099
025300         INTO(REGISTO)                                            02530099
025310         LENGTH(WS-LEN)                                           02531099
025320         RIDFLD(CARNO)                                            02532099
025330         RBA                                                      02533099
025400       END-EXEC                                                   02540099
025500       MOVE LOW-VALUES TO WS-MESSAGE                              02550099
025600       MOVE LOW-VALUES TO CARMAI, CARMAO                          02560099
025700       IF FS-CAR-OK                                               02570099
025800         MOVE 'FILE OPENED OK' TO WS-MESSAGE                      02580099
025900       ELSE                                                       02590099
025910         MOVE 'FILE NOT OPENED ERROR' TO WS-MESSAGE (1:21)        02591099
025920         MOVE ': ' TO WS-MESSAGE (22:2)                           02592099
025930         MOVE FS-CAR TO WS-MESSAGE (24:2)                         02593099
025940       END-IF                                                     02594099
025950       MOVE WS-MESSAGE TO MSGO                                    02595099
025960       PERFORM 030-SEND-MAP                                       02596099
026000         ADD 1 TO READ-COUNT                                      02600099
026001         MOVE LOW-VALUES TO CARMAI, CARMAO                        02600199
026002         MOVE WS-NAMEDAY TO WS-MESSAGE (1:10)                     02600299
026003         MOVE ',  ' TO WS-MESSAGE (11:3)                          02600399
026004         MOVE WS-DATE TO WS-MESSAGE (14:10)                       02600499
026005         MOVE WS-MESSAGE TO CDAYO                                 02600599
026010         MOVE 'READING RECORDS IN FILE' TO MSGO                   02601099
026100         MOVE DATESOLD TO SALEO                                   02610099
026200         MOVE CARBRAND TO BRANDO                                  02620099
026500         MOVE CARMODEL TO MODELO                                  02650099
026600         MOVE REGISTRATION TO PLATEO                              02660099
026900         MOVE CLIENTNAME TO CLIENTO                               02690099
027000         MOVE CONTACT TO PHONEO                                   02700099
027300         MOVE PRODUCTIONYEAR TO CREATO                            02730099
027400         MOVE MILEAGE TO MILESO                                   02740099
027700         MOVE CARPRICE TO PRICEO                                  02770099
027800         PERFORM 030-SEND-MAP                                     02780099
027900     END-PERFORM.                                                 02790099
028000*    CLOSE CAR.                                                   02800099
 

Re: Problem COBOL - CICS Program gives ABEND AEIP - INVREQ

PostPosted: Wed Aug 01, 2018 10:02 pm
by Robert Sample
What do you get when you do a REPRO of the ESDS data set to print?

Re: Problem COBOL - CICS Program gives ABEND AEIP - INVREQ

PostPosted: Wed Aug 01, 2018 10:47 pm
by rogerb
If you are talking about using REPRO to copy ESDS to a PS file, when I submit the Job I get success (MAXCC = 0).
When I go to the PS, I see the following


****** ***************************** Top of Data ******************************
==MSG> -Warning- The UNDO command is not available until you change            
==MSG>           your edit profile using the command RECOVERY ON.              
000001 123 DUMMYTEST TESTDATA                                                  
****** **************************** Bottom of Data ****************************



Thank you,
Roger

Re: Problem COBOL - CICS Program gives ABEND AEIP - INVREQ

PostPosted: Thu Aug 02, 2018 12:03 am
by Robert Sample
I looked at your code. You are doing some very strange things (such as displaying one field message at a time) and you're using conversational mode programming (which is highly inefficient). However, the STARTBR is flat out wrong. You have
024600     EXEC CICS STARTBR                                            02460099
024700       FILE('CARSDD')                                             02470099
024800       RIDFLD(CARNO)                                              02480099
024810       RBA                                                        02481099
024900     END-EXEC.                                                    02490099
Points to be made:
1. With an ESDS base (which is what you are using), you MUST specify RBA. If you are using an ESDS alternate index, you may use the key but you don't have an alternate index.
2. An RBA is an unsigned 32-bit value (PIC 9(09) COMP-5 in COBOL terms).
3. Your CARNO variable is a zoned decimal 3-byte variable. This is not a valid RBA neither in length nor in USAGE.
4. Your RIDFLD is part of the data record being read by your EXEC CICS READ. This will wipe out the value in the variable (which is needed for the next EXEC CICS READ), which will also cause you problems when you get to that point. The RIDFLD variable should be independent and retained from record to record without being changed.
5. I highly recommend you add a RESP variable to trap the response code -- it can help in debugging.

Re: Problem COBOL - CICS Program gives ABEND AEIP - INVREQ

PostPosted: Thu Aug 02, 2018 1:24 am
by rogerb
I know my current program is far from perfect.
In the 050-ADD-RECORD I'm asking the user to insert data in field 1, then in field 2, field 3 etc.., because I thought that it would be simpler to ask all the details that are going to be recorded in the file and only then writing in the file.
The 060-SHOW-RECORDS is supposed to be the exact opposite, showing all the data of a record in the respective fields.
As for the program being conversational, I've already created Conversational COBOL-CICS programs and Pseudo-Conversational COBOL-CICS programs.
Because this is something entirely new to me, I preferred to start by creating a conversational program.
I removed the variable CARNO from the data record (REGISTO).

This is CARNO now:

01 CARNO PIC9(09) COMP-5

About the response RESP variable, in one of the Pseudo-Conversational programs I created, I added a RESPONSE variable in the receive map, to prevent MAPFAIL.

This is the RESPONSE variable I used:

01  VALIDATE.                                                    00160099
001700     05 VY                  PIC 99.                               00170099
001710     05 RESPONSE            PIC S9(8) BINARY.                     00171099



And this is the CHECKDATA:

030-CHECKDATA.                                                   00780099
007900     EXEC CICS                                                    00790099
008000     RECEIVE MAP('LEAPMA') MAPSET('LEAPMAP')                      00800099
008020     RESP(RESPONSE)                                               00802099
008100     END-EXEC.                                                    00810099
008200     MOVE YI TO YOUT.                                             00820099
008300     MOVE YL TO VY.                                               00830099
008302     IF RESPONSE = DFHRESP(MAPFAIL)                               00830299
008500       MOVE "INSERT VALUE FOR THE YEAR" TO WS-MESSAGE             00850099
008600       MOVE WS-MESSAGE TO MSGO                                    00860099
008700       MOVE LOW-VALUES TO YI                                      00870099
008800       EXEC CICS                                                  00880099
008900       SEND MAP('LEAPMA') MAPSET('LEAPMAP')                       00890099
009000       ERASE                                                      00900099
009100       END-EXEC                                                   00910099
009200       GO TO 030-CHECKDATA                                        00920099
009201     ELSE                                                         00920199
009210       IF RESPONSE = DFHRESP(NORMAL)                              00921099



This variable RESPONSE with PIC S9(8) BINARY is good enough for the STARTBR or I need to change it ?

Finally about the STARTBR, I should change it to be like this:


EXEC CICS STARTBR                                          
       FILE('CARSDD')                                            
       RIDFLD(CARNO)                                          
       RBA                                        
       RESPONSE(RESPONSE)            
     END-EXEC.



Or what should it be like ?

Thank you,
Roger

Re: Problem COBOL - CICS Program gives ABEND AEIP - INVREQ

PostPosted: Thu Aug 02, 2018 1:59 am
by Robert Sample
This variable RESPONSE with PIC S9(8) BINARY is good enough for the STARTBR or I need to change it ?
In general, most of the time there is a single RESPONSE variable for a CICS program. The same variable is used for every API call and queried as appropriate after each API call.
I preferred to start by creating a conversational program.
There are few, if any, CICS sites around that allow the use of conversational programming. CICS sites mandate the use of pseudo-conversational programming because of the resource overhead of conversational programming (the terminal, network line, memory, and potentially any file / TDQ / TSQ and so forth in the program will be tied up as long as that transaction is running whether it is conversational and execution time is measured in minutes to hours or pseudo-conversational and execution time is measured in seconds to minutes).

The usual way to process maps is to display the map with every field needed, the terminal user keys data into every relevant field, and then when the map is received validate each field sequentially. If the map needs to be resent to fix errors, every error field will be highlighted and can be fixed at one time. Processing the data in the program often takes no more than a few seconds, while the data entry may require several minutes.

Re: Problem COBOL - CICS Program gives ABEND AEIP - INVREQ

PostPosted: Thu Aug 02, 2018 7:36 pm
by rogerb
Good afternoon Mr. Robert Sample.
Thank you for your previous answer.
In the past I created Pseudo-Conversational programs, but in this case I started with a Conversational.
I will change the program to Pseudo-Conversational, and I will try to change the program to process the map in the way you explained previously.
I may need to ask for you help in these matters.
But for now I have to solve the other problem, with the STARTBR.
I changed the STARTBR to be like this:

EXEC CICS STARTBR                                      
   FILE('CARSDD')                                      
   RIDFLD(CARNO)                                        
   RBA                                                  
   RESP(RESPONSE)                                      
 END-EXEC.                                              
 MOVE LOW-VALUES TO WS-MESSAGE.                        
 MOVE LOW-VALUES TO CARMAI, CARMAO.                    
 IF FS-CAR-OK                                          
   MOVE 'FILE OPERATION OK' TO WS-MESSAGE              
 ELSE                                                  
   MOVE 'FILE OPERATION ERROR' TO WS-MESSAGE (1:20)    
   MOVE ': ' TO WS-MESSAGE (21:2)                      
   MOVE RESPONSE TO WS-MESSAGE (24:2)                  
 END-IF.                                                


When I execute the program in the STARTBR it still makes the INVREQ.
After that it sends the map and it shows the message FILE OPERATION ERROR: 00
So, I think the response code is 00.
I looked in the internet and I think the message means:
"The user has no access."

Thank you,
Roger

Re: Problem COBOL - CICS Program gives ABEND AEIP - INVREQ

PostPosted: Thu Aug 02, 2018 7:56 pm
by Robert Sample
CICS does not set the file status code on file operations. Testing FS-CAR-OK in your CICS program is a waste of time and code. This is why it is so critical to check the RESPONSE value after each API call. How do you know that you are getting INVREQ on the STARTBR? If you think so because of the file status code, you need to rethink. Your code should be
EXEC CICS STARTBR                                      
   FILE('CARSDD')                                      
   RIDFLD(CARNO)                                        
   RBA                                                  
   RESP(RESPONSE)                                      
 END-EXEC.  
IF  RESPONSE NOT = DFHRESP(NORMAL)
    <handle bad code on STARBR>
END-IF
 

Re: Problem COBOL - CICS Program gives ABEND AEIP - INVREQ

PostPosted: Thu Aug 02, 2018 9:16 pm
by rogerb
I changed the code like you showed in the previous answer.
Now the code is:


EXEC CICS STARTBR                                      
   FILE('CARSDD')                                  
   RIDFLD(CARNO)                                        
   RBA                                                  
   RESP(RESPONSE)                                      
 END-EXEC.                                              
 MOVE LOW-VALUES TO WS-MESSAGE.                        
 MOVE LOW-VALUES TO CARMAI, CARMAO.                    
 IF RESPONSE NOT = DFHRESP(NORMAL)                      
   MOVE 'FILE OPERATION ERROR' TO WS-MESSAGE (1:20)    
   MOVE ': ' TO WS-MESSAGE (21:2)                      
   MOVE RESPONSE TO WS-MESSAGE (24:8)                  
 END-IF.  
MOVE WS-MESSAGE TO MSGO.
PERFORM 030-SEND-MAP.                            


When I run the program in CEDF debug mode, I see the INVREQ after the STARTBR is executed.
The RESPONSE CODE is 16.

The program then continues to the READNEXT, and then it abends with AEIP.

EIBRESP = 16 INVREQ
EIBRESP2 = 34

Thank you,
Roger

Re: Problem COBOL - CICS Program gives ABEND AEIP - INVREQ

PostPosted: Thu Aug 02, 2018 9:36 pm
by Robert Sample
I'm running out of ideas, but I'll keep researching. What do you get when you enter CEDA V GR(*) FI(CARSDD) -- if you get a line showing the file, put a V after the GROUP and post the output (using the Code button to preserve spacing)? One possibility would be if the CICS region has been shut down and brought back up, and the CEDA defines were not put into a list installed at CICS start up, your CARSDD file definition would not be out there any longer.
MOVE LOW-VALUES TO CARMAI, CARMAO.
This code is redundant, by the way -- if you look at the copy book, CARMAO REDEFINES CARMAI. So moving LOW-VALUES to one of them also moves LOW-VALUES to the other one since they represent the same storage locations.