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

How can read a dataset with record-format/length undefined?


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
Gabriele Soranzo

New User


Joined: 28 Dec 2006
Posts: 6
Location: Italy, Trieste

PostPosted: Tue Jan 16, 2007 7:59 pm
Reply with quote

Hi all,

I use the IBM VS COBOL II Release 4.0 compiler.

I have the following need for a Cobol program:

read a sequential dataset with record-format and record-length undefined (for "undefined" I mean: I know its at runtime moment, not in compile time).

Other information:
- I can assume that the record-format is only or FB or VB.
- I can call Assembler modules.
- I cannot change the version of compiler.
- I know the DDNAME of the dataset, and it is defined in the JCL of execution of the Cobol

In my knowledge it's impossible satisfy this goal only in Cobol (I mean: in VS COBOL II).

In the web I founded a lot of Assembler routine (called from a Cobol) that use DYNALLOC macro, but these routines are not useful for me, since I must define in the Cobol the FD with the exact lenght of the dataset.

My main questions:

a) Is it true my knowledge that it's impossible satisfy this goal only in Cobol (I mean: in VS COBOL II)?

b) If answer to a) is "yes", somebody has already developed an Assembler routines (callable from a Cobol) that reachs the goal?

c) If answer to b) is "no", somebody has already developed an Cobol examples that reachs the goal?

and, last question (but only if there is an aswer to first three)
d) Somebody has already developed an Assembler routines (callable from a Cobol) or a Cobol that writes an undefined dataset?

Many thanks for any hint/idea/support,

Gabriele
Back to top
View user's profile Send private message
DavidatK

Active Member


Joined: 22 Nov 2005
Posts: 700
Location: Troy, Michigan USA

PostPosted: Fri Jan 19, 2007 6:52 am
Reply with quote

Gabriele Soranzo,

I am absolutely 100% that with the correct assembler routines this is possible, but if you have access to these types of assembler subroutines, why not just let the subroutine deal with ALL of the I/O and just pass back the record.

Another question: What are you going to do with a record of varying lengths, how are you going to process this?
Back to top
View user's profile Send private message
William Thompson

Global Moderator


Joined: 18 Nov 2006
Posts: 3156
Location: Tucson AZ

PostPosted: Fri Jan 19, 2007 7:09 am
Reply with quote

Gabriele Soranzo wrote:
I have the following need for a Cobol program:
read a sequential dataset with record-format and record-length undefined (for "undefined" I mean: I know its at runtime moment, not in compile time).
Other information:
- I can assume that the record-format is only or FB or VB.
- I can call Assembler modules.
- I cannot change the version of compiler.
- I know the DDNAME of the dataset, and it is defined in the JCL of execution of the Cobol
Is This the third or fourth one of these questions that have surfaced here in the last couple of cycles?
Why won't will these people just look and see if the question has been answered yet?
Assembler (subroutines) can identify the format and structure of the dataset prior to actually opening it, like David said:
Quote:
with the correct assembler routines this is possible
.
Look before asking, better to ask for search instructions than to just blindly ask for answers, that is what defines a programmer from a coder.... icon_cry.gif
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Fri Jan 19, 2007 8:06 am
Reply with quote

Hello Gabriele,

Depending on just what you are going to do with the data once you read it, and that you know the dcb info before you start the process, you might copy the "undefined" file into a fixed length file that has an lrecl larger than the largest possible input record can be. Depending on the range of data lengths you intend to support, you might have a few of these modules so that "everything" doesn't need an intermediate of maximum possible length.

When your program runs, it will have "standard" records to process and then it can proceed. One of the parms you would pass it is the data length is has to work with.

You could make the copy with SORT or IEBGENER.

While this is not as elegant and would cost an extra pass of the data, it would keep all of your code in standard COBOL with no calling of assembler modules that aren't yet on your system or trying to chase/modify control blocks in your program.

Also, if you provide some details as to what your program is supposed to do (other than just read undefined records), we may be able to provide better suggestions.
Back to top
View user's profile Send private message
skkp2006

New User


Joined: 14 Jul 2006
Posts: 93
Location: Chennai,India

PostPosted: Fri Jan 19, 2007 4:52 pm
Reply with quote

Correct me if i am wrong.

1.Read the dataset into a variable larger than largest of the record.
2.Then perform a loop from the end of the record looking for value not equal to spaces and retreive the actual length.

eg:
PERFORM VARYING TRX036-OPER-STMT-DATA-LEN
FROM 590 BY -1 UNTIL
FC-NAR-OPER-STMT-VALUES(TRX036-OPER-STMT-DATA-LEN:1)
NOT = SPACES

SYAM
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Fri Jan 19, 2007 8:44 pm
Reply with quote

Hello,

Yes, that will parse the data once it is read, but the challange is opening/reading the "undefined" file and resolving the dcb parameters dynamically.
Back to top
View user's profile Send private message
Gabriele Soranzo

New User


Joined: 28 Dec 2006
Posts: 6
Location: Italy, Trieste

PostPosted: Sat Jan 20, 2007 3:07 am
Reply with quote

Hi all,

thanks for your answers.

I adopted the suggestion of Dave, and I have developed an Assembler routines that just open-read-close a generic sequential dataset (the routine receive in input only the DDNAME, all other information (recfm and lrecl are not needs).

I list below the solution (there is the Assembler routines and the Cobol programs used for Unit Test), maybe this code will be used by others members...I spent an entire day for investigate on the web the same question but I wanted a confirm that it was impossible solve the problem in "pure" Cobol (I mean: without Assembler).

For William: I was (very) forced in the time, I had read several threads on this topic, but I was not sure that it's definitly impossible reach my goal without Assembler, I didn't wanted violate the rules of this forum (but I think that I have not done it). In every case I appreciate the cooperative approach and I consider that your comment should appears a personal dispute, and I am definitly not interested to do it. I somebody had developed already a solution for me it was welcome. In every case the next time I will be more precise in my requests.

For the below code:
- the Assembler code use two custom macro (MINIZIA and MFINE) that I "forced" to used for programming convention, just substitute it with the standard start and end of an Assembler routine.
- there are not remarks...it should be in in Italian icon_smile.gif
- the routine receives in input always P$COMMAND (CL8'OPEN'/CL8'READ'/CL8'CLOSE) and in output always P$RETCOD(C'00' success, other errors) and P$RETMSG(if success it's space, otherwise it is a short error message),
for OPEN in input P$DDNAME, in output P$RECLNG, P$BLKSIZ, p$RECFMT, P$DSNAME,
fore READ in input nothing, in output P$RECLNG, p$EOF ('N' not eof, 'Y' eof)
for CLOSE in input nothing, in output nothing.
The Cobol code used for unit test receives in input from PARM the DDNAME (if it's not defined the DDNAME 'INFILE' is used.

Regards,

Gabriele

Code:

****BASED ON R9****
         DCBD  DSORG=PS
*
****BASED ON RA****
DSJFCB   DSECT
         IEFJFCBN
*
****BASED ON R8****
P$PARAM    DSECT
P$COMMAND  DS   CL8       * OPEN/READ/CLOSE
P$DDNAME   DS   CL8       * DCBDDNAM
P$BUFLNG   DS   H         * DCBBUFL
P$RECLNG   DS   H         * DCBLRECL
P$BLKSIZ   DS   H         * DCBBLKSI
P$RECFMT   DS   BL1       * DCBRECFM
P$DSNAME   DS   CL44
P$EOF      DS   CL1
P$RETCOD   DS   CL2
P$RETMSG   DS   CL60
****BASED ON R7****
P$PARAMR DSECT
P$RECVAL DS   CL32760
*
GWDSEQ1A MINIZIA RBASE=(R3,R4),DATEUPD=?DATEUPD,TIMEUPD=?TIMEUPD        00002500
*
         SAVE  (14,12)
         BALR  12,0
         USING *,12
*
         B      START
*
JFCB     RDJFCB INFILE,MF=L
*
START    EQU    *
*
         ST    R1,SAVER1
         USING P$PARAM,R8
         L     R8,0(,R1)
*
         MVC   P$RECLNG,=H'0'
         MVI   P$EOF,C'N'
         MVI   P$DSNAME,C' '
         MVC   P$DSNAME+1(L'P$DSNAME-1),P$DSNAME
         MVC   P$RETCOD,=C'00'
         MVI   P$RETMSG,C' '
         MVC   P$RETMSG+1(L'P$RETMSG-1),P$RETMSG
*
         CLC   P$COMMAND,READ
         BE    C_READ
*
         CLC   P$COMMAND,OPEN
         BE    C_OPEN
*
         CLC   P$COMMAND,CLOSE
         BE    C_CLOSE
*
         MVC   P$RETCOD,=C'01'
         MVC   P$RETMSG(20),=CL20'COMANDO INVALIDO'
         MVI   P$RETMSG+20,C'('
         MVC   P$RETMSG+21(8),P$COMMAND
         MVI   P$RETMSG+29,C')'
         B     END_KO                Return to Calling program
*
END_EOF  EQU   *
*
         MVI   P$EOF,C'Y'
         B     END_OK
*
END_KO   EQU   *
*
         LA    RF,1
         B     END_X
*
END_OK   EQU   *
*
         SR    RF,RF
         B     END_X
END_X    EQU   *
*
         MFINE RC=(RF)
*
***********************************************************************
C_OPEN   EQU   *
*
         CLC   P$DDNAME,=CL8' '
         BE    C_OPEN2
*
         USING IHADCB,R9
         LA    R9,INFILE
         MVC   DCBDDNAM,P$DDNAME
*
         SR    R1,R1
         LH    R1,=F'32760'
         STH   R1,DCBBUFL
*
         RDJFCB MF=(E,JFCB)
*
         USING INFMJFCB,RA
         LA    RA,IN$JFCB
         MVC   P$DSNAME,JFCBDSNM
*
         LA    R9,INFILE
         USING IHADCB,R9
*
C_OPEN2  EQU   *
*
         OPEN  (INFILE,(INPUT))
         TM    DCBOFLGS,X'10'
         BZ    ERR_IO
         LA    R9,INFILE
*
         MVC   P$RECLNG,DCBLRECL
         MVC   P$BLKSIZ,DCBBLKSI
         MVC   P$RECFMT,DCBRECFM
*
         B     END_OK
*
***********************************************************************
C_READ   EQU   *
*
         L     R1,SAVER1
         USING P$PARAMR,R7
         L     R7,4(,R1)
         GET   INFILE,P$RECVAL
         LA    R9,INFILE
         MVC   P$RECLNG,DCBLRECL
         B     END_OK
*
***********************************************************************
C_CLOSE  EQU   *
*
         CLOSE INFILE
         FREEPOOL INFILE
         B     END_OK
*
ERR_IO   EQU   *
*
         MVC   P$RETCOD,=C'02'
         MVC   P$RETMSG(20),=CL20'ERRORE I/O'
         MVI   P$RETMSG+20,C'('
         MVC   P$RETMSG+21(8),P$COMMAND
         MVI   P$RETMSG+29,C')'
         B     END_KO
*
INFILE   DCB   DDNAME=INFILE,                                          *
               DSORG=PS,                                               *
               EODAD=END_EOF,                                          *
               EXLST=IN$EXLST,                                         *
               MACRF=GM,                                               *
               SYNAD=ERR_IO
*
D$RECVAL DC    CL80' '
*
SAVER1   DC    F'0'
*
READ     DC    CL8'READ    '
OPEN     DC    CL8'OPEN    '
CLOSE    DC    CL8'CLOSE   '
*
IN$EXLST DS    0F
         DC    X'87'
         DC    AL3(IN$JFCB)
IN$JFCB  DS    0F
         DC    CL176' '
*
         END

       IDENTIFICATION DIVISION.
       PROGRAM-ID. GWTSEQ1R.
      *
      *
       ENVIRONMENT DIVISION.
      *
      *
       INPUT-OUTPUT SECTION.
      *
      *
       FILE-CONTROL.
      *
      *
       DATA DIVISION.
      *
      *
       FILE SECTION.
      *
      *
       WORKING-STORAGE SECTION.
      *
       01  DSEQ-PARAM.
        03 DSEQ-PARAM-INPUT.
           05  DSEQ-COMMAND            PIC  X(0008).
               88  DSEQ-COMMAND-OPEN   VALUE 'OPEN'.
               88  DSEQ-COMMAND-OPEN   VALUE 'READ'.
               88  DSEQ-COMMAND-OPEN   VALUE 'CLOSE'.
           05  DSEQ-DDNAME             PIC  X(0008).
           05  DSEQ-BUFLNG             PIC S9(0004) COMP.
        03 DSEQ-PARAM-OUTPUT.
           05  DSEQ-RECLNG             PIC S9(0004) COMP.
           05  DSEQ-BLKSIZ             PIC S9(0004) COMP.
           05  DSEQ-RECFMT             PIC  X(0001).
           05  DSEQ-DSNAME             PIC  X(0044).
           05  DSEQ-EOF                PIC  X(0001).
               88  DSEQ-EOF-NOT        VALUE 'N'.
               88  DSEQ-EOF-YES        VALUE 'Y'.
           05  DSEQ-RETCOD             PIC  X(0002).
               88  DSEQ-RETCOD-SUCCESS VALUE '00'.
               88  DSEQ-RETCOD-ERRCMD  VALUE '01'.
               88  DSEQ-RETCOD-ERRIO   VALUE '02'.
           05  DSEQ-RETMSG             PIC  X(0060).
      *
       01  DSEQ-PARAMR.
           05  DSEQ-RECVAL.
               10  FILLER              PIC  X(0001)
                                       OCCURS  0 TO   32760
                                       DEPENDING ON   DSEQ-RECLNG.
      *
       01  GWDSEQ1A                    PIC  X(0008) VALUE 'GWDSEQ1A'.
      *
       LINKAGE SECTION.
      *
       01  PARAM-AREA.
           05  PARAM-AREA-LNG          PIC S9(0004) COMP.
           05  PARAM-VALUE.
               10  FILLER              PIC  X(0001)
                                       OCCURS 1 TO 80
                                       DEPENDING ON PARAM-AREA-LNG.
      *
       PROCEDURE DIVISION      USING   PARAM-AREA.
      *----------------------------------------------------------------
      *
       MAIN.

           DISPLAY 'GWTSEQ1R - STARTED'
      *
           INITIALIZE DSEQ-PARAM
           MOVE   'OPEN'               TO  DSEQ-COMMAND
           IF     PARAM-AREA-LNG       EQUAL  0
                  MOVE   'INFILE'      TO  DSEQ-DDNAME
           ELSE
                  MOVE   PARAM-VALUE   TO  DSEQ-DDNAME
           END-IF
           DISPLAY 'GWTSEQ1R - OPEN BEFORE (' DSEQ-DDNAME ')'
           CALL    GWDSEQ1A    USING   DSEQ-PARAM
                                       DSEQ-PARAMR
           DISPLAY 'GWTSEQ1R - OPEN AFTER (' DSEQ-RETCOD ')'
                                         '(' DSEQ-RECLNG ')'
                                         '(' DSEQ-BUFLNG ')'
                                         '(' DSEQ-BLKSIZ ')'
                                         '(' DSEQ-RECFMT ')'
           IF  NOT DSEQ-RETCOD-SUCCESS
                   GO TO ERRORE
           END-IF
      *
           PERFORM UNTIL DSEQ-EOF-YES
      *
               INITIALIZE DSEQ-PARAM
               MOVE   'READ'               TO  DSEQ-COMMAND
               DISPLAY 'GWTSEQ1R - READ BEFORE'
               CALL    GWDSEQ1A    USING   DSEQ-PARAM
                                           DSEQ-PARAMR
               DISPLAY 'GWTSEQ1R - READ AFTER (' DSEQ-RETCOD ')'
                                             '(' DSEQ-RECLNG ')'
                                             '(' DSEQ-EOF ')'
               IF  NOT DSEQ-RETCOD-SUCCESS
                       GO TO ERRORE
               END-IF
               DISPLAY '(' DSEQ-RECVAL ')'
      *
           END-PERFORM
      *
           INITIALIZE DSEQ-PARAM
           MOVE   'CLOSE'              TO  DSEQ-COMMAND
           DISPLAY 'GWTSEQ1R - CLOSE BEFORE'
           CALL    GWDSEQ1A    USING   DSEQ-PARAM
                                       DSEQ-PARAMR
           DISPLAY 'GWTSEQ1R - CLOSE AFTER ' DSEQ-RETCOD
           IF  NOT DSEQ-RETCOD-SUCCESS
                   GO TO ERRORE
           END-IF
      *
           DISPLAY 'GWTSEQ1R - ENDED'
           GOBACK.
      *
       ERRORE.
           DISPLAY 'GWTSEQ1R - ERRORE'
           DISPLAY             '(' DSEQ-RETCOD ')'
           DISPLAY             '(' DSEQ-RETMSG ')'
      *
           STOP    RUN.


[/code]
Back to top
View user's profile Send private message
DavidatK

Active Member


Joined: 22 Nov 2005
Posts: 700
Location: Troy, Michigan USA

PostPosted: Sat Jan 20, 2007 3:15 am
Reply with quote

Gabriele,

Thanks for posting your solution, I'm sure it will generate much discussion and several new threads. icon_biggrin.gif
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Sat Jan 20, 2007 4:23 am
Reply with quote

Hello Gabriele,

Thanks for posting your solution.

Congrats on a quick, solid solution. icon_biggrin.gif
Back to top
View user's profile Send private message
William Thompson

Global Moderator


Joined: 18 Nov 2006
Posts: 3156
Location: Tucson AZ

PostPosted: Sat Jan 20, 2007 5:55 am
Reply with quote

Gabriele,

Gabriele Soranzo wrote:
For William: I was (very) forced in the time, I had read several threads on this topic, but I was not sure that it's definitly impossible reach my goal without Assembler, I didn't wanted violate the rules of this forum (but I think that I have not done it). In every case I appreciate the cooperative approach and I consider that your comment should appears a personal dispute, and I am definitly not interested to do it. I somebody had developed already a solution for me it was welcome. In every case the next time I will be more precise in my requests.
icon_redface.gif I apologize for the flame, The synchronicity of your inquiry and several others just rang my bell. You were right, as was David, assembler is the only way this can be done. You have NOT violated any rules of this forum, sometimes the "planets" just don't align as we wish they would.

Again I am sorry; keep asking and contributing to this forum; everything added is potentially helpful to somebody (providing he/she looks icon_smile.gif )

Bill

BTW, thank you (again) for following up and "closing" the thread. icon_smile.gif
Back to top
View user's profile Send private message
Gabriele Soranzo

New User


Joined: 28 Dec 2006
Posts: 6
Location: Italy, Trieste

PostPosted: Sun Jan 21, 2007 6:48 am
Reply with quote

Hi William,

don't worry...in true also I have criteria for distinguish "coder" and "developer"...just I don't use this forum for describes it ;)...and I understand the relevance of the "planets" !

I hope and I think that we have good benefits using this forum,

Gabriele
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 -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts Store the data for fixed length COBOL Programming 1
No new posts How to split large record length file... DFSORT/ICETOOL 10
No new posts Populate last day of the Month in MMD... SYNCSORT 2
No new posts PARSE Syntax for not fix length word ... JCL & VSAM 7
No new posts Error to read log with rexx CLIST & REXX 11
Search our Forums:

Back to Top