Home Back to 370 Assembler Tips & Tricks Index Links

Mixing 24-Bit and 31-Bit CSECT's in a single load module

In a previous tutorial, I discuss building 31-Bit modules that can load 24-Bit DCB's separately into 24-Bit storage pools, while the 31-Bit CSECT's are loaded into 31-Bit storage pools.

Sometime in July, 2003, I received an email from Ulrich Schauwecker of Zürcher Kantonalbank in Zürich.  Ulrich wrote that he had an alternate technique for addressing 24-Bit load modules from 31-Bit load modules.

With z/OS, one can combine 24-Bit CSECT's with 31-Bit CSECT's in a single load module and let the operating system loader place the CSECT's into 24-Bit and 31-Bit storage pools respectively.

The following outlines all that it necessary to combine 24-Bit and 31-Bit CSECT's in a single load module:

  • Code your 24-Bit CSECT's with a 31-Bit AMODE and 24-Bit RMODE.

  • Code your 31-Bit CSECT's with a 31-Bit AMODE and either a 31-Bit or ANY RMODE.

  • Assemble your module with the combined 31-Bit and 24-Bit CSECT's as you normally would.

  • When you Bind (Link-edit) your module, you must be sure to direct the output load module from the Binder to a PDSE (PDS-Extended).
    In order for the operating system to load the separate CSECT's into the appropriate 24-Bit and 31-Bit storage pools, the load module must reside in a PDSE and you must instruct the Binder to use a SPLIT residency mode: "RMODE(SPLIT)".

Here's a Job-Stream to allocate a PDSE.  Modify it as necessary to suit your environment:


//DEVEL01A JOB (30900001),'Marc Niegowski',NOTIFY=&SYSUID, 
//             CLASS=A,MSGLEVEL=(1,1),MSGCLASS=H 
//*--------------------------------------------------------------------
//*            Job-Stream to allocate a PDSE. 
//*--------------------------------------------------------------------
//         JCLLIB  ORDER=DEVEL01.TSO.CNTL 
//         SET     TITLE='''Allocate PDSE Job''' 
//         INCLUDE MEMBER=OUTPUT01 
//IEFBR14  EXEC PGM=IEFBR14 
//PDSE      DD DSN=DEVEL01.PDSE.SYSLMOD, 
//             DISP=(NEW,CATLG,DELETE), 
//             DSNTYPE=LIBRARY, 
//             DCB=(RECFM=U,DSORG=PO), 
//             SPACE=(TRK,(5,5,0)) 
//*--------------------------------------------------------------------

Notice the DSNTYPE=LIBRARY in the above JCL example.  This defines the Dataset Name Type as Library which creates a PDSE.

The following is a fully functional code example of a program that contains both 24-Bit and 31-Bit CSECT's.  In this example, the DCB's are coded in the same module as a separate 24-Bit CSECT, while the main program code occupies a 31-Bit CSECT.  Notice that the Binder parameters are supplied at the end of the source module via "PUNCH" statements, and in particular, notice the RMODE(SPLIT) Binder control statement.


MIXMODE  TITLE 'Mixed residency (24/31-Bit) module example.'
*---------------------------------------------------------------------*
*        Private code Copyright preamble.                             *
*---------------------------------------------------------------------*
         CSECT ,                   Private Code CSECT.
AMODE    31                        Set 31-Bit Addressing mode.
RMODE    31                        Set 31-Bit Residency mode.
         SPACE , 
         DC    C'Assembly date && time: &SYSDATE &SYSTIME '
         DC    C'Copyright (C) 1993-2004, Marc Niegowski '
         DC    C'Systems Programmer At Large '
         DC    C'All Rights Reserved.'
         SPACE ,
*---------------------------------------------------------------------*
*        Standard DCB resident in 24-Bit storage.                     *
*---------------------------------------------------------------------*
R24MODE  CSECT ,                   Standard DCB CSECT.
R24MODE  AMODE 31                  Set 31-Bit Addressing mode.
R24MODE  RMODE 24                  Set 24-Bit Residency mode.
         SPACE ,
         DC    C'SYSIN DCB Foundation.'
STDSIN   DCB   DDNAME=SYSIN,       Standard SYSIN DD.                  C
               DCBE=STDSIX,        Standard SYSIN DCB extension.       C
               LRECL=80,           80 Char card image.                 C
               DSORG=PS,           Physical sequential organization.   C
               RECFM=F,            Fixed, unblocked.                   C
               MACRF=(GL)          GET macro, locate mode.
         SPACE ,
         DC    C'SYSIN DCB Extension.'
STDSIX   DCBE  RMODE31=BUFF        31-Bit buffer addressing.
         EJECT ,
         DC    C'SYSPRINT DCB Foundation.'
STDSPR   DCB   DDNAME=SYSPRINT,    Standard SYSPRINT DD.               C
               DCBE=STDSPX,        Standard SYSPRINT DCB extension.    C
               LRECL=133,          132 Char lines + 1 byte CC.         C
               DSORG=PS,           Physical sequential organization.   C
               RECFM=FBA,          Fixed, blocked ANSI control chars.  C
               MACRF=(PM)          PUT macro, move mode.
         SPACE ,
         DC    C'SYSPRINT DCB Extension.'
STDSPX   DCBE  RMODE31=BUFF        31-Bit buffer addressing
         EJECT ,
         DC    C'SYSSNAP DCB Foundation.'
STDSNP   DCB   DDNAME=SYSSNAP,     Standard SNAP DD.                   C
               DCBE=STDSNX,        Standard SYSSNAP DCB extension.     C
               LRECL=125,          120 Char lines + CC + RDW.          C
               BLKSIZE=882,        Standard SNAP blocksize.            C
               DSORG=PS,           Physical sequential organization.   C
               RECFM=VBA,          Variable, blocked, ANSI cc's.       C
               MACRF=(W)           WRITE macro.
               SPACE ,
         DC    C'SYSSNAP DCB Extension.'
STDSNX   DCBE  RMODE31=BUFF        31-Bit buffer addressing.
         SPACE ,
         CNOP  0,4                 Fullword alignment.
R24MODX  EQU   *-1                 A(End of module).
         EJECT ,
*---------------------------------------------------------------------*
*        31-Bit resident CSECT to address 24-Bit resident DCB.        *
*---------------------------------------------------------------------*
R31MODE  CSECT ,                   Main CSECT.
R31MODE  AMODE 31                  Set 31-Bit addressing mode.
R31MODE  RMODE 31                  Set 31-Bit residency mode.
         SPACE ,
         ENTRY R31MODE             CSECT entry point.
         BAKR  14,0                Store callers regs to system stack.
         LR    12,15               Load A(CSECT base).
         USING R31MODE,12          Establish CSECT addressability.
         SPACE ,
         STORAGE OBTAIN,           Allocate some working storage...    C
               ADDR=(11),          ...for a register save area ...     C
               LENGTH=WSDL         ...(RSA), Stack, Buffers, etc..
         SPACE ,
         USING WSD,11              Establish WSD addressability.
         LA    2,1(,11)            Load A(Working Storage + 1) to R2.
         LA    3,WSDL-1            Load L'Working Storage - 1 to R3.
         LR    4,11                Load A(Working storage) to R4.
         LA    5,1                 Load 1 to R5.
         MVCL  2,4                 Init working storage to X'00's.
         LA    8,WSDSTACK          Base the stack with R8.
         SPACE ,
         ST    13,WSDR13P          Save A(Prior RSA).
         MVC   WSDR13,=C'F1SA'     Set system stack ID for others.
         LA    13,WSDRSA           Load A(RSA) to R13.
         SPACE ,
         L     3,=A(STDSPR)        Load A(Standard SYSPRINT DCB).
         USING IHADCB,3            Establish DCB addressability.
         BAS   14,R31MOPN          Open SYSPRINT in 31-Bit mode.
         TM    DCBOFLGS,DCBOFOPN   Did SYSPRINT open successfully?
         BNO   R31M500             No, take error exit branch.
         SPACE ,
         L     1,=A(R31MMSG1)      Point R1 to first header line.
         LA    2,L'R31MMSG1        Load Length of header line to R2.
         LA    4,2                 Load number of header lines.
R31M100  DS    0H                  Write sample output to SYSPRINT.
         BAS   14,R31MPUT          Write message header line.
         LA    1,0(2,1)            Index to next header line.
         BCT   4,R31M100           Write next header line.
         SPACE ,
         L     3,=A(STDSIN)        Load A(Standard SYSIN DCB).
         BAS   14,R31MIPN          Open SYSIN in 31-Bit mode.
         TM    DCBOFLGS,DCBOFOPN   Did SYSIN open successfully?
         BNO   R31M500             No, take error exit branch.
         SPACE ,
         L     3,DCBDCBE           Load A(DCBE).
         DROP  3                   Drop DCB.
         USING DCBE,3              Establish DCBE addressability.
         MVC   DCBEEODA,=A(R31M300)          SYSIN EOD address.
         DROP  3                   Drop DCBE.
         L     3,=A(STDSIN)        Load A(Standard SYSIN DCB).
         USING IHADCB,3            Establish DCB addressability.
         LA    2,80                Load input record length to R2.
         SPACE ,
R31M200  DS    0H                  Read SYSIN until EOD.
         GET   (3)                 Read a record from SYSIN.
         L     3,=A(STDSPR)        Load A(SYSPRINT) DCB.
         BAS   14,R31MPUT          Write record to SYSPRINT.
         L     3,=A(STDSIN)        Re-load A(SYSIN) DCB.
         B     R31M200             Continue reading records.
         SPACE ,
R31M300  DS    0H                  SYSIN End of Data (EOD) processing
         BAS   14,R31MCLS          Close SYSIN DCB in 31-Bit mode.
         L     3,=A(STDSPR)        Load A(Standard SYSPRINT DCB).
         BAS   14,R31MCLS          Close SYSPRINT DCB in 31-Bit mode.
         SPACE , 
R31M400  DS    0H                  Snap the 24 and 31-Bit storage.
         L     3,=A(STDSNP)        Load A(Standard SYSSNAP DCB).
         BAS   14,R31MOPN          Open SYSSNAP DCB in 31-Bit mode.
         TM    DCBOFLGS,DCBOFOPN   Did SYSSNAP open successfully?
         BO    R31M600             Yes, take branch.
         SPACE ,
R31M500  DS    0H                  No, open error exit.
         L     15,12               Set RC=12.
         B     R31MXIT             Branch to module exit.
         SPACE ,
R31M600  DS    0H                  Sample snaps.
         L     2,=A(R31MHDL1)      Load A(Snap heading 1).
         L     4,=A(R31MODE)       Load A(R31MODE CSECT).
         L     5,=A(R31MODX)       Load A(End of R31MODE CSECT).
         BAS   14,R31MSNP          Snap 31-Bit CSECT to SYSSNAP.
         SPACE ,
         L     2,=A(R31MHDL2)      Load A(Snap heading 2).
         L     4,=A(R24MODE)       Load A(R24MODE CSECT).
         L     5,=A(R24MODX)       Load A(End of R24MODE CSECT).
         BAS   14,R31MSNP          Snap 24-Bit CSECT to SYSSNAP.
         SPACE ,
         L     2,=A(R31MHDL3)      Load A(Snap heading 3).
         LR    4,11                Load A(WSD) to R4.
         LA    5,WSDL-1(,4)        Load A(End of WSD) to R5.
         BAS   14,R31MSNP          Snap working storage to SYSSNAP.
         SPACE ,
         BAS   14,R31MCLS          Close SYSSNAP in 31-Bit mode.
         SPACE ,
         DROP  3                   Drop IHADCB.
         XR    15,15               Set RC=00.
         SPACE ,
R31MXIT  DS    0H                  Module exit.
         LR    2,15                Save the return code in R2.
         L     13,WSDR13P          Restore original R13.
         DROP  11                  Drop WSD.
         SPACE ,
         STORAGE RELEASE,          Free working storage area (WSD).    C
               ADDR=(11),                                              C
               LENGTH=WSDL
         SPACE ,
         LR    15,2                Restore return code to R15.
         PR                        Return to caller.
         EJECT ,
*---------------------------------------------------------------------*
*        Open a DCB for input.                                        *
*---------------------------------------------------------------------*
         SPACE ,
*        Call with: R3  = A(DCB)
*                   R8  = Stack pointer.
*        Returns:   Nothing.
         SPACE ,
R31MIPN  DS    0H                  Routine entry point.
         ST    14,0(,8)            Store return address to stack.
         LA    8,4(,8)             Increment stack pointer.
         SPACE ,
         OPEN  ((3),INPUT),        Open DCB in 31-Bit mode.            C
               MODE=31
         SPACE ,
R31MIPX  DS    0H                  Routine exit.
         AHI   8,-4                Decrement stack pointer.
         L     14,0(,8)            Restore return address.
         BR    14                  Return to caller.
         EJECT ,
*---------------------------------------------------------------------*
*        Open a DCB for output.                                       *
*---------------------------------------------------------------------*
         SPACE ,
*        Call with: R3  = A(DCB)
*                   R8  = Stack pointer.
*        Returns:   Nothing.
         SPACE ,
R31MOPN  DS    0H                  Routine entry point.
         ST    14,0(,8)            Store return address to stack.
         LA    8,4(,8)             Increment stack pointer.
         SPACE ,
         OPEN  ((3),OUTPUT),       Open DCB in 31-Bit mode.            C
               MODE=31
         SPACE ,
R31MOPX  DS    0H                  Routine exit.
         AHI   8,-4                Decrement stack pointer.
         L     14,0(,8)            Restore return address.
         BR    14                  Return to caller.
         EJECT ,
*---------------------------------------------------------------------*
*        Close a DCB.                                                 *
*---------------------------------------------------------------------*
         SPACE ,
*        Call with: R3  = A(DCB)
*                   R8  = Stack pointer.
*        Returns:   Nothing.
         SPACE ,
R31MCLS  DS    0H                  Routine entry point.
         ST    14,0(,8)            Store return address to stack.
         LA    8,4(,8)             Increment stack pointer.
         SPACE ,
         CLOSE ((3)),              Close DCB in 31-Bit mode.           C
               MODE=31
         SPACE ,
R31MCLX  DS    0H                  Routine exit.
         AHI   8,-4                Decrement stack pointer.
         L     14,0(,8)            Restore return address.
         BR    14                  Return to caller.
         EJECT ,
*---------------------------------------------------------------------*
*        Write a line to SYSPRINT.                                    *
*---------------------------------------------------------------------*
         SPACE ,
*        Call with: R1  = A(Message line to write)
*                   R2  = Length of message line
*                   R3  = A(DCB)
*                   R8  = Stack pointer.
*                   R11 = Working storage (WSD)
*        Returns:   Nothing.
         SPACE ,
R31MPUT  DS    0H                  Routine entry point.
         ST    14,0(,8)            Store return address to stack.
         STM   1,2,4(8)            Save callers R1 & R2 to stack.
         LA    8,12(,8)            Increment stack pointer.
         SPACE ,
         USING WSD,11              Establish WSD addressability.
         SPACE ,
         MVI   WSDMSGB,X'40'       Clear message buffer.
         MVC   WSDMSGB+1(L'WSDMSGB-1),WSDMSGB
         BCTR  2,0                 Decrement message length for MVC.
         EX    2,R31MPMV           Move message text to buffer.
         SPACE ,
         PUT   (3),WSDMSGB         Write line to SYSPRINT DCB.
         SPACE ,
R31MPUX  DS    0H                  Routine exit.
         AHI   8,-12               Decrement stack pointer.
         LM    1,2,4(8)            Restore callers R1 & R2.
         L     14,0(,8)            Restore return address.
         BR    14                  Return to caller.
         SPACE ,
R31MPMV  MVC   WSDMSGB(0),0(1)     MVC from R1 to message buffer.
         SPACE ,
         DROP 11
         EJECT ,
*---------------------------------------------------------------------*
*        Snap dump of storage.                                        *
*---------------------------------------------------------------------*
         SPACE ,
*        Call with: R2  = A(Snap header = 1 byte length + text)
*                   R3  = A(Snap DCB)
*                   R4  = A(Starting address of snap)
*                   R5  = A(Ending address of snap)
*                   R8  = Stack pointer.
*        Returns:   Nothing.
         SPACE ,
R31MSNP  DS    0H                  Routine entry point.
         ST    14,0(,8)            Store return address to stack.
         LA    8,4(,8)             Increment stack pointer.
         SPACE ,
         SNAP  DCB=(3),            Snap working storage to SYSSNAP.    C
               STORAGE=((4),(5)),  Start and end address to dump.      C
               STRHDR=((2)),       Set the snap heading.               C
               PDATA=REGS          Dump the regs also.
         SPACE ,
R31MSNX  DS    0H                  Routine exit.
         AHI   8,-4                Decrement the stack pointer.
         L     14,0(,8)            Restore return address.
         BR    14                  Return to caller.
         EJECT ,
*---------------------------------------------------------------------*
*        Literal pool origin and program constants.                   *
*---------------------------------------------------------------------*
         LTORG ,
         SPACE ,
R31MMSG1 DC    C' Testing mixed residency (24/31-Bit) modules.'
R31MMSG2 DC    C' --------------------------------------------'
R31MHDL1 DC    AL1(L'R31MHDR1)
R31MHDR1 DC    C'Snap of 31-Bit resident portion of module.'
R31MHDL2 DC    AL1(L'R31MHDR2)
R31MHDR2 DC    C'Snap of 24-Bit resident portion of module.'
R31MHDL3 DC    AL1(L'R31MHDR3)
R31MHDR3 DC    C'Snap of working storage area.'
         SPACE ,
         CNOP  0,4                 Fullword alignment.
R31MODX  EQU   *-1                 End of module.
         SPACE ,
         DROP  12                  Drop R31MODE CSECT base.
         EJECT ,
*---------------------------------------------------------------------*
*        Working storage area DSECT.                                  *
*---------------------------------------------------------------------*
WSD      DSECT ,
WSDRSA   DS    18F                 Register save area.
         ORG   WSDRSA+4            Set origin to R13 save word.
WSDR13   DS    F                   R13 save word.
         ORG   ,                   Reset origin.
WSDR13P  DS    F                   Previous R13 save word.
WSDSTACK DS    16F                 Subroutine save stack.
WSDMSGB  DS    CL133               Message buffer.
WSDL     EQU   ((*-WSD+7)/8)*8     Length of DSECT to nearest dblword.
         EJECT ,
*---------------------------------------------------------------------*
*        Generate Physical Sequential DCB DSECT.                      *
*---------------------------------------------------------------------*
         DCBD  DSORG=(PS)          Physical Sequential DCB DSECT.
         EJECT ,
*---------------------------------------------------------------------*
*        Generate DCB Extension DSECT.                                *
*---------------------------------------------------------------------*
         IHADCBE                   DCB Extension DSECT.
         SPACE ,
*---------------------------------------------------------------------*
         END   ,                   End of assembly.
         PUNCH '*Binder option overrides'
         PUNCH ' SETOPT PARM(REUS=SERIAL,EXTATTR(NOAPF,PGM))'
         PUNCH ' SETOPT PARM(GID=DEVEL01,UID=DEVEL01)'
         PUNCH '*Module addressability and residency options'
         PUNCH ' MODE AMODE(31)'       Binder 31-Bit addressing mode.
         PUNCH ' MODE RMODE(SPLIT)'    Binder split residence mode.
         PUNCH ' ENTRY R31MODE'        Binder entry statement.
         PUNCH ' NAME MIXMODE(R)'      Binder module name statement.
         END   ,                   End of Binder/Linkage Editor cards. 

Put it together using the following Assembler and Binder Job-Stream as an example.  Modify the Job-Stream as necessary to suit your environment:


//DEVEL01A JOB (30900001),'Marc Niegowski',NOTIFY=&SYSUID,
//             CLASS=A,MSGLEVEL=(1,1),MSGCLASS=H
//*--------------------------------------------------------------------
//*            HIGH LEVEL ASSEMBLER (HLASM) JOB-STREAM.
//*--------------------------------------------------------------------
//         JCLLIB  ORDER=DEVEL01.TSO.CNTL
//         SET     TITLE='''Assemble and Bind MIXMODE'''
//         INCLUDE MEMBER=OUTPUT01
//ASMA90   EXEC PGM=ASMA90,
//             PARM='NODECK,OBJECT'
//SYSPRINT  DD SYSOUT=*
//SYSLIB    DD DISP=SHR,DSN=SYS1.MACLIB
//          DD DISP=SHR,DSN=SYS1.SISTMAC1
//          DD DISP=SHR,DSN=SYS1.MODGEN
//SYSUT1    DD UNIT=SYSDA,SPACE=(CYL,(1,1))
//SYSLIN    DD DISP=(NEW,PASS),DSN=&OBJECT,
//             SPACE=(CYL,(1,1)),
//             UNIT=SYSDA
//SYSIN     DD DISP=SHR,DSN=DEVEL01.TSO.SRCLIB(MIXMODE)
//*--------------------------------------------------------------------
//* BINDER (LINKAGE EDITOR) JOB-STEP.
//*--------------------------------------------------------------------
//HEWLH096 EXEC PGM=HEWLH096,COND=(0,LT),
//             PARM=('SIZE=(1000K,100K)',NCAL,XREF,LIST,MAP,
//             'MSGLEVEL=8','COMPAT=CURR')
//SYSPRINT  DD SYSOUT=*
//SYSLMOD   DD DISP=SHR,DSN=DEVEL01.PDSE.LOADLIB
//SYSUT1    DD UNIT=SYSDA,SPACE=(6160,(230,760))
//SYSLIN    DD DISP=(OLD,DELETE,DELETE),DSN=&OBJECT
//*--------------------------------------------------------------------

Your assembler and binder output should look something similar to this.

Finally, to execute this MIXMODE tutorial program, you can use the following sample JCL.  Modify the JCL as necessary to suit your environment:


//DEVEL01M JOB (30900001),'Marc Niegowski',NOTIFY=&SYSUID,
//             CLASS=A,MSGLEVEL=(1,1),MSGCLASS=H
//*--------------------------------------------------------------------
//*            TEST MIXED RESIDENCY MODE.
//*--------------------------------------------------------------------
//         JCLLIB  ORDER=DEVEL01.TSO.CNTL
//         SET     TITLE='''MIXMODE Job'''
//         INCLUDE MEMBER=OUTPUT01
//MIXMODE  EXEC PGM=MIXMODE,
//             REGION=12K
//STEPLIB   DD DISP=SHR,DSN=DEVEL01.PDSE.LOADLIB
//SYSPRINT  DD SYSOUT=*
//SYSMDUMP  DD DISP=(NEW,DELETE,CATLG),DSN=&SYSUID..MIXMODE.DUMP,
//             DATACLAS=(DUMP),STORCLAS=(DEFAULT)
//SYSSNAP   DD SYSOUT=*
//*            First byte of SYSIN records is ASA character.
//SYSIN     DD *
0All work and no play makes Jack a dull boy.
  All work and no play makes Jack a dull boy.
   All wrok and no play makes Jack a dull boy.
    All work and no pray makes Jack a dull boy.
     All wrok adn no pay makes Jock a dull boy.
    All work and no olay maeks Jack a dull boy.
   All sork adn on pay makes Jake a dull boy.
  All work and no play makes Jack a dull boy.
 All work and no play makes Jack a dull boy.
  All work and no play makes Jack a dull boy.
   All wrok and no play makes Jack a dull boy.
    All work and no pray makes Jack a dull boy.
     All wrok adn no pay makes Jock a dull boy.
    All work and no olay maeks Jack a dull boy.
   All sork adn on pay makes Jake a dull boy.
  All work and no play makes Jack a dull boy.
 All work and no play makes Jack a dull boy.
  All work and no play makes Jack a dull boy.
   All wrok and no play makes Jack a dull boy.
    All work and no pray makes Jack a dull boy.
     All wrok adn no pay makes Jock a dull boy.
    All work and no olay maeks Jack a dull boy.
   All sork adn on pay makes Jake a dull boy.
  All work and no play makes Jack a dull boy.
 All work and no play makes Jack a dull boy.
  All work and no play makes Jack a dull boy.
   All wrok and no play makes Jack a dull boy.
    All work and no pray makes Jack a dull boy.
     All wrok adn no pay makes Jock a dull boy.
    All work and no olay maeks Jack a dull boy.
   All sork adn on pay makes Jake a dull boy.
  All work and no play makes Jack a dull boy.
 All work and no play makes Jack a dull boy.
  All work and no play makes Jack a dull boy.
   All wrok and no play makes Jack a dull boy.
    All work and no pray makes Jack a dull boy.
     All wrok adn no pay makes Jock a dull boy.
    All work and no olay maeks Jack a dull boy.
   All sork adn on pay makes Jake a dull boy.
  All work and no play makes Jack a dull boy.
 All work and no play makes Jack a dull boy.
  All work and no play makes Jack a dull boy.
   All wrok and no play makes Jack a dull boy.
    All work and no pray makes Jack a dull boy.
     All wrok adn no pay makes Jock a dull boy.
    All work and no olay maeks Jack a dull boy.
   All sork adn on pay makes Jake a dull boy.
  All work and no play makes Jack a dull boy.
 All work and no play makes Jack a dull boy.
  All work and no play makes Jack a dull boy.
   All wrok and no play makes Jack a dull boy.
    All work and no pray makes Jack a dull boy.
     All wrok adn no pay makes Jock a dull boy.
    All work and no olay maeks Jack a dull boy.
   All sork adn on pay makes Jake a dull boy.
  All work and no play makes Jack a dull boy.
 All work and no play makes Jack a dull boy.
  All work and no play makes Jack a dull boy.
   All wrok and no play makes Jack a dull boy.
    All work and no pray makes Jack a dull boy.
     All wrok adn no pay makes Jock a dull boy.
    All work and no olay maeks Jack a dull boy.
   All sork adn on pay makes Jake a dull boy.
  All work and no play makes Jack a dull boy.
 All work and no play makes Jack a dull boy.
  All work and no play makes Jack a dull boy.
   All wrok and no play makes Jack a dull boy.
    All work and no pray makes Jack a dull boy.
     All wrok adn no pay makes Jock a dull boy.
    All work and no olay maeks Jack a dull boy.
   All sork adn on pay makes Jake a dull boy.
  All work and no play makes Jack a dull boy.
 All work and no play makes Jack a dull boy.
  All work and no play makes Jack a dull boy.
   All wrok and no play makes Jack a dull boy.
    All work and no pray makes Jack a dull boy.
     All wrok adn no pay makes Jock a dull boy.
    All work and no olay maeks Jack a dull boy.
   All sork adn on pay makes Jake a dull boy.
  All work and no play makes Jack a dull boy.
//*--------------------------------------------------------------------

The above MIXMODE Job-Stream should produce output similar to this.  Pay particular attention to the snap dump section of the output.  Here you can clearly see that your DCB CSECT was loaded into a 24-Bit storage pool, while the main module CSECT was loaded into a 31-Bit storage pool.

If you wish to experiment with the files in this tutorial and would rather download the samples than cut and paste them from this page, you can download the mixmode.samples.pds.xmit.zip file.  Unzip this file and send it to your host TSO session using your favorite transmission method (IND$FILE, for example) using a record length of 80 and a record format of fixed (or fixed blocked as long as the blocksize is a multiple of the record length).

Next you need to RECEIVE the file under TSO as follows:

  • Enter "RECEIVE INDS(mixmode.samples.pds.xmit)" without the quotes, either at a TSO prompt or ISPF option 6.

  • Once you receive the "INMR906A Enter restore parameters or 'DELETE' or 'END' +" message
    Enter "da(whatever.name.you.choose)" without the quotes.

  • TSO Receive will produce message indicating the progress of the receive and when finished, you will have a PDS named "youruserid.whatever.name.you.choose" containing all of the samples in this tutorial.

Thank you Ulrich Schauwecker for providing me with the idea for this tutorial.

I will continue to add tips and techniques as time permits.

Please direct any inquiries or problems regarding this web to webmaster@marcsweb.com


Page design, composition and HTML by Marc Niegowski
Copyright © 1998-2012, Marc Niegowski - Connectivity, Inc., All Rights Reserved
23 W. Fourth Street • Media • Pennsylvania • 19063-2805 • USA
Phone: 610-566-0227 • Fax: 610-566-0641 • Email: Marc@Tech-Center.com

Revision Date: Wednesday, November 15, 2006 10:03:13 AM