IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

Creating a VB file


IBM Mainframe Forums -> PL/I & Assembler
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
Lloyd Christensen

New User


Joined: 26 Apr 2022
Posts: 9
Location: United States

PostPosted: Sat Jun 04, 2022 1:35 am
Reply with quote

Hopefully, this will be my last question related to the class I'm in. I do appreciate the help I've gotten the past couple of weeks.

The assignment is to read in a PDS member (FB, LRECL=80). The first two bytes will reflect the length of the remaining record.

We're to create a variable length file (either blocked or unblocked). If I just send the print to SYSPRINT I can see the records. But when I add VB to the DCB and JCL I get an S002-18.

My instructor made a change and now I've lost something. In the code my intent was to use R9 for the record length but after his change R9 isn't being used.

[/code] PRINT ON,NODATA,NOGEN
* ------------------------------------------------------------------*
APGM6 CSECT , COMMA REQUIRED IF COMMENT ON THIS STMT
SAVE (14,12) SAVE CALLER'S REGS
BASR R12,0 ESTABLISH
USING *,R12
* LA R11,2048
* LA R11,2048(R12,R11)
* ------------------------------------------------------------------*
* SAVE CALLER REGISTERS *
LA R2,SAVEAREA POINT TO MY LOWER-LEVEL SA
ST R2,8(,R13) FORWARD-CHAIN MINE FROM CALLER'S
ST R13,SAVEAREA+4 BACK-CHAIN CALLER'S FROM MINE
LR R13,R2 SET 13 FOR MY SUBROUTINE CALLS

* ------------------------------------------------------------------*
* *
* Program logic: *
* The source is a PDS member with a fixed LRECL=80. The first two *
* bytes provide the length of the record to follow. *
* *
* Convert the record length field to packed and then binary. *
* Write to FILEOUT the varying length record. *
* ------------------------------------------------------------------*
* GET STARTED *
OPEN (FILEIN,(INPUT))
OPEN (FILEOUT,(OUTPUT))
STRTUP EQU *
*
SR R8,R8 ZERO R8, holds reclen as dblword
SR R9,R9 ZERO R9, this will have the rec len
SR R10,R10 ZERO R10, this will be used 4 dsect
GET FILEIN,INRECS GET THE RECORD
* PUT FILEOUT,INRECS
* I can see the whole record
PACK PKLEN,INLEN Convert FIXEDLEN to packed (PKLEN)
ZAP DBLWORD,PKLEN Zap pklen into dblword
CVB R8,DBLWORD Move DBLWORD into R9
bctr r8,r0
[code][
s r8,=f'4'
EX R8,WRDATA run the MVC in WRDATA
PUT FILEOUT,OUTREC
*
B STRTUP
* -----------------------------------------------------------*
WRAPUP EQU *
CLOSE FILEIN
CLOSE FILEOUT
L R13,SAVEAREA+4 POINT TO CALLER'S SAVE AREA
RETURN (14,12),RC=0 RESTORE CALLER'S REGS & RETURN
SAVEAREA DC 18F'0' AREA FOR MY CALLEE TO SAVE & RESTORE MY REGS
* ------------------------------------------------------------------*
* DATA AREAS *
*
PKLEN DS PL3 2-byte packed field for field length
DBLWORD DS D doubleword for conversion to binary
*
INRECS DS 0CL80 Define input record
INLEN DS ZL2
INRECRD DS CL78
*
*
WRDATA MVC VRECOUT(R9),INRECRD
* ------------------------------------------------------------------*
FILEIN DCB DSORG=PS, X
MACRF=(GM), X
DEVD=DA, X
DDNAME=FILEIN, X
RECFM=FB, X
LRECL=80
FILEOUT DCB DSORG=PS, X
MACRF=(PM), X
DEVD=DA, X
DDNAME=FILEOUT, X
RECFM=VB, X
LRECL=80
*
[code]*
OUTREC DS 0CL80
DS CL2'::'
VRECOUT DS CL78
********************** WRAP IT UP ***********************
LTORG
YREGS
END
//L.SYSLMOD DD DSN=KC03I71.ASM.LOAD,DISP=SHR
//L.SYSLIB DD DSN=KC03I71.ASM.LOAD,DISP=SHR
//L.SYSIN DD *
NAME APGM6(R)
/*
//*
//RUNAPGM6 EXEC PGM=APGM6,COND=EVEN
//STEPLIB DD DISP=SHR,DSN=KC03I71.ASM.LOAD
//FILEIN DD DISP=SHR,DSN=KC03I71.ASM.SRC(DATA6)
//FILEOUT DD DISP=(,CATLG,DELETE),DSN=KC03I71.PROG6.VB,
// SPACE=(TRK,(1,1)),RECFM=V,LRECL=84,BLKSIZE=84
//SYSOUT DD SYSOUT=*
//SYSUDUMP DD SYSOUT=*,OUTLIM=5000
//* [/code]
Back to top
View user's profile Send private message
dneufarth

Active User


Joined: 27 Apr 2005
Posts: 420
Location: Inside the SPEW (Southwest Ohio, USA)

PostPosted: Sat Jun 04, 2022 1:57 am
Reply with quote

please delete my post
Back to top
View user's profile Send private message
sergeyken

Senior Member


Joined: 29 Apr 2008
Posts: 2024
Location: USA

PostPosted: Sat Jun 04, 2022 2:24 am
Reply with quote

The result of your CVB R8,DBLWORD instruction is placed fully into R8, not into R9
Back to top
View user's profile Send private message
Willy Jensen

Active Member


Joined: 01 Sep 2015
Posts: 712
Location: Denmark

PostPosted: Sat Jun 04, 2022 2:30 am
Reply with quote

For starters
PKLEN DS PL3 2-byte packed field for field length
no, it is a 3-byte field, which can contain up to the value 99999, plus the sign.

The front end of a variable record is a 2-byte length followed by a 2-byte segment number, the latter being zero unless you are doing spanned records.

So I suggest something like the following (from the top of my head):
Code:
         Get   infile,indata                                           
         pack  dw,infile(2)            make packed dec                 
         cvd   r1,dw                   binary value in r1               
         sll   r1,16                   shift left halfword             
         st    r1,outrdw               save as RDW                     
         Put   outfile,outrdw                                           
       . . . .                                                         
dw       ds    d                                                       
outrdw   ds    a                       output RDW                       
indata   ds    cl80                                                       
Infile   DCB   DDNAME=INFILE,MACRF=GM,DSORG=PS ,EODAD=eod-addr           
OutFile  DCB   DDNAME=OUTFILE,MACRF=PM,DSORG=PS,                       c
               RECFM=VB,LRECL=84,BLKSIZE=0   

Note the EOD= parameter for the input DCB if you use a loop to read all records.
I suggest that you supply the bare minimum of parameters in the DCBs and get the rest from the datasets at open time.

And when you post code, please use the 'code' tags and only show the significant part of the program, I believe that most folks here knows how to setup base register and save area.
Anyway, good to see another one taking interest in assembler icon_smile.gif
Back to top
View user's profile Send private message
Willy Jensen

Active Member


Joined: 01 Sep 2015
Posts: 712
Location: Denmark

PostPosted: Sat Jun 04, 2022 7:04 pm
Reply with quote

Oops, just realized that I forgot to add the size of the RDW. So a slightly modified sample, which maybe makes the length field more clear:
Code:
         Get   infile,indata                                           
         pack  dw,infile(2)            make packed dec                 
         cvd   r1,dw                   binary value in r1 
         ahi   r1,4                    plus size of RDW             
         sth   r1,outlen               save length in RDW                     
         Put   outfile,outrdw                                           
       . . . .                                                         
dw       ds    d                                                       
outrdw   ds    0a                      output RDW                       
outlen   dc    h'0'                    length     
outseq   dc    h'0'                    segment nr (spanned only)
indata   ds    cl80
Back to top
View user's profile Send private message
sergeyken

Senior Member


Joined: 29 Apr 2008
Posts: 2024
Location: USA

PostPosted: Sat Jun 04, 2022 7:18 pm
Reply with quote

It might be a good idea also to add a fool-protection against bad input data, for the output length not to exceed the actual size of output buffer. The decimal length specified in the input line can be up to 99 in this particular case.

Also, conversion to binary should be CVB, not CVD

Code:
         Get   infile,indata                                           
         pack  dw,infile(2)            make packed dec                 
         CVB   r1,dw                   binary value in r1 
         CHI   r1,L'indata          VERIFY AN OVERSIZED RECORD
         JLE   *+8                  ACCEPT GIVEN LENGTH
         LHI   r1,L'indata          TRUNCATE TO MAXIMUM SIZE   
         ahi   r1,4                    plus size of RDW             
         sth   r1,outlen               save length in RDW                     
         Put   outfile,outrdw                                           
       . . . .                                                         
dw       ds    d                                                       
outrdw   ds    0a                      output RDW                       
outlen   dc    h'0'                    length     
outseq   dc    h'0'                    segment nr (spanned only)
indata   ds    cl80
Back to top
View user's profile Send private message
Willy Jensen

Active Member


Joined: 01 Sep 2015
Posts: 712
Location: Denmark

PostPosted: Sun Jun 05, 2022 2:53 pm
Reply with quote

yes must be CVB, good catch.
Back to top
View user's profile Send private message
Lloyd Christensen

New User


Joined: 26 Apr 2022
Posts: 9
Location: United States

PostPosted: Sun Jun 05, 2022 7:27 pm
Reply with quote

I am getting an abend in an I/O macro. It is a S002-18 for the output file (FILEOUT).

The definition of the S002-18 is:
18
An incorrect record was encountered on a QSAM PUT operation; the data set uses the variable record format. The value in the length of the record descriptor word (RDW) is incorrect for one of the following reasons:
It is greater than 32,767, or greater than the block size specified in the DCB.
It is less than 4, or less than 5 if ASA or machine control characters are used.
It specifies a value greater than the DCBLRECL value (maximum record size) that was specified when the data set was opened.

So I am fairly certain that it's a conflict with the output record and the DCB in the JCL but can't see a problem.

If I comment out the PUT FILEOUT,OUTREC statement the program runs. It allocates but as expected doesn't write to the FILEOUT dataset; it does write FILEOUT1 and at the data is there. Which leads me back to an LRECL/DCB issue.

Code:
STRTUP   EQU   *                                                     
*                                                                     
         SR    R8,R8             ZERO R8, holds reclen as dblword     
         SR    R9,R9             ZERO R9, holds reclen as halfword   
         MVC   OUTREC,=CL82' '   Move blanks into OUTREC             
         GET   FILEIN,INRECS     GET THE RECORD                       
*                                                                     
         PACK  PKLEN,INLEN       Convert INLEN to packed (PKLEN)     
         ZAP   DBLWORD,PKLEN     Zap PKLEN into DBLWORD               
         CVB   R8,DBLWORD        Move DBLWORD into R9                 
         BCTR  R8,R0                                                 
         S     R8,=F'4'          SUBTRACT 4                           
         LH    R9,R8                                                 
         A     R9,=F'5'                                               
         STH   R9,RECLEN                                             
         MVC   RECSEQ,=H'00'                                         
         MVC   RECLEN,R9                                             
         EX    R8,WRDATA         run the MVC in WRDATA               
         PUT   FILEOUT,OUTREC                                         
         PUT   FILEOUT1,OUTREC                                       
*                                                                     
         B     STRTUP                                                 
*        -----------------------------------------------------------*
WRAPUP   EQU   *                                                     
         CLOSE FILEIN                                                 
         CLOSE FILEOUT                                               
         CLOSE FILEOUT1                                               
         L     R13,SAVEAREA+4         POINT TO CALLER'S SAVE AREA     
         RETURN (14,12),RC=0          RESTORE CALLER'S REGS & RETURN 
SAVEAREA DC    18F'0'     AREA FOR MY CALLEE TO SAVE & RESTORE MY REGS
* ------------------------------------------------------------------*
*                       DATA AREAS                                   *
*                                                                     
PKLEN    DS    PL2           2-byte packed field for field length     
DBLWORD  DS   D              doubleword for conversion to binary     
*                                                                     
INRECS   DS   0CL80          Define input record                     
INLEN    DS    ZL2                                                   
INRECRD  DS    CL78                                                   
*                                                                     
*                                                                     
OUTREC   DS   0CL82                                                   
RDWOUT   DS   0F                                                     
RECLEN   DS    H                                                     
RECSEQ   DS    H                                                     
VRECOUT  DS    CL78                                                   
*                                                                     
WRDATA   MVC   VRECOUT(0),INRECRD       
* ------------------------------------------------------------------*   
FILEIN   DCB   DSORG=PS,                                               X
               MACRF=(GM),                                             X
               DEVD=DA,                                                X
               DDNAME=FILEIN,                                          X
               RECFM=FB,                                               X
               LRECL=80,                                               X
               EODAD=WRAPUP                                             
FILEOUT  DCB   DSORG=PS,                                               X
               MACRF=(PM),                                             X
               DEVD=DA,                                                X
               DDNAME=FILEOUT,                                         X
               RECFM=V,                                                X
               LRECL=82                                                 
*              BLKSIZE=0                                               
FILEOUT1 DCB   DSORG=PS,                                               X
               MACRF=(PM),                                             X
               DEVD=DA,                                                X
               DDNAME=FILEOUT1,                                        X
               RECFM=FB,                                               X
               LRECL=133,                                              X
               BLKSIZE=0                                               
*                                                                       
//RUNAPGM6 EXEC PGM=APGM6,COND=EVEN                     
//STEPLIB  DD DISP=SHR,DSN=KC03I71.ASM.LOAD             
//FILEIN   DD DISP=SHR,DSN=KC03I71.ASM.SRC(DATA6)       
//FILEOUT  DD DISP=(,CATLG,DELETE),DSN=KC03I71.PROG6.VB,
//         SPACE=(TRK,(1,1)),RECFM=V,LRECL=82           
//FILEOUT1 DD SYSOUT=*                                 
//SYSOUT   DD SYSOUT=*                                 
//SYSUDUMP DD SYSOUT=*,OUTLIM=5000                     
//*                                                                                 


Content from the actual abend includes:
JOB KC03I716         STEP RUNAPGM6        TIME 095417   DATE 22156    ID = 000
COMPLETION CODE      SYSTEM = 002      REASON CODE = 00000018                 
                                                                             
  PSW AT ENTRY TO ABEND   075C1000  80E3AB46  ILC  02  INTC  000D             
PSW MODULE     ADDRESS = 00000000_00E38000  OFFSET = 00002B46                 
NAME=IFG0199B                                                                 
Back to top
View user's profile Send private message
Lloyd Christensen

New User


Joined: 26 Apr 2022
Posts: 9
Location: United States

PostPosted: Sun Jun 05, 2022 8:19 pm
Reply with quote

Hi,

I found the problem. I was able to get past the S002-18 and in addition to the variable file I wanted to create I was sending the whole record to FILEOUT1 for SYSOUT

When I turned HEX on for FILEOUT1 I saw that it showed all records had a '05' in the first halfword and that shouldn't be. I was using the wrong register for the EX statement.

It works now, and I can move on to the next assignment which is to read in that same variable length file.

Thank you all,
Lloyd
Back to top
View user's profile Send private message
Willy Jensen

Active Member


Joined: 01 Sep 2015
Posts: 712
Location: Denmark

PostPosted: Sun Jun 05, 2022 8:58 pm
Reply with quote

your instruction
MVC RECLEN,R9
copies 2 bytes from address 9, it should be STH R9,RECLEN
Back to top
View user's profile Send private message
sergeyken

Senior Member


Joined: 29 Apr 2008
Posts: 2024
Location: USA

PostPosted: Sun Jun 05, 2022 11:18 pm
Reply with quote

Also, the instruction
Code:
  LH    R9,R8         
loads into R9 the 2-bytes content from absolute address 8, which makes absolutely no sense. It should be
Code:
  LR    R9,R8       


All those errors are very trivial, just misunderstanding of the basics of IBM architecture...
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> PL/I & Assembler

 


Similar Topics
Topic Forum Replies
No new posts Compare 2 files and retrive records f... DFSORT/ICETOOL 3
No new posts FTP VB File from Mainframe retaining ... JCL & VSAM 8
No new posts Extract the file name from another fi... DFSORT/ICETOOL 6
No new posts How to split large record length file... DFSORT/ICETOOL 10
No new posts Extracting Variable decimal numbers f... DFSORT/ICETOOL 17
Search our Forums:

Back to Top