Skip to content
The Punctilious Programmer

Learn IBM Assemb;y Lsnhushr

woolbright_david@icloud.comwoolbright_david@icloud.com
  • IBM Mainframe Assembler
  • The Video Course
  • Course Datasets
  • Test Bank
  • The Big Blue Assembler Book
  • Visiblez Home Page
  • IBM Enterprise COBOL
  • Punctilious Publishing
  • Advanced Assembler Class
Close Menu
The Punctilious Programmer Advanced Assembler Class

Advanced Assembler Class

Week 1

1) Passing a variable number of parameters

2) Working with Bits (Part 1)

4) Read Chapter 37. Subroutines and Linkage Conventions in Assembly Language Programming for IBM System z Servers by John Ehrman.

3) Working with Bits (Part 2)

5) Program Management 

6) Playing With Control – XCTL and LINK

7) Write Program 1 that computes a Greatest Common Divisor using the following algorithm. Greatest Common Divisor Computation for A and B

  1. Let rem =  remainder of dividing the larger number by the smaller number
  2. Replace the larger number with rem
  3. Stop if A or B = 0, print A + B.  Otherwise go to step 1

Example          A             B

                      84            24

                      12            24

                      12              0           GCD = 12 + 0 = 12        

Read a file of records, GCDDATA, with two integers per record stored in a character/zoned-decimal format.

Columns 1-4 – integer 1

Columns 5-8 – integer 2

Print each integer and the GCD of the pair.  Use Packed Decimal computations. Print one record for each record in the input file

8) Write Program 2 that converts the program in Program 1 to a subroutine called GCDSUB. It is designed to be passed three integer variables, X, Y, and Z. X and Y are two integers. The GCD of X and Y is computed and passed back through Z.

Write a main program that reads GCDDATA and calls GCDSUB to compute the GCD of X and Y.

As before, print a report with X, Y, and the GCD of X and Y.

9) Write Program 3 that computes a montly payment (simple interest) given a loan amount, a yearly rate (monthly rate = yearly rate/12), and a number of years.

Compute a payment using the following formula:

P = r (PV) / (1 – (1/(1+r)n))

P = payment   (Euros and cents)

r = monthly rate as a %

PV = Present Value of the loan

n = number of months

Keep at least 6 decimal places of accuracy

Xn requires n – 1 multiplications in a loop

Read the file PAYMENT (all data in character format)

Cols 1-6 PV in Euros    (100000 = €100000.00)

Cols 7-11 Rate r as %   (10000 = 10% = .10000)

Cols 12-13 Number of years

For each line in the file, print the PV, rate, number of years, monthly payment 

Use SNAP dump for debugging

Consider writing the payment calculation as a subroutine.

Week 2

  1. Labeled (Named) USINGs (MP4)
  2. Reading Object Code Lesson (PDF) – We examine 6 instruction formats – five that were part of the original architecture (SS1, SS2, SI, RX, RS) and one newer one (RI).
  3. Base Displacement Addressing Lesson (PDF)
  4. Relative Addressing Lesson (PDF)
  5. Set Program Mask (PDF)
  6. Dependent and Labeled Dependent USINGs (PPT)
  7. Dependent and Labeled Dependent USINGs (MP4)
  8. Automation Topic (MP4)  
  9. Grande Instruction Video (MP4)
  10. Grande Instruction Powerpoints (PPT)
  11. Visual Prompts for Grande Division (PDF)
  12. Visual Prompts for Grande Addition (PDF)
  13. Visual Prompts for Grande Subtraction  (PDF)
  14. Visual Prompts for Grande Multiplication (PDF)
  15. Visual Prompts Video (MP4)
  16. Grande Instruction Video (MP4)
  17. Grande Instruction Powerpoints (PPT)
  18. Write Program 4 described below.

Program 4

Rewrite the GCD subprogram using Grande Arithmetic instructions. Keep the same interface for the main program. In other words, pass and return packed decimal integers. Link the GCD with your main program. Use the same data as before.

Week 3

  1. Processing Variable-length Data (MP4) Updated Mar 29, 2017
  2. Reading and Writing V or VB Records (MP4)
  3. Write Program 5 described below.
  4. Reentrant Skeleton Program  (MP4)
  5. Reentrant Program Video  (MP4)
  6. Reentrant Program (PPT)
  7. External Dummy Sections (MP4)  
  8. External Dummy Sections (PPTX)
  9. External Dummy Section Code – PROGP listed below,
//KC02486A JOB (KC024861),'WOOLBRIGHT',REGION=3M,CLASS=A,MSGCLASS=H,
// NOTIFY=&SYSUID,MSGLEVEL=(1,1)
//STEP1 EXEC PROC=HLASMCL,PARM.L='MAP,XREF,LIST,CALL'
//C.SYSIN DD *
PRINT ON,NODATA,NOGEN
**********************************************************************
********************** STORAGE FOR ASECT ****************************
**********************************************************************
ASTOR DSECT
A1 DS CL80 SOME VARIABLES FOR ASECT
A2 DS CL30
A3 DS CL5
A4 DS PL10
A5 DS 200CL5
SAVEA DS 18F AREA FOR MY CALLEE TO SAVE & RESTORE MY REGS
**********************************************************************
********************** STORAGE FOR PARMS ****************************
**********************************************************************
PARMSECT DSECT
X DS CL80
Y DS CL80
Z DS CL80
**********************************************************************
********************** ASECT CONTROL SECTION ***********************
**********************************************************************
ASECT CSECT
ASECT AMODE 31
ASECT RMODE 24
********************** ENTRY LOGIC *********************************
STM 14,12,12(R13) SAVE CALLER'S REGS
BASR R12,0 ESTABLISH
USING *,R12 ADDRESSABILITY
L R8,EDSLEN GRAB LENGTH OF STORAGE NEEDED
STORAGE OBTAIN,LENGTH=(R8),ADDR=(R11)
LR R10,R11 GRAB ADDRESS FOR ALL STORAGE
A R10,ASECTO ADD OFFSET FOR MY DSECT
USING ASTOR,R10 I HAVE ADDRESSABILITY
ST R13,SAVEA+4 BACK-CHAIN CALLER'S FROM MINE
LA R13,SAVEA POINT TO MY LOWER-LEVEL SA
********************** BEGIN LOGIC *********************************
OPEN (FILEOUT,(OUTPUT))
PUT FILEOUT,=CL80'ENTERING PROGASECT'
LR R9,R11 POINT AT DYNAMIC STORAGE
A R9,PARMO ADD THE OFFSET FOR PARMS
USING PARMSECT,R9 I HAVE ADDRESSABILITY
MVC X,=CL80'THIS IS PARM X' INITIALIZE ...
MVC Y,=CL80'THIS IS PARM Y' ... PARMS
MVC Z,=CL80'THIS IS PARM Z'
LA R1,=A(FILEOUT,PARMO) PASS THE DCB AND PARMO
L R15,=A(BSECT) CALLING BSECT
BASR R14,R15 BRANCH THERE
PUT FILEOUT,=CL80'RETURNED TO PROGA1'
LR R9,R11 POINT AT ALLOCATED STORAGE
A R9,XXXAO ADD THE OFFSET TO XXX
PUT FILEOUT,0(R9) R9 POINTS AT XXX
CLOSE FILEOUT
STORAGE RELEASE,LENGTH=(R8),ADDR=(R11)
*********************** STARDARD EXIT ********************************
RETURN EQU * BRANCH TO HERE FOR NORMAL RETURN
L R13,SAVEA+4 POINT TO CALLER'S SAVE AREA
LM R14,R12,12(R13) RESTORE CALLER'S REGS
LA R15,0 SET RETURN CODE REG 15 = 0
BR R14
****************** LOCAL DATA AREAS ********************************
FILEOUT DCB DSORG=PS, X
MACRF=(PM), X
DEVD=DA, X
DDNAME=FILEOUT, X
RECFM=FB, X
LRECL=80
ASECTO DC Q(ASTOR) OFFSET TO ASTOR
PARMO DC Q(PARMSECT) OFFSET TO PARMSECT
XXX DXD CL80 DECLARATION OF XXX IN EDS
XXXAO DC Q(XXX) OFFSET TO XXX
EDSLEN CXD FULLWORD TOTAL SPACE NEEDED
LTORG
YREGS

**********************************************************************
********************** STORAGE FOR BSECT ****************************
**********************************************************************
BSTOR DSECT
B1 DS F THE STORAGE AREAS NEEDED IN BSECT
B2 DS CL20
B3 DS PL5
B4 DS CL100
B5 DS CL5
SAVEB DS 18F BSECT SAVE AREA
**********************************************************************
********************** BSECT CONTROL SECTION ************************
**********************************************************************
BSECT CSECT
STM 14,12,12(R13) SAVE CALLER'S REGS
BASR R12,0 ESTABLISH
USING *,R12 ADDRESSABILITY
LR R10,R11 SET UP...
A R10,BSECTO ... ADDRESSABILITY FOR BSECT
USING BSTOR,R10 I HAVE STORAGE ADDRESSABILITY
LR R9,R11 POINT AT ALLOCATED MEMORY
L R6,4(R0,R1) R6 POINTS AT PARMO
A R9,0(R0,R6) ADD THE OFFSET FOR PARMS
USING PARMSECT,R9 I HAVE PARM ADDRESSABILITY
ST R13,SAVEB+4
LA R13,SAVEB
********************** BEGIN LOGIC *********************************
L R5,0(R0,R1) R5 POINTS AT MY RECOUT DCB
PUT (R5),=CL80'ENTERED BSECT'
PUT (R5),X PRINT THE PARMS
PUT (R5),Y
PUT (R5),Z
*
* USE BSTOR FIELDS CAN BE USED HERE
*
MVC B4,=CL80'THIS IS B4 DATA'
PUT (R5),B4
*
* PREPARE TO USE XXX
*
LR R9,R11 POINT AT XDS WITH R9
A R9,XXXBO ADD THE OFFSET TO XXX
MVC 0(80,R9),=CL80'XXX IN ASECT WAS CHANGED IN BSECT'
*
PUT (R5),=CL80'ABOUT TO LEAVE BSECT'
*********************** STARDARD EXIT ********************************
L R13,SAVEB+4 STANDARD EXIT CODE
LM R14,R12,12(R13)
BR R14
************* INITIALIZED DATA AREAS AND PARMS ***********************
BSECTO DS Q(BSTOR) OFFSET FOR BSECT STORAGE
XXXBO DC Q(XXX) OFFSET TO XXX
LTORG
END ASECT
/*
//L.SYSLMOD DD DSN=KC02486.ASM.LOAD,DISP=SHR
//L.SYSLIB DD DSN=KC02486.ASM.LOAD,DISP=SHR
//L.SYSIN DD *
NAME PROGP(R)
/*
//

Program 5

Write a program that prints the parm data it is passed through JCL.   Run the program three times with these JCL EXEC statements:

//COND00A EXEC PGM=JCLCONC1,PARM=‘THE’

//COND00B EXEC PGM=JCLCONC1,PARM=‘THE MESSAGE‘

//COND00C EXEC PGM=JCLCONC1,PARM=‘ABCDEFGHIJKLMNOPQRSTUVWXYZ’

Program 6

Write a program that reads and writes 40-byte records in locate mode. The first byte of each record is a code consisting of a character A, B, or C. The rest of each record is a 79-byte field. Use a single DSECT and a named-USING that allows you to filter out all the C records. Use this data for input.

A012345678910234567890123456789012345678
BXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX
CYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYY
A012345678910234567890123456789012345678
BXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX
CYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYY
A012345678910234567890123456789012345678
BXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX
CYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYY
A012345678910234567890123456789012345678
BXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX
CYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYYY

Week 4

  1. Reentrant Skeleton Program  (MP4)
  2. Reentrant Program Video  (MP4)
  3. Reentrant Program (PPT)
  4. Going Reentrant (PDF)
  5. Program 7: Take the first program that computed the GCD of two integers and convert it to a reentrant program.
  6. Translate and Translate and Test (MP4)
  7. Debugging Session BOMB1 (MP4)
  8. Debugging Session BOMB2 (MP4)
  9. Writing a Simple Macro (MP4)
  10. Introduction to Conditional Assembly and Macro Writing (MP4) (PPT)
  11. Conditional Assembly and Macro Writing Part 2 (MP4)
  12. Try you hand at writing a macro (ungraded) (PDF)
  13. Building TR Tables (MP4) (PPT)
  14. Processing Variable-length Data (MP4)
  15. Reading and Writing V or VB Records (MP4)
  16. Programming Assignments #7 and #8
  1. • Program 8: Read the file  DATA6 (member in your pds) which has records in the following format:
  2. • Cols 1-2 Length in Character format
  3. • Cols 3-80 Data
  4. • Write a program with reads the file as 80 byte records and writes out a V or VB file using the  length of each record to determine how much data to write
  5. •  Program 9 : Read the file VB file you produced in Program 8.
  6. •  Print each record using the length that is delivered in the RDW

Week 5

  1. Lots of Code On One Base Register (MP4)
  2. Lots of Code On One Base Register Program (This program is called RELATIVE in ZXP.DEW.ASM.JCL
  3. LARL (PPT)
  4. LARL (MP4)
  5. The Linkage Stack (BAKR and PR) (PPTX)
  6. The Linkage Stack (MP4)
  7. Using CPOOL to Create a Stack (PPTX)
  8. The Sample CPOOL Program Listed below and in ZXP.DEW.ASM.JCL
  9. Using CPOOL to Create a Stack (MP4)
  10. Program 10. Write a program that uses TR to translate records. Letters are translated to lowercase. All other symbols are translated to #’s. Read the file ZXP.DEW.DATA(DATA10) and print each record before and after translation.
  11. Program 11. Write a program that uses TRT for searching. Read the file ZXP.DEW.DATA(DATA11). Each record has a last name and a first name separated by a comma. The first name ends in #. Read each record and print each name in first name last name order.

//DEWASMA  JOB 9,NOTIFY=&SYSUID
//ASM      EXEC PGM=ASMA90
//SYSLIB   DD   DSN=SYS1.MACLIB,DISP=SHR
//SYSUT1   DD   DSN=&&SYSUT1,SPACE=(4096,(120,120),,,ROUND),
//             DCB=BUFNO=1,UNIT=SYSALLDA
//SYSPRINT DD   SYSOUT=*
//SYSLIN   DD   DSN=&&OBJ,SPACE=(3040,(40,40),,,ROUND),UNIT=SYSALLDA,
//             DISP=(MOD,PASS),
//             DCB=(BLKSIZE=3040,LRECL=80,RECFM=FBS,BUFNO=1)
//SYSIN    DD   *
         TITLE  'SKELETON ASSEMBLER PROGRAM'
         PRINT  ON,DATA,NOGEN
         AMODE   31
         RMODE   ANY
         SYSSTATE OSREL=SYSSTATE
******************************************************************
*                                                                *
*   PROGRAMMER:  WOOLBRIGHT                                      *
*   COMMENTS  :  STACK PROGRAM                                   *
*                                                                *
******************************************************************
             YREGS
******************************************************************
*                                                                *
*     STACK ITEM DSECT                                           *
*                                                                *
******************************************************************
ITEM         DSECT
ITEMREC      DS   0CL48       STACK ITEM LAYOUT
ITEMNEXT     DS    A          POINTER TO NEXT STACK ITEM
ITEMLNAME    DS    CL20       LAST NAME
ITEMFNAME    DS    CL20       FIRST NAME
ITEMAGE      DS    CL4        AGE
ITEMSIZE     EQU   *-ITEMREC
******************************************************************
*                                                                *
*     MAIN PROGRAM                                               *
*                                                                *
******************************************************************
STACK    CSECT                         STANDARD ENTRY CODE
         BAKR  R14,R0                  SAVE REGS AND RETURN ADDR
         BASR  R12,R0                  ESTABLISH...
         USING *,R12                   ADDRESSABILITY
         USING ITEM,R5                 R5 CONTROLS STACK DSECT
******************************************************************
* BEGIN THE PROGRAM LOGIC. FIRST OPEN THE INPUT AND OUTPUT FILES
******************************************************************
         OPEN  (FILEOUT1,(OUTPUT))
         OPEN  (FILEIN1,(INPUT))
         CPOOL BUILD,                  GET STORAGE FOR A STACK         X
               PCELLCT=100,            INITIAL NO OF CELLS             X
               SCELLCT=100,            SECONDARY NO OF CELLS           X
               CSIZE=ITEMSIZE,         CELL SIZE                       X
               SP=2,                   SUBPOOL NO                      X
               CPID=(R3)               SUBPOOL ID
         GET   FILEIN1,RECIN           GET THE FIRST RECORD, IF THERE
*
*        READ AND PRINT LOOP
*
LOOP     EQU   *
         MVC   LNAMEO,LNAMEI           FORMAT...
         MVC   FNAMEO,FNAMEI           ... THE OUTPUT RECORD
         MVC   AGEO,AGEI               ... WITH INPUT DATA
         PUT   FILEOUT1,RECOUT         WRITE THE RECORD
         MVC   STKLNAME,LNAMEI         STAGE DATA...
         MVC   STKFNAME,FNAMEI         TO BE WRITTEN
         MVC   STKAGE,AGEI             ... TO THE STACK
         JAS   R8,PUSH                 PUSH THE STACK RECORD
         GET   FILEIN1,RECIN           GET THE NEXT RECORD
         J     LOOP                    GO BACK AND PROCESS
*
*        END OF INPUT PROCESSING
*        1) EMPTY AND PRINT THE STACK
*        2) CLOSE THE FILES
*
EXIT     EQU   *
         CLOSE (FILEIN1)
         PUT   FILEOUT1,=CL80'******** PRINTING THE STACK ********'
STKLOOP  EQU   *
         ZAP   STKCNT,STKCNT           IS THE STACK EMPTY?
         JZ    STKEMPTY                ...YES, TAKE THE JUMP
         JAS   R8,POP                  ...NO, PROCESS NEXT ITEM
         LTR   R15,R15                 GOT AN ITEM?
         JNZ   POPERR                  ...NO, THAT'S A PROBLEM
         MVC   LNAMEO,STKLNAME         ...YES, GRAB THE DATA...
         MVC   FNAMEO,STKFNAME         OFF THE STACK
         MVC   AGEO,STKAGE
         PUT   FILEOUT1,RECOUT         PRINT A STACK RECORD
         J     STKLOOP                 TRY AGAIN
POPERR   EQU   *
         PUT   FILEOUT1,=CL80' YOU POPPED AN EMPTY STACK...'
STKEMPTY EQU   *
         CPOOL DELETE,                 RETURN THE SPACE                X
               CPID=(R3)               SUBPOOL ID
         CLOSE (FILEOUT1)              NO MORE OUTPUT
         LA    R15,0                   RETURN CODE = 0
         PR                            ... ALL DONE
******************************************************************
*
*    PUSH STACK ...
*
******************************************************************
PUSH     EQU   *
         CPOOL GET,                                                    X
               UNCOND,                 ABEND IF NOT AVAILABLE          X
               CELL=(R5),              R5 POINTS AT NEW CELL           X
               CPID=(R3)               SUBPOOL ID
         MVC   ITEMLNAME,STKLNAME      MOVE STACK DATA
         MVC   ITEMFNAME,STKFNAME      ... TO THE NEW ITEM
         MVC   ITEMAGE,STKAGE          ... ON THE STACK
         AP    STKCNT,=P'1'            BUMP RECORD COUNT
         CP    STKCNT,=P'1'            WAS THE STACK EMPTY?
         JE    PSHEMPTY                IF YES, TAKE THE BRANCH
         L     R6,STKTOP               GRAB PTR TO TOP OF STACK
         ST    R6,ITEMNEXT             MAKE NEW ITEM POINT AT IT
         ST    R5,STKTOP               NEW ITEM PUT AT TOP OF STACK
         J     PUSHEXIT                LET'S GET OUT
PSHEMPTY EQU   *                       ADD THE NEW ITEM
         MVC   ITEMNEXT,=F'0'          MARK AS BOTTOM OF STACK
         ST    R5,STKTOP               ... AT THE TOP OF THE STACK
PUSHEXIT EQU   *
         BR    R8
******************************************************************
*
*    POP STACK ...
*
******************************************************************
POP      EQU   *
         CP    STKCNT,=P'0'           IS THE STACK EMPTY?
         JE    POPEMPTY               IF YES, TAKE THE BRANCH
         SP    STKCNT,=P'1'           ABOUT TO BE ONE LESS ITEM
         L     R5,STKTOP              DROP DSECT ON TOP ITEM
         MVC   STKLNAME,ITEMLNAME     SAVE THE ITEM DATA...
         MVC   STKFNAME,ITEMFNAME     IN THE STACK AREA
         MVC   STKAGE,ITEMAGE
         L     R6,ITEMNEXT            GRAB NEXT ITEM ADDR UNDER THIS
         ST    R6,STKTOP              ...THAT BECOMES TOP OF STACK
         CPOOL FREE,                  RETURN THE ITEM SPACE            X
               CELL=(R5),             R5 POINTS AT NEW CELL            X
               CPID=(R3)              SUBPOOL ID
         LA    R15,0                  SET GOOD RETURN CODE
         J     POPEXIT                LET'S LEAVE
POPEMPTY EQU   *                      ADD THE NEW ITEM
         XC    STKREC,STKREC          BINARY 0'S IN THE STKREC
         LA    R15,8                  SET BAD RETURN CODE
POPEXIT  EQU   *
         BR    R8                     LEAVING POP ROUTINE
******************************************************************
*
*    STACK DATA ...
*
******************************************************************
         DS    0F
STKTOP   DC    F'0'                   INITALLY EMPTY STACK
STKCNT   DC    PL3'0'                 STACK COUNT
STKREC   DS   0CL44                   STACK RECORD AREA
STKLNAME DS    CL20                   LAST NAME
STKFNAME DS    CL20                   FIRST NAME
STKAGE   DS    CL4                    AGE
******************************************************************
*                                                                *
*     OUTPUT FILE - DATA CONTROL BLOCK                           *
*                                                                *
******************************************************************
               DC X'FFFFFFFF'
FILEOUT1 DCB   DSORG=PS,                                               X
               MACRF=(PM),                                             X
               DEVD=DA,                                                X
               DDNAME=FILEOUT1,                                        X
               RECFM=FB,                                               X
               LRECL=80
******************************************************************
*                                                                *
*     INPUT FILE - DATA CONTROL BLOCK                           *
*                                                                *
******************************************************************
               DC X'FFFFFFFF'
FILEIN1  DCB   DSORG=PS,                                               X
               MACRF=(GM),                                             X
               DEVD=DA,                                                X
               DDNAME=FILEIN1,                                         X
               EODAD=EXIT,                                             X
               RECFM=FB,                                               X
               LRECL=80
******************************************************************
*
*    INPUT RECORD AREA
*
******************************************************************
RECIN    DS   0CL80
LNAMEI   DS    CL20
FNAMEI   DS    CL20
AGEI     DS    CL4
         DS    CL36
******************************************************************
*
*    OUTPUT RECORD AREA
*
******************************************************************
RECOUT   DS   0CL80               PRINT AREA
LNAMEO   DS    CL20
         DC    CL1' '
FNAMEO   DS    CL20
         DC    CL1' '
AGEO     DS    CL4
         DC    CL34' '
******************************************************************
*
*    LITERAL POOL
*
******************************************************************
         LTORG *
         END   STACK
/*
// IF (ASM.RC LE 4) THEN
//LINK       EXEC PGM=HEWL,PARM='MAP,LET,LIST,NCAL'
//SYSPRINT   DD   SYSOUT=*
//SYSLIN     DD   DSN=&&OBJ,DISP=(MOD,PASS)
//           DD *
  NAME STACK(R)
/*
//SYSLMOD    DD DSN=KCXXXXX.ASM.LOAD,DISP=SHR
// ENDIF
// IF (LINK.RC LE 4) THEN
//GO         EXEC PGM=STACK
//STEPLIB    DD DSN=KCXXXXX.ASM.LOAD,DISP=SHR
//SYSABOUT   DD SYSOUT=*
//SYSUDUMP   DD SYSOUT=*
//PRINTER    DD SYSOUT=*
//FILEIN1    DD *
SMITH               RICHARD             0035
JONES               SALLY               0045
FRANKLIN            BONNIE              0078
BROWN               JOHN                0065
MACSHANE            IAN                 0072
ROGERS              FRED                0088
/*
//FILEOUT1  DD  SYSOUT=*
// ENDIF
//

Week 6

  1. Intro to VSAM for Assembler Programmers (Part 1) (PPT)
  2. Intro to VSAM for Assembler Programmers (Part 2) (PPT)
  3. Intro to VSAM for Assembler Programmers (Part 1) (MP4)
  4. Intro to VSAM for Assembler Programmers (Part 2) (MP4)
  5. VSAM Lecture (MP4)
  6. The ACB’s of VSAM (PDF)
  7. Program 12 – Read file ZXP.DEW.DATA(DATA12) which is a collection of 80-byte records. It has a five-byte key (part number) in columns 1-5, a part name in columns 10-29, and a quantity field (zoned decimal) in columns 30-34. Create a VSAM KSDS cluster using JCL (file name here). Read each record and write it to the cluster.
  8. Program 13 – Read file ZXP.DEW.DATA(DATA13) which is a random collection of part number keys. There is a key in columns 1-5. For each key in the file, print the key, the part name, and the quantity.

Week 7

  1. A discussion of MAIN and SUBX programs is below (MP4).
  2. Main – A program that has AMODE 31, RMODE 24, and calls a SUBX that switches to 64-bit addressing.
  3. SUBX – A program that switches to AMODE 64 and allocates storage above the bar.
  4. Program 14 – Modify SUBX so that it has a Modify routine that is passed a record number and 76 bytes of data. The routine writes the data to the existing record. Assume the record number is valid. Modify the MAIN routine so that it can test your changes.

Week 8

  • z/OS Language Environment (PDF)
  • Recovering with ESPIE (PDF)

Share this:

  • Click to share on X (Opens in new window) X
  • Click to share on Facebook (Opens in new window) Facebook
  • Click to share on LinkedIn (Opens in new window) LinkedIn
  • Click to email a link to a friend (Opens in new window) Email

Like this:

Like Loading...

Calendar

December 2025
M T W T F S S
1234567
891011121314
15161718192021
22232425262728
293031  
« Nov    

Categories

  • Fans of IBM z
  • IBM Champion
  • IBM DB2
  • IBM Enterprise Cobol
  • IBM Mainframe Assembler
  • My Books
  • VSAM

Search

Meta

  • Log in

Advance Training Academy WordPress Theme By Themeshopy

Go to mobile version
%d