0% found this document useful (0 votes)
304 views116 pages

Churchil Assembler

The document provides an introduction to assembly language programming on IBM mainframes. It discusses basic concepts like the IBM 370 machine architecture, instruction formats, types of instructions including machine instructions, assembler directives and macros. It describes different instruction fields, register types, addressing modes and operand types. The document is a reference for assembly language programming and provides details on instructions, assembler statements and programming techniques.

Uploaded by

Saravanan Bhojan
Copyright
© Attribution Non-Commercial (BY-NC)
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as PDF, TXT or read online on Scribd
0% found this document useful (0 votes)
304 views116 pages

Churchil Assembler

The document provides an introduction to assembly language programming on IBM mainframes. It discusses basic concepts like the IBM 370 machine architecture, instruction formats, types of instructions including machine instructions, assembler directives and macros. It describes different instruction fields, register types, addressing modes and operand types. The document is a reference for assembly language programming and provides details on instructions, assembler statements and programming techniques.

Uploaded by

Saravanan Bhojan
Copyright
© Attribution Non-Commercial (BY-NC)
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as PDF, TXT or read online on Scribd
You are on page 1/ 116

ASSEMBLY LANGUAGE - 25/09/2004

1 / 116

ASSEMBLY LANGUAGE

ASSEMBLY LANGUAGE - 25/09/2004

2 / 116

CONTENTS 1. Introduction 2. Basic Concepts 3. Instructions 4. Symbols, literals, expressions, Constants and data areas, location counter 5. Integer operations 6. Decimal operations 7. Data transfer and Logical operations 8. Bit manipulations 9. Branching 10. Assembler Directives 11. JCL aspects 12. Subroutines, linkage 24 bit mode 13. Macros and conditional assembly 14. MVS system Macros 15. VSAM Macros 16. Linkage Conventions, 24 & 31 bit addressing, mixed mode addressing issues 17. Mixed Mode Programming using COBOL and Assembler.

ASSEMBLY LANGUAGE - 25/09/2004

3 / 116

INTRODUCTION
What is Assembly Language Lowest-level of programming on a system Symbolic forms of representing machine language instructions Usually represents a single machine instruction Machine dependent Advantages over high-level language Very efficient and tight code can be developed Disadvantages

back

Applications development time is more Applications are machine dependent Relatively more difficult to learn and understand than a high level Language Advantages over machine language Use of mnemonic operation codes helps remembering the instructions Symbols can be used to represent variables and constants Macros can be used to generate repeated codes Conditional assembly enables tailoring the code generated

ASSEMBLY LANGUAGE - 25/09/2004

4 / 116

BASIC CONCEPTS
IBM-370 MACHINE ARCHITECTURE

back

Main storage Addressed by 24 bits or 31 bits One single address space contains code and data Byte is the least addressable unit Instruction categories Fixed point Arithmetic, Decimal Arithmetic, Floating point Arithmetic, Logical Operations, Branching, Status Switching, Input Output Programmer accessible Hardware Registers are Program Status Word (PSW) 64 bits wide General Purpose Registers (GPRs) Floating Point Registers (FPRs) Control Registers (CRs) 0-15 each 32 bits wide Access Registers (AR'S) 0-15 each 32 bits wide PSW 64 bits in length Contains the Condition Code (two bits) Address of the next instruction to be executed. PSW Key field GPR'S numbered 0-15 and 32 bits wide Used as accumulators in Fixed point arithmetic Used as base and index registers in computing the effective address Two consecutive registers can be used to hold 64bit operands addressed by even register AR'S Numbered 0-15 each 32 bits wide Used to point to address / data space FPR Used for floating point operations Numbered 0,2,4,6 each 64 bits wide 64 bits in length Can contain short or long operand Two adjacent registers can be used as 128 bit register for extended precision CR'S Control registers each of 32 bits are available Used by the IBM control program Instructions to access / modify them are privileged and can be issued only by the OS. INPUT/OUTPUT Data processing and I/O processing are concurrent Consists of Channel subsystem, Control Unit and I/O unit

ASSEMBLY LANGUAGE - 25/09/2004

5 / 116

ASSEMBLY STATEMENT FORMAT NAME FIELD 1 OPERATION FIELD OPERAND FIELD 10 16 REMARK S * 72 SEQUENC E

Fixed Format. Can be changed only through ICTL Assembler Directive Fields in a statement are separated by one or more blanks Name / label field if present must start in column 1 and maximum 8 characters in length To continue a statement to next line, type a non blank character in column 72 and continue the next line from column 16 Comment lines start with character ('*') on column 1

PSW Format IE Prog 0R0 0 0TOX Key 1MWPA SC C Mask 0 0 0 0 0 0 0 0 0 5 8 12 16 18 20 24 31 A Instruction Address 32 63 PER Mask (R): Bit 1 controls whether the CPU is enabled for interruptions associated with program-event recording (PER). When the bit is zero, no PER event can cause an interruption. When the bit is one, interruptions are permitted, subject to the PER-event-mask bits in control register 9. DAT Mode (T): Bit 5 controls whether dynamic address translation takes place. When the bit is zero, DAT is off, and logical and instruction addresses are treated as real addresses. When the bit is one, DAT is on, and the dynamic-address-translation mechanism is invoked. I/O Mask (IO): Bit 6 controls whether the CPU is enabled for I/O interruptions. When the bit is zero, an I/O interruption cannot occur. When the bit is one, I/O interruptions are subject to the I/O-interruption subclass-mask bits in control register 6. External Mask (EX): Bit 7 controls whether the CPU is enabled for interruption by conditions included in the external class. When the bit is zero, an external interruption cannot occur. When the bit is one, an external interruption is subject to the corresponding external subclass-mask bits in control register 0; PSW Key: Bits 8-11 form the access key for storage references by the CPU. If the reference is subject to key-controlled protection, the PSW key is matched with a storage key when information is stored or when information is fetched from a location that is protected against fetching. Machine-Check Mask (M): Bit 13 controls whether the CPU is enabled for interruption by machine-check conditions. When the bit is zero, a machine-check interruption cannot occur. Wait State (W): When bit 14 is one, the CPU is waiting; that is, no instructions are processed by the CPU, but interruptions may take place. When bit 14 is zero, instruction fetching and execution occur in the normal manner. The wait indicator is on when the bit is one.

ASSEMBLY LANGUAGE - 25/09/2004

6 / 116

Problem State (P): When bit 15 is one, the CPU is in the problem state. When bit 15 is zero, the CPU is in the supervisor state. In the supervisor state, all instructions are valid. In the problem state, only those instructions that cannot affect system integrity are permitted; such instructions are called unprivileged instructions. The instructions that are never valid in the problem state are called privileged instructions. When a CPU in the problem state attempts to execute a privileged instruction, a privileged-operation exception occurs. Address-Space Control (AS): Bits 16 and 17, in conjunction with PSW bit 5, control the translation mode. Condition Code (CC): Bits 18 and 19 are the two bits of the condition code. The condition code is set to 0, 1, 2, or 3, depending on the result obtained in executing certain instructions. Program Mask: Bits 20-23 are the four program-mask bits. Each bit is associated with a program exception, as follows: Program- Mask Bit Program Exception 20 Fixed-point overflow 21 Decimal overflow 22 Exponent underflow 23 Significance When the mask bit is one, the exception results in an interruption. When the mask bit is zero, no interruption occurs. Addressing Mode (A): When the bit is zero, 24-bit addressing is specified (AMODE 24). When the bit is one, 31-bit addressing is specified (AMODE 31). Instruction Address: Bits 33-63 form the instruction address. This address designates the location of the leftmost byte of the next instruction to be executed. Bit positions 0, 2-4, and 24-31 are unassigned and must contain zeros. A specification exception is recognised when these bit positions do not contain zeros. When bit 32 of the PSW specifies the 24-bit addressing mode, bits 33-39 of the instruction address must be zeros; otherwise, a specification exception is recognised. A specification exception is also recognised when bit position 12 does not contain a one

ASSEMBLY LANGUAGE - 25/09/2004

7 / 116

INSTRUCTIONS
TYPES OF INSTRUCTIONS machine instructions Assembler instructions (directives) Macro instructions

back

Example : PRINT NOGEN TEST1 CSECT STM BALR USING ST LA MVC PUTMSG WTO L LM SR BR DATA1 DS DATA2 DS SAVE DS END

14,12,12(13) 12,0 *,12 13,SAVE+4 13,SAVE DATA1,DATA2 'MESSAGE' 13,SAVE+4 14,12,12(13) 15,15 14 CL100 CL100 18F

Assembler Directive Machine instruction Machine instruction Assembler Directive Machine instruction Machine instruction Machine Instruction Macro instruction Machine instruction Machine instruction Machine instruction Machine Instruction Data Definition Data Definition Data Definition Assembler Directive

INSTRUCTIONS FUNDAMENTALS Two, four, or six bytes in length Should begin on a half-word boundary First byte normally contains the operation code. In some instructions it is two bytes. Operation code specifies the function of the instruction Operand designation follows the operation code Operands Entities that are involved in operations defined by operation code Operands can be either implicit or explicit Four types of operands Register operand Example immediate operand Example Storage operand Example Implied operand, Example AR 3,2 MVI DATA,X'F1' L 3,FIELD1 LM 14,12,SAVE

REGISTER OPERAND Identified by R field in the instruction Specifies either GPR or FPR Operand access is faster Example AR 1,2

ASSEMBLY LANGUAGE - 25/09/2004

8 / 116

IMMEDIATE OPERAND Contained with in the instruction itself Eight bit value Self defining term or an absolute symbol can be used Example : MVI DATA,B'10000000' STORAGE OPERAND Resides in memory Address is not specified explicitly Base and 12 bit offset with (in some instructions) index register is used Program can be relocated If Register 0 is used as a base or index register its contents are ignored 12 bit displacement BALR instruction is used to load base register If symbols are used assembler resolves it to base displacement form Effective address = (base register) + (Index Register) + 12 bit displacement (note that some instruction formats do not support index register) base register should be made to contain the base address at run time Size of storage operand is implied by the instruction for some instructions For some instructions Length field(s) is/are embedded in the instruction Storage operands can be specified in implicit form as a re-locatable expression Example L 3,DATA L 3,DATA+4 Storage operands can be specified in the Explicit form Example L 3,4(1,2) Explicit addresses are of the form D2(X2,B2) or D2(B2) or D2(L2,B2) or D1(L1,B1) or D1(B1) Absolute addresses are also assembled in base displacement form. However the value in the base register will not change on relocation Implicit addresses are those where a single re-locatable or absolute expression is specified Example L 4,DATA L 3,DATA+4 LA 2,1000 . . DATA DS F IMPLIED OPERAND The instruction implies the operand Example

TRT D1(L,B1),D2(B2) Registers 0,1 participate in this operation

ASSEMBLY LANGUAGE - 25/09/2004

9 / 116

INSTRUCTIONS CLASSIFICATION FIRST HALF WORD RR FORMAT OP CODE 0 8 RRE FORMAT OP CODE 0 16 RX FORMAT OP CODE R1 X2 0 8 RS FORMAT OP CODE 0 8 R1 R3 12 B2 16 20 DI 20 31 D2 31 12 16 24 R1 28 R2 31 R1 12 R2 15 SECOND HALF WORD THIRD HALF WORD

B2 20

D2 31

SI FORMAT OP CODE I2 0 8 S FORMAT OP CODE 0 SS FORMATS OP CODE 0 8 OP CODE 0 8 L1 12 L 16 L2/I3 16 16 16

B1

B2 20

D2 31

B1 20 B1 20

D1 32 D1 32

B2 36 B2 36

D2 47 D2 47

EXAMPLES : RR type instruction AR 2,3 (reg 2) <== (reg 2) + (reg 3) RS type instruction BXLE 1,2,D2(B2) (reg 1) <== (reg 1) + (reg 2) If reg1>reg3 then branch RX type instruction L 1,D2(X2,B2) (reg 1) < == memory referenced by (D2 +X2 +B2) S type instruction LPSW D2(B2) SI type instruction

ASSEMBLY LANGUAGE - 25/09/2004

10 / 116

NI D1(B1),I2 SS type instruction MVC D1(L,B1),D2(B2) PACK D1(L1,B1),D2(L2,B2) Note that (Rn) denotes the contents of GPR n. It is known as Register Notation and is commonly used to supply values for a Macro operand.

ASSEMBLY LANGUAGE - 25/09/2004

11 / 116

SYMBOLS, LITERALS, DATA AREAS, LOCATION COUNTER

back

SYMBOLS A sequence of one to eight characters as specified below under ORDINARY,VARIABLE,SEQUENCE symbols Absolute value assigned to a symbol by using 'EQU' assembler instruction with an absolute value operand A re-locatable value is assigned to a symbol by using it in the name field of a machine instruction Symbols can be used in operand fields to represent registers, displacements, lengths, immediate data, addresses etc. Example : LABEL001 QUIT S1 S2 COUNT MVC B BR DS DC EQU S1,S2 QUIT 14 CL100 CL100'THE QUICK BROWN FOX' 10

LABEL001, QUIT, S1, S2 and COUNT are all Symbols. All are re-locatable except COUNT which is absolute. Ordinary Symbols Optional used in the name and operand field of machine/assembler instructions Up to eight Alphanumeric characters A-Z,$,#,&,0-9 First character must be alphabetic A-Z Rest can be alphanumeric Example ABCD0001 Variable Symbols First character must be an ampersand second character must be alphabetic Up to six alphanumeric characters Example &ABC0001 Sequence Symbols First Character must be a period Next Character must be alphabetic Up to six alphanumeric characters Example .ABC0001 Advantages of symbols Easier to remember and use Meaningful symbol names instead of values For address the assembler calculates the displacement Change the value at one place (through an EQU) instead of several instructions Printed in the cross-reference table by the assembler Symbol Length attribute TO DS FROM DS ADCON DC CHAR DC DUPL DC CL80 CL240 A(OTHER) C'YUKON' 3F'200' L'TO = 80 L'FROM = 240 L'ADCON = 4 L'CHAR = 5 L'DUPL = 4

ASSEMBLY LANGUAGE - 25/09/2004

12 / 116

Self Defining terms Can be used to designate registers, masks, and displacements within the operand entry Decimal self-defining term An unsigned decimal integer maximum number of digits 10 Maximum value 2**31-1 Hexadecimal self-defining A Hexadecimal integer within apostrophes and preceded by a X Maximum number of digits 8 Maximum value 2**31-1 Binary Self Defining Term sequence of 1s and 0s enclosed in single quotation marks and preceded by the letter B; for example, B'11000101' Character self-defining term A character string within apostrophes and preceded by a C Maximum number of characters 4 EXAMPLES: 15 241 B'1101' X'F' X'F1F2' C'ABCD' C'&&' C'''''' Literals L L MVC L L DC MVC MVI MVI . . EQU DS LA LA . EQU 1,=F'200' 2,=A(SUBRTN) MESSAGE(20),=CL20'THIS IS A MESSAGE' 3,=F'33' BOTH ARE SAME 3,FIELD BOTH ARE SAME F'33' FLAG,=X'00' SAME EFFECT FLAG,X'00' SAME EFFECT FLAG,ZERO SAME EFFECT X'00' C 4,LOCORE 4,1000 1000 An expression is absolute if it's value is unchanged by program relocation CSECT DC F'2' DC F'3' DC F'4' EQU 100

UPTO 2,147,483,647 UPTO 32 BITS UPTO 8 HEX DIGITS UPTO 4 CHARACTERS TWO AMPERSANDS TO REPRESENT ONE TWO APOSTROPHES TO REPRESENT ONE

FIELD

ZERO FLAG

SAME EFFECT SAME EFFECT

LOCORE

Absolute expressions FIRST A B C ABSA

ASSEMBLY LANGUAGE - 25/09/2004

13 / 116

ABSB ABSC ABSD

EQU EQU EQU

X'FF' B-A *-A

All these are absolute expressions:ABSA 15 L'A ABSA+ABSC-ABSC*15 B-A ABSA+15-B+C-ABSD/(C-A+ABSA) Relocatable expressions A relocatable expression is one whose value changes with program relocation. FIRST CSECT A DC H'2' B DC H'3' C DC H'4' ABSA EQU 10 ABSB EQU *-A ABSC EQU 10*(B-A) The following are relocatable expressions:A A+ABSA+10 B-A+C-10*ABSA Location Counter Location counter is incremented after instruction or data definition is assembled to the next available location Assembler checks boundary alignment and adjusts location counter if required. While assembling the current line the location counter value does not change Location counter Source Statements 000004 DONE DC CL3'SOB' 000007 BEFORE EQU * 000008 DURING DC F'200' 00000C AFTER EQU * 000010 NEXT DS D 000018 AFTNEXT EQU * 000018 NEXT1 DS D 000020 NEXT2 DS D 000028 ORG *+8 000030 NEXT3 DS D Example : LOOP EQU B . . . B * *+80

LOOP

ATTRIBUTES OF SYMBOLS : Length attribute Referred to as L'symbol For a symbol defined by "DC' or 'DS', it is the implicit or explicit length.

ASSEMBLY LANGUAGE - 25/09/2004

14 / 116

For a symbol referring to a machine instruction, it is the length of the instruction. For a 'EQU' symbol, it is the length of the left most term or supplied by the second operand DS DS DS AR EQU EQU EQU F 20FL4 XL3 1,2 A+4 102 A,256 length 4 4 3 2 4 1 256

Example : A

AA S1 BUF

Type attribute Referred to as 'T' symbol Gives the one character type code of the symbol A,Y,V,S For the related Address Constants B,C,D,E,F,H,Z,P For the related data constants I For machine instruction M For a Macro instruction J For a control section name T For a EXTRN symbol $ For a WXTRN symbol N For a self defining term O Null string CONSTANTS AND DATA AREAS Run Time Constants DC directive Literals Self defining terms Assembly time constants EQU statement

Constants can be absolute / re-locatable A re-locatable constant has a unbalanced re-locatable term

DC instruction To reserve storage and initialise it with values Location counter advanced by the number of bytes associated with the specified type Not true constants, the values can be changed in the program Similar to specifying initial values in variable declarations of a high level language

DC

DUPLICATING FACTOR TYPE LENGTH MODIFIER CONSTANT

SYNTAX {NAME}

DC

{DUP}TYPE{MOD}{V1,V2,...VN} TYPE BYTES ALLOC F'100,-10,200' 12 F'123' 4 F'-123' 4 3F'23' 12 H'20' 2 H'123,23,-34' 6

Run time constant DC DC DC DC DC DC

ASSEMBLY LANGUAGE - 25/09/2004

15 / 116

DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC DC

B'11000001' 1 X'FFFFFFFF' 4 X'FF01FF01' 4 C'ABCDEF' 6 C'abcdefg''A&&SS@#..' 16 , note double & and ' P'-1234' 3 P'1234' 3 P'-34' 2 Z'1234' 4 E'-3.25E10' 4 E'+.234E-10' 4 E'-2.3E15' 4 A(LOOP1) 4 V(LOOP1) 4 S(FIELD2) 2 C'USER01' 6 F'100,200' Two full words with value 100,200 CL3'JAN,FEB' Months contain 3 bytes value "JAN' 3H'2,4,8,16' 12 half words with the given value B'10001000' 1 C'SAMPLE STRING' 13 P'123' 2 ZL10'123' 10 PL4'123' 4 E'1.25' 4 D'2.57E65' 8 AL3(THERE) 3 V(EXTSYM) 4 Y(124) 2

DEFINE STORAGE (DS) To reserve storage Storage is not initialised Location counter is advanced by bytes allocated DS SYNTAX {NAME} EXAMPLES DS DS DS DS 80C CL80 4D 0F 0D 0CL8 100H F 10F H 2CL3 Bytes allocated 4 40 2 6 80 L'A=1 80 L'A=80 32 0 used to force a word Boundary 0 used to force a double word boundary 0 length attribute is 8 200 DUPLICATING FACTOR TYPE LENGTH MODIFIER DS {DUP}TYPE{MOD}

DS DS DS DS DS DS DS

A self defining term is an absolute constant that can be written as a A binary integer B'1001' A decimal integer 3

ASSEMBLY LANGUAGE - 25/09/2004

16 / 116

A hexadecimal integerX'4A' A sequence of text characters C'ABCD' These can be used as immediate operands in any instruction which needs an immediate operand. Example CLI 0(8),C'Z'

A literal is a symbolic representation of a constant to which the assembler assigns an address L L L MVC DC 5,FCON 5,=F'1' 2,=F'-4' MSG,=C***Error ***' F'1'

LOAD MOVE FCON

The first two statements are exactly equivalent to the third. A convenient means of introducing constants without the use of 'DC' instruction Storage is allocated for literals at the end of the first CSECT (Literal Pool) where multiple CSECTS are coded in a single source file.To avoid addressing problems, use a LTORG at end of each CSECT Storage allocation can be forced at any point by 'LTORG" assembler instruction Two literals are the same if their specifications are identical Assembler translates a literal into a base register and a displacement A equivalence constant allows a programmer to define a value for a symbol and use it wherever there is a need to employ that value. R1 HERE OFF ON Y Z W EQU EQU EQU EQU DC EQU EQU CLI BE CLI BE 1 * X'00' X'FF' F'4' 4 Y W is equivalent to Y STATUS,ON POWERON STATUS,OFF POWEROFF

Data Alignment Instructions have to be aligned on half-word boundary Data can be specified to be aligned to Double word D (Divisible by 8) Full-word F (Divisible by 4) Half-word H (Divisible by 2) Location counter skipped as per alignment requirement Example : 000100 DC C'ABC' 000103 skipped 000104 DC F'4' 000108 DC C'A' 000109 skipped 000110 skipped 000111 skipped 000112 DC F'560' Instruction Alignment

ASSEMBLY LANGUAGE - 25/09/2004

17 / 116

Instructions are always aligned on a half word boundary. Some times it may be required to align instructions on a Full word or double word boundary. Use the CNOP instruction to do so. For example to get full word alignment use CNOP 0,4 as below. The BAL instruction will always be aligned on a Full word boundary. Assembler will introduce, if required, a NOP ( X0700 ) instruction to ensure this. CNOP BAL PARM DC DC BALR 0,4 1,*+12 A(P1) A(P2) 14,15

IF ASSEMBLER OPTION ALIGN IS SPECIFIED Assembler checks storage addresses (labels) to ensure that they are aligned on boundaries required by the instruction. Data areas are aligned on boundaries implicit with their type if no length modifier is present LOC-CTR PROGRAM 000010 DATA DC C'ABC' 000014 DS F ASSM. AT WORD BDRY IF NOALIGN IS SPECIFIED Constants and data areas are not automatically aligned Assembler does not check storage addresses for boundary alignment. LOC-CTR PROGRAM 000010 DATA DC C'ABC' 000013 DS F ASSM. AT NEXT LOC Example This example illustrates the use of literals and commonly used data definitions. TEST2 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE WTO 'ASM1 REPORTING',ROUTCDE=(11) L 3,=F'200' LA 3,ABSB MVC DATA1(6),=C'ABCDEF' MVC DATA1,=CL20'ABCDEF' L 13,SAVE+4 LM 14,12,12(13) SR 15,15 BR 14 SAVE DS 18F DC A(SAVE1) A DC H'2' B DC H'3' C DC H'4' ABSA EQU 10 ABSB EQU *-A DC F'100' DC F'-100' DC H'100' DC 3H'100' DC C'ABCEFGH'

ASSEMBLY LANGUAGE - 25/09/2004

18 / 116

DATA1

DC DC DC DC DC DC DS END

CL20'ABCDEFGH' 10C'AB' P'123' P'-123' PL5'-123' 3PL5'-123' CL20

ASSEMBLY LANGUAGE - 25/09/2004

19 / 116

INTEGER OPERATIONS
FIXED POINT ARITHMETIC ADD SUBTRACT MULTIPLY DIVIDE ARITHMETIC COMPARE LOAD STORE ARITHMETIC SHIFT CONVERT TO BINARY CONVERT TO DECIMAL Constants used Fixed Point Binary Hexadecimal Character Decimal Address AR,A,AH,ALR,AL SR,S,SH,SLR,SL MR,M,MH DR,D CR,C,CH LR,L,LH,LTR,LCR,LPR ST,STH,STM SLA,SRA,SLDA,SRDA CVB CVD Type H and F B X C P Y,A,S,V,Q

back

ASSEMBLY LANGUAGE - 25/09/2004

20 / 116

INTEGER ARITHMETIC GPR's are 32 bits with bit 0 as a sign bit Negative numbers stored as two's complement Both Full word and Half Word instructions are supported GPR/GPR and GPR/Memory instructions available Half words converted to full word by extending sign bit to the left Decimal 0 -1 -2 -3 -4 -5 -6 -7 Binary 0000 1111 1110 1101 1100 1011 1010 1001

Two's Complement Decimal Binary 0 0000 +1 0001 +2 0010 +3 0011 +4 0100 +5 0101 +6 0110 +7 0111 Addition and Subtraction

0110 -6 1010 +5 0101 -5 1011 0001 +(-1) 1111 +(+6) 0110 +(-6) 1010 --------------------0111 1001 1011 0100 00 11 01 10 No overflow No overflow Overflow Overflow If the carry into the sign bit is different from the carry out of it, there is an overflow condition. L Copy full word from memory to GPR RX L 3,A GPR3 Before 0246 0357 After 000A 00B0 Copy a full word from GPR to memory RX ST 3,A GPR3 Before 0123 0456 0123 0456 Copies a half word from memory to GPR LH 3,A GPR3 Before 0159 0260 After 0000 4321 Before After STH 0000 FFFF 4321 C321 R1,D2(X2,B2) Memory Field A 000A 00B0 000A 00B0 R1,D2(X2,B2) Memory field A 0ABC 0DEF 0123 0456 RX R1,D2(X2,B2) Memory Field A 4321 4321 C321 C321 R1,D2(X2,B2) Memory field A 0DEF 0456

+6 +(+1)

ST

LH

Copy a half word from GPR to memory RX STH 3,A GPR3 Before 0123 0456 After 0123 0456

ASSEMBLY LANGUAGE - 25/09/2004

21 / 116

LM

Copies 1 to 16 Full words from memory RS R1,R3,D2(B2) to consecutive GPR,s LM 2,4,A GPR'S Memory Address Before 2:00001234 A+0:0001ABCD 3:00003456 A+4:0002BCDE 4:00005678 A+8:0003CDEF After 2:0001ABCD A+0:0001ABCD 3:0002BCDE A+4:0002BCDE 4:0003CDEF A+8:0003CDEF Copies 1 to 16 Full words to memory From consecutive GPR,s STM 2,4,A Before After RS R1,R3,D2(B2) Memory Address A+0:0001ABCD A+4:0002BCDE A+8:0003CDEF A+0:00001234 A+4:00003456 A+8:00005678

STM

GPR'S 2:00001234 3:00003456 4:00005678 2:00001234 3:00003456 4:00005678

LR

Copies one GPR to another LR 3,4 Before After

RR R1,R2 GPR3 GPR4 ABCD EF00 1234 5678 1234 5678 1234 5678

ADDITION A

Adds a memory field to GPR RX R1,D2(X2,B2) Example 64+10=74. A 3,=F'10' GPR3 Memory Before 0000 0040 0000 000A After 0000 004A 0000 000A Subtracts a memory field from GPR RX R1,D2(X2,B2) Example 64-10=54 S 3,=F'10' GPR3 Memory Before 0000 0040 0000 000A After 0000 0036 0000 000A Adds a GPR to another GPR Example 4096+(-1)=4095 AR 6,5 Before After RR GPR6 0000 1000 0000 0FFF R1,R2 GPR5 FFFF FFFF FFFF FFFF R1,R2 GPR5 FFFF FFFF FFFF FFFF

AR

SR

Subtracts a GPR from another GPR RR Example 4096-(-1)=4097 SR 6,5 GPR6 Before 0000 1000 After 0000 1001

AH

Adds a half word memory field to a GPRRX R1,D2(X2,B2) Example 80+8=88 AH 10,=H'8' GPR10 Memory

ASSEMBLY LANGUAGE - 25/09/2004

22 / 116

Before After Example 80+(-8)=72 AH 10,=H'8' Before After SH

0000 0050 0000 0058 GPR10 0000 0050 0000 0048

0008 0008 Memory FFF8 FFF8

Subtracts a half word memory field from RX R1,D2(X2,B2) a GPR Example 8-80=-72 SH 10,=H'80' GPR10 Memory Before 0000 0008 0050 After FFFF FFB8 0050 Add Logical Adds a GPR logically to another GPR RX RR R1,D2(X2,B2) R1,R2

AL ALR

Range of result in the GPR is from -2**31 to 2**31-1 If an overflow occurs (carry into sign bit and carry out are different) hardware interrupts occur if not suppressed through a program mask For logical additions the operands are assumed to be unsigned Condition code is set (zero, negative, positive or overflow) |--------------consecutive GPR'S------------------------| |---even numbered GPR--|--odd numbered GPR---| Before multiplication After multiplication M Multiply Example 2 X 3 = 6 L 7,=F'2' M 6,=F'3' Before After GPR6 any number 0000 0000 Any number V1 64 bit product V1 X V2 RX R1,D2(X2,B2)

MULTIPLICATION

GPR7 0000 0002 0000 0006 R1,D2(X2,B2)

Memory 0003 0003

MR Multiply one GPR with another RX Example 65536 X 65536 L 4,=F'65536' MR 6,4 GPR6 Before 0000 0000 After 0000 0001 MH

GPR7 0001 0000 0000 0000

GPR4 0001 0000 0001 0000

Multiply a GPR with a half word RX R1,D2(X2,B2) from a memory field Example 2 X 5 = 10 L 7,=F'2' MH 7,=F'5' GPR7 Memory Before 0000 0002 0005 After 0000 000A 0005

ASSEMBLY LANGUAGE - 25/09/2004

23 / 116

DIVISION |-----------------consecutive GPR'S-----------------------------| |---even numbered GPR----|----odd numbered GPR----| Before Division After Division 64 BIT DIVIDEND V1 32 BIT REMAINDER 32 BIT QUOTIENT RX R1,D2(X2,B2)Field

D DIVIDE even odd GPR pair by memory Example 7 / 2 = quotient =3, remainder=1 L 9,=F'7' M 8,=F1' D 8,=F'2' GPR8 Before 0000 0000 After 0000 0001 Rem +1 DR

GPR9 0000 0007 0000 0003 Quot +3 GPR

Memory 0002 0002 Divisor +2 R1,R2

Divide one even/odd pair GPR with another

Example 150 / -40 L 9,=F'150' M 8,=F'1' L 10,=F'-40' DR 8,10 Before After GPR8 0000 0000 0000 001E rem +30 GPR9 0000 0096 FFFF FFFD Quot -3 GPR10 FFFF FFD4 FFFF FFD4 Divisor -40

The condition code is NOT set by the MULTIPLY and DIVIDE instructions. To test the result use the LTR instruction. ARITHMETIC COMPARE C Compare GPR with memory field CR Compare a GPR with another CH Compare GPR with a memory half word Condition code is set ( equal, V1<V2, V2>V2) LCR Load complement register Example LCR 3,3 Before After LCR 3,4 Before After LPR Load positive register Example LPR 5,4 RR GPR3 FFFFFFFA 00000006 GPR3 87654321 80000000 **ovfl set RR GPR5 R1,R2 GPR4 R1,R2

RX RR RX

R1,D2(X2,B2) R1,R2 R1,D2(X2,B2)

GPR4 80000000 80000000

ASSEMBLY LANGUAGE - 25/09/2004

24 / 116

Before After LPR 4,5 Before After LPR 8,7 Before After LNR Load negative register Example LNR 4,5 Before After LPR 4,5

000000AB 00000006 GPR4 FFFFFFFA 0000000AB GPR8 12345678 80000000 ***ovflw RR R1,R2

FFFFFFFA FFFFFFFA GPR5 000000AB 000000AB GPR7 80000000 80000000

GPR4 FFFFFFFA FFFFFF55

GPR5 000000AB 000000AB GPR5 FFFFFF55 FFFFFF55

GPR4 Before 00000011 After 000000AB Condition code is set( zero, positive , negative, overflow) SPM Set Program Mask SPM R1

The first operand is used to set the condition code and the program mask of the current PSW. Bits 12-15 of the instruction are ignored. Bits 2 and 3 of general register R1 replace the condition code, and bits 4-7 replace the program mask. Bits 0, 1, and 8-31 of general register R1 are ignored. SR 4,4 L 4,=X0F000000 SPM 4 turn on all 4 program mask bits IPM Insert Program Mask IPM R1 The condition code and program mask from the current PSW are inserted into bit positions 2-3 and 4-7, respectively, of general register R1. Bits 0 and 1 of the register are set to zeros; bits 8-31 are left unchanged. Note that unless the Program Mask bits in the PSW are 1 some interrupts are suppressed. See the PSW fields for details.

ASSEMBLY LANGUAGE - 25/09/2004

25 / 116

DECIMAL OPERATIONS
ADD SUBTRACT MULTIPLY DIVIDE DECIMAL COMPARE MOVE DECIMAL DATA WITH 4 BIT OFFSET SHIFT DECIMAL DATA SET TO ZERO AND ADD CONVERT ZONED TO PACKED CONVERT PACKED TO ZONED Constants used Decimal Zoned AP SP MP DP CP MVO SRP ZAP PACK UNPK Type P Z

back

BCD Representation (Packed Decimal) 0011 0111 AREA1 AREA2 0010 1000 0101 1001 DS DC 1100 1101 +325 -789 X325C X789D

PL5 P+12345678

Only permissible (and mandatory) modifier is the length modifier example PLn Padding is always at the left with Zeroes Truncation is from the left and choice of length modifier is crucial OPCODES are Arithmetic, Comparison, Copying from storage to storage, Conversion to and from Packed decimal format. Most instructions are SS1 D1(L,B1),D2(B2) (length < 256) SS2 D1(L1,B1),D2(L2,B2) (length < 16) ZAP Zero and add packed Example ZAP A(3),B(4) SS2 Before After AP Add packed Example AP A(2),B(3) SS2 Before After Before After SP Subtract packed Example SP A(2),B(3) SS2 Before After A 099D 100D B 00001C 00001C A 099C 100C 999C 000C (ovfl cond) B 00001C 00001C 00001C 00001D A Dont Care 23456C B 0023456C 0023456C

ASSEMBLY LANGUAGE - 25/09/2004

26 / 116

Before After Before After MP

999C 000C (ovfl cond) 123C 113C

00001D 00001D 00010C 00010C

Multiply packed SS2 Length of L2 must be between 1 and 8 and less than L1. L1 must have at least L2 bytes of high order zeroes A(4),B(2) Before After MP A(3),B(2) Before After Before After A 0000999C 0998001D 00999C 98001D **ovflw** 012C 012C **error** B 999D 999D 999D 999D 012C 012C

Example MP

MP

A(2),B(2)

DP

Divide Packed SS2 DP D1(L1,B1),D2(L2,B2) L1 (Dividend) and L2(divisor) L2 < L1 1<=L2<=8 The quotient and remainder is stored in the L1(dividend field) replacing the dividend QUOTIENT REMAINDER L1-L2 BYTES L2 BYTES DIVIDEND FIELD

Example DP

A(4),B(2)

Before After Before After

A 0000999C 001D001C |

B 998D 998D

DP DP

A(4),B(2) A(2),B(1)

0000999C 3C 00333C0C 3C | Before 999C 3C After 999C 3C **Divide exception** ***L1-L2=1 (insufficient length for quotient) Before 999C 00003C After 999C 00003C **specification exception** ***L1-L2=-1(impossible length for quotient)

DP

A(2),B(3)

ASSEMBLY LANGUAGE - 25/09/2004

27 / 116

ERRORS Decimal overflow occurs when result is too long to fit into first operand and a significant digit would be lost Data exception occurs whenever Sign fields are invalid Operands overlap The first operand of a MP instruction does not have sufficient zeroes. COMPARISONS CP Compare packed BE BH BL SRP V1=V2 V1>V2 V1<V2 D1(L1,B1),D2(B2),I3 SS1 SS2 D1(L1,B1),D2(L2,B2)

Shift and Round Packed

The first operand represents an address The second operands low order 6 bits is the number of positions to be shifted and direction of shift. Positive represents left shift and vacated positions on the left are filled with zeroes. Negative represents a right shift and zeroes are inserted on the left. The sign is not disturbed in any case. The third operand is the rounding to be applied in case of right shift and is an immediate operand. L 8,=F-3 for shift right 3 positions SRP A(5),0(8),5 before 031415926C after 000031416C CONVERSION BETWEEN EBCDIC, BINARY AND PACKED DECIMAL FORMAT CVD converts binary to packed decimal 32 bit binary to a 8 byte packed decimal field Example CVD 5,A REG5 A Before 7F FF FF FF any number after 7F FF FF FF 00 00 02 14 74 83 64 7C CVD after CVB 5,A REG5 A Before 80 00 00 00 dont care 80 00 00 00 00 00 02 14 74 83 64 8D

converts packed decimal to binary 8 byte packed decimal field to a 32 bit binary field Example CVB 5,A REG5 A Before dont care 00 00 00 00 00 00 01 6C after 00 00 00 10 00 00 00 00 00 00 01 6C CVB 5,A REG5 Before dont care after FF FF FF F0 A 00 00 00 00 00 00 01 6D 00 00 00 00 00 00 01 6D

PACK converts EBCDIC to packed decimal D1(L1,B1),D2(L2,B2) Operand one will receive packed decimal field Operand two is the EBCDIC field in zoned decimal format Example PACK A(4),B(4) A B Before any F1 F2 F3 C4 after 00 01 23 4C F1 F2 F3 C4

ASSEMBLY LANGUAGE - 25/09/2004

28 / 116

UNPK converts packed decimal to EBCDIC D1(L1,B1),D2(L2,B2) Operand two is the packed decimal field Operand one will receive the EBCDIC field Example UNPK A(8),B(4) A B Before any 12 34 56 7D After F0 F1 F2 F3 F4 F5 F6 D7 12 34 56 7D ED Converting a packed decimal number to EBCDIC with editing D1(L,B1),D2(B2) V1 is pattern, V2 is packed fld ED P(15),Y Before Y 0 0 1 2 3 4 5 6 7 D Before P 40 20 6B 20 20 20 6B 20 21 20 4B 20 20 60 40 After P 40 40 40 40 F1 F2 6B F3 F4 F5 4B F6 F7 60 40 1st byte of pattern is the fill character, in this case a blank Hex 20 is a digit selector Hex 21 is a significance starter Hex 6B is a , Hex 4B is a . Every byte of packed decimal needs two bytes of EBCDIC code 00 12 3C ----------------- F0 F0 F1 F2 C3

EDMK Does everything ED does. In addition it sets register 1 to the address of the first significant digit. You can then bump Register 1 down by 1 and move immediate a currency symbol to that storage location represented by the address in 1. Note that you initially set 1 to the first digit position that is forced to print if no significant digits occur to the left. MVC P,MASK LA 1,MASK+9 EDMK P,Y BCTR 1,0 MVI 0(1),C$ . . Y DC PL5-1234567 P DS CL15 MASK DC X40206B2020206B2021204B20206040 Example of Packed Decimal Divide TEST3 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE DP A,B UNPK QUOT,A(L'A-L'B) UNPK REM,A+L'A-L'B(L'B) OI QUOT+3,X'F0' OI REM+3,X'F0' LA 3,MSG WTO TEXT=(3) L 13,SAVE+4

ASSEMBLY LANGUAGE - 25/09/2004

29 / 116

SAVE MSG QUOT REM LEN A B

LM LA BR DS DC DC DS DC DC DS EQU DC DC END

14,12,12(13) 15,0 14 18F AL2(LEN) C'QUOT=' CL4 C',' C'REM=' CL4 *-MSG-2 PL4'+0000999' PL2'-998'

Example of displaying a Integer TEST4 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE LA 4,2345 CVD 4,DW UNPK MSG+2(16),DW OI MSG+17,X'F0' LA 3,MSG WTO TEXT=(3) L 13,SAVE+4 LM 14,12,12(13) LA 15,4 BR 14 SAVE DS 18F MSG DC AL2(16) DS CL16 DW DS D END

ASSEMBLY LANGUAGE - 25/09/2004

30 / 116

DATA TRANSFER AND LOGICAL OPERATIONS


MOVE LOGICAL COMPARE AND LOGICAL OR LOGICAL EXCLUSIVE OR TESTING BINARY PATTERNS INSERTING CHARS INTO GPR STORE CHARS INTO AREAS LOAD ADDRESS INTO GPR LOGICAL SHIFT OF GPR DATA TRANSLATION MVI,MVC,MVZ,MVCL CLR,CL,CLC,CLCL,CLM NR,N,NI,NC OR,O,OI,OC XR,X,XI,XC TM IC,ICM STC,STCM LA SLL,SRL,SLDL,SRDL TR,TRT

back

BYTE AND STRING MANIPULATIONS IC Insert character RX R1,D2(X2,B2) STC store Character RX

Copies 1 byte from memory to 8 right most bits of a GPR Copies 1 byte (right most 8 bits) from GPR to Memory Copies 1 to 4 bytes depending on the mask from memory to GPR Copies 1 to 4 bytes depending on the mask from GPR to memory SI Copies 1 byte from immediate field of the instruction to memory SS Copies 1 to 256 chars from one memory field to another

R1,D2(X2,B2) ICM Insert Characters under mask RS

R1,Mask,D2(B2) STCM Store characters under mask R1,mask,D2(B2) MVI Move Immediate RS

D1(B1),I2 MVC Move Characters

D1(L,B1),D2(B2) MVCL Move Characters Long R1,R2 MVCIN Move Inverse SS Copies 1 to 256 bytes from one memory field to another reversing the order of bytes Comparison RR Copies 1 to 2**24 chars from one memory field to another

COMPARISON (LOGICAL) Unsigned 8 bit numbers (logical quantity) Smallest byte is X00, Largest is XFF Comparison starts from left most position (high order) CL Compare logical R1,D2(X2,B2) CLR Compare Logical Register R1,R2 RR Compares 4 bytes from two GPRS RX Compares a 4 byte string in memory to contents of a GPR

ASSEMBLY LANGUAGE - 25/09/2004

31 / 116

CLM

Compare Logical under mask

RS

Compares 1 to 4 bytes (determined by mask) from a GPR to a memory field Compares an 1 byte immediate operand to a byte in memory Compares 1 to 256 bytes from one memory field to another RR Compares 1 to 2**24 characters from one memory field to another. CC 1 OPR1<OPR2 CC 2 OPR1>OPR2 CC3 NA.

R1,M,D2(B2) CLI Compare Logical Immediate D1(B1),I2 CLC Compare Logical Characters SS SI

D1(L,B1),D2(B2) CLCL Compare Logical Characters long BRANCHING CC 0 CL,CLC,CLCL, CLI,CLM,CLR Opcode BE BNE BL BNL BH BNH OPR1=OPR2 Meaning OPR1=OPR2 OPR1!=OPR2 OPR1<OPR2 OPR1=>OPR2 OPR1>OPR2 OPR1<=OPR2

Notes: Destructive overlap occurs when a to field starts from within a from field How to modify length field at run time EX R1,D2(X2,B2). The instruction at the memory address specified is executed after ORing bits 8-15(length field) with bits 24-31 of R1. LH SH EX | | MVC | | DS DS 4,=H20 4,=H1 4,MOVEV TO(0),FROM 10F 10F

MOVEV FROM TO

CLCL and MVCL instructions CLCL R1,R2 MVCL R1,R2

R1 bits 8 to 31 is the TO address R1+1 bits 8 to 31 is the length of TO field R2 bits 8 to 31 is the FROM address R2+1 bits 8 to 31 is the length of FROM field bits 0 to 7 is the padding character to be used to lengthen the shorter string

ASSEMBLY LANGUAGE - 25/09/2004

32 / 116

S T

LA L LA L ICM MVCL | | | DS DS

4,S 5,=A(LS) 2,T 3,=A(LT) 5,B1000,=X00 2,4

CL1000 CL2000

TR and TRT instructions TR TRT Translate SS instructions can be used to replace certain bytes of the string with other bytes D1(L,B1),D2(B2) instruction can be used to find one of a set of characters in a string D1(L,B1),D2(B2)

Translate & test SS

Notes: Operand 1 is the argument string operated on by TR and searched by TRT instruction Operand 2 is the Function string set up by the programmer and is 256 bytes long FN1 DS ORG DC ORG DS | TRT BC BC BC CL256 FN1+C+ XFF CL256 ARG1(256),FN1 8,NONE 4,MORE 2,ONE

ARG1

Notes: How the instruction works is as follows. Read a byte from argument string. Use it as an offset into the function string. In the TR instruction replace the argument byte with the function byte. In the TRT instruction , if the function byte is non zero, a copy of that byte is inserted in bits 24 to 31 of GPR2 and the address of the byte is set into bits 8 to 31 of GPR1. Execution terminates and a CC is set to 1 if more bytes remain to be scanned in the argument string. A CC of 2 is set if there was a non zero byte in the function string and there were no more bytes to be scanned as well. Else CC 0 is set. Example of TR This sample translates a lower case string to upper case, leaving numeric digits intact. All other characters are converted to NULL. TR CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE TR DATA,TABLE WTO TEXT=MSG L 13,SAVE+4

ASSEMBLY LANGUAGE - 25/09/2004

33 / 116

SAVE MSG DATA LEN TABLE

LM SR BR DS DC DC EQU DC ORG DC ORG DC ORG DC ORG DC ORG END

14,12,12(13) 15,15 14 18F AL2(LEN) C'abcdefghijklmnopqrstuvwxyz1234567890' *-DATA 256X'00' TABLE+C'a' C'ABCDEFGHI' TABLE+C'j' C'JKLMNOPQR' TABLE+C's' C'STUVWXYZ' TABLE+C0 C0123456789

Example of TRT This example illustrates how the string at DATA is parsed into two components about the comma. The example can be extended to parse the string around multiple commas in the string. TRT CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) TRT DATA,TABLE ST 1,REG1 * LA 4,DATA SR 1,4 LR 4,1 STH 4,MSG SH 4,=H'1' LA 3,DATA EX 4,MV WTO TEXT=MSG * L 1,REG1 LA 3,1(0,1) LA 5,DATAEND SR 5,3 STH 5,MSG SH 5,=H'1' EX 5,MV WTO TEXT=MSG * SR 15,15 L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13)

ASSEMBLY LANGUAGE - 25/09/2004

34 / 116

SAVE TABLE

DATA DATAEND REG1 MSG MV

BR 14 DS 18F DC 256X'00' ORG TABLE+C',' DC C',' ORG DC C'ABCDEFGH,FDFDFDF' EQU * DS F DS AL2 DS CL256 MVC MSG+2(0),0(3) END

ASSEMBLY LANGUAGE - 25/09/2004

35 / 116

BIT MANIPULATIONS
SRA SLA SRDA SLDA Shift Shift Shift Shift Right Single Arithmetic Left Single Arithmetic Right Double Arithmetic Left Double Arithmetic

back RS RS RS (first operand is even odd GPR pair) RS

When shifting left zeroes are inserted on the right and overflow is set if a bit value other than the sign bit is lost from the shift. When right shifting the low order bits are lost and the sign bit is propagated If overflow occurs it can be checked by BO (branch on Overflow) If overflow is not set condition code 0,1, or 2 is set SRL SLL SRDL SLDL Shift Shift Shift Shift Right Single Logical Left Single Logical Right Double Logical Left Double Logical RS RS RS (first operand is even odd GPR pair) RS

When right shifting the low order bits are lost and the zeroes are inserted on the right When shifting left zeroes are inserted on the right and the high order bits are lost. The condition code is never set O N X OR NR XR OI NI XI OC NC XC Or RX And RX Exclusive Or RX Or GPRS RR And GPRS RR XOR GPRS RR Or Immediate SI And Immediate SI Exclusive Or Immediate SI Or Memory fields SS And Memory Fields SS Exclusive Or Mem Flds SS SI D1(B1),I2

TESTING BITS TM Test Under Mask

I2 is one byte. Bits corresponding to '0' bit(s) in the mask byte are not tested. Associated Branch Instructions BZ BO BM Branch if Zeroes Branch if Ones Branch if mixed All tested bits are '0' or all mask bits are '0' All tested bits are '1' Tested bits are a mix of '0' and '1'

ASSEMBLY LANGUAGE - 25/09/2004

36 / 116

BRANCHING INSTRUCTIONS
BRANCH ON CONDITION CODE BRANCH AND LINK BRANCH ON COUNT BRANCH ON INDEX COMPARE TEMPORARY BRANCH BCR,BC BALR,BAL BCTR,BCT BXH,BXLE EX

back

BC Branch on Condition RX M1,D2(X2,B2) BE,BER,BNE,BNER,BL,BLR,BNL,BNLR BH,BHR,BNH,BNHR,BZ,BZR,BNZ,BNZR BM,BMR,BNM,BNMR,BP,BPR,BNP,BNPR BO,BOR,BNO,BNOR, NOP,NOPR,B,BR All implemented using BC instruction BRANCHING AND LOOPS BCT Branch on count RX R1,D2(X2,B2) Subtract 1 from R1 and test for non zero. Branch if non zero BXH Branch on Index High RS R1,R2,D3(B3) Increments or decrements Index Counting iterations Test to determine whether loop should be repeated BHX is normally used with decrementing BXLE is used with incrementing R1 is the Index register R2 contains the increment / R2+1 contains the limit S3 is the branch address

Example This example illustrates using the BXLE instruction to iterate through arrays LA 7,LIMIT LA 6,INCR L 5,=F'0' LOOP L 3,X(5) A 3,Y(5) A 3,Z(5) BXLE 5,6,LOOP . X DS 20F Y DS 20F Z DS 20F LIMIT EQU Y-X-1 INCR EQU 4

ASSEMBLY LANGUAGE - 25/09/2004

37 / 116

ASSEMBLER DIRECTIVES
CSECT Indicates the beginning of a control section Smallest portion of the code which can be relocated A program can have more than one CSECT CSECTS can be continued across CSECTS or DSECTS Separate location counter for each CSECT Symbols are not addressable across CSECT s

back

RSECT Defines a read only CSECT and makes the Assembler check for possible violations. The assembler check is not fool proof. DSECT Dummy Control Sections To describe the structure of a block of data in memory without actually allocating memory Acts as a template (for example with storage obtained dynamically at run time) No code is generated DC statement is not allowed in a DSECT Example: CUSTOMER DSECT FIELD1 DS CL3 FIELD2 DS CL10 FIELD3 DS CL10 FIELD4 DS CL10 FIELD5 DS F CITY DS PL5 USING USING <symbol>, Rn Symbol can be any relocatable symbol defined in the program * can be used in the place of symbol Fields in the DSECTs are accessed after Establishing a base register with USING instruction at Assembly time Initialising the Base Register with the address of the storage area at run time. Rn, base register, to be used by the assembler for resolving the symbols in the base displacement FORM The location counter of the symbol is used as the base from which displacements are calculated Users responsibility to load the base register with base address BALR instruction can be used to load the base address Range of a base register is 4096 including the base If the code size is more than 4096 bytes, multiples base registers have to be used Example : BALR 12,0 Load the base address USING *,12 Reg 12 is a base register USING PROG,10 Base for DSECT PROG ORG ORG <EXPR> If expr is specified, location counter is set up with expr value If expr is not specified, location counter takes previous maximum value Used to redefine the storage Example: BUFFER DS 100F ORG BUFFER A DS CL80

ASSEMBLY LANGUAGE - 25/09/2004

38 / 116

B C D

DS DS DS ORG

CL80 CL80 CL80

DROP DROP (R0,R1,...RN) Specified registers are dropped as base registers Example BALR 12,0 USING *,12 . . . DROP 12 END LABEL Signals the end of a control section or program, Label is the entry point

EJECT Force a form feed The directive itself not printed in the listing LTORG Forces assembler to dump the literals collected up to that point EXTRN, ENTRY This example illustrates how a data item can be externalised and the address of the data item caught in another program. The second program can then manipulate the data in the data item. TEST5 CSECT ENTRY STM BALR USING ST LA WTO LA WTO L BALR WTO LA WTO L LM LA BR DS DC DC DC DC END DATA 14,12,12(13) 12,0 *,12 13,SAVE+4 13,SAVE 'IN ASM4 BEFORE CALL TO SUB4' 3,MSG TEXT=(3) 15,ASUB1 14,15 'IN ASM4 AFTER CALL TO SUB4' 3,MSG TEXT=(3) 13,SAVE+4 14,12,12(13) 15,4 14 18F A(SAVE) V(SUB4) AL2(L'DATA) CL20'DATA BEFORE CALL'

SAVE ASUB1 MSG DATA

ASSEMBLY LANGUAGE - 25/09/2004

39 / 116

SUB4

SAVE ADATA

CSECT EXTRN STM BALR USING ST LA WTO L MVC WTO L LM SR BR DS DC END

DATA 14,12,12(13) 12,0 *,12 13,SAVE+4 13,SAVE 'IN SUB 4 BEFORE CHANGING DATA' 3,ADATA 0(20,3),=CL20'DATA AFTER CHANGE' 'IN SUB 4 AFTER CHANGING DATA' 13,SAVE+4 14,12,12(13) 15,15 14 18F A(DATA)

WXTRN

defines a weak external reference. A weak external reference does not trigger a linkage editor auto call. Note that in the following example the linkage editor does not object to SAVE1 remaining unresolved. However, in the course of resolving strong external references, if an ENTRY of SAVE1 is found then it is resolved in this module.

Example This example illustrates how you must test whether a WXTRN has been resolved before you use the reference. WXT CSECT WXTRN WXDATA STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE L 4,AWXDATA LTR 4,4 BZ NOTRES RES . . USE ADDRESS . NOTRES . NOT RESOLVED . L 13,SAVE+4 LM 14,12,12(13) SR 15,15 BR 14 SAVE DS 18F AWXDATA DC A(WXDATA) END COM

ASSEMBLY LANGUAGE - 25/09/2004

40 / 116

Defines a common section. All common sections across CSECTS with the same name map to the same storage. The storage for COMMON sections is allocated at the time the load module is built. Example This example illustrates how a COM area may be defined and shared across CSECTS. COM CSECT COM AMODE 31 COM RMODE ANY STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE L 15,ASUB BALR 14,15 ICM 4,B'1111',ACOM WTO TEXT=(4) L 13,SAVE+4 LM 14,12,12(13) LA 15,0 BR 14 SAVE DS 18F ASUB DC V(SUB) ACOM DC A(COMMON) COMMON COM MSG DS AL2 DS CL100 END SUB SUB SUB CSECT AMODE RMODE STM BALR USING ST LA L LA STH MVC L LM LA BR DS DC COM DS DS END 31 ANY 14,12,12(13) 12,0 *,12 13,SAVE+4 13,SAVE 4,ACOM 5,15 5,0(0,4) 2(15,4),=CL15'THIS IS SUB' 13,SAVE+4 14,12,12(13) 15,0 14 18F A(COMMON) AL2 CL100

SAVE ACOM COMMON MSG

ASSEMBLY LANGUAGE - 25/09/2004

41 / 116

JCL ASPECTS
COPY BOOKS SOURCE MACLIBS

back

ASSEMBLER

OBJECT LIBRARIES

OBJECT DECK

LINKER

LOAD MODULE LOAD IN MAIN STORAGE FOR EXECUTION

program consists of Machine instructions Assembler instructions Macro Instructions. Development cycle Coding Pre Assembly Assembly Linkage Edit Program fetch

JCL:- The ASMACL procedure that assembles and links a assembler program can be used. It is usually found in SYS1.PROCLIB. Look at this JCL on your system and understand the JCL. If the C step is the compilation step and the L step is the Link edit step, the following DDNAMES refer to the data sets mentioned against each:C.SYSIN points to the source C.SYSLIB points to the Macro and Copy book libraries C.SYSPRINT is the compilation listing. L.SYSLIB points to an Object code Library which may contain subprograms in Object form L.SYSLMOD points to the target Load library. L.SYSPRINT is the linkage editor listing. The C.SYSUT1 and L.SYSUT1 datasets are work files.

ASSEMBLY LANGUAGE - 25/09/2004

42 / 116

Some of the Important linkage editor options are given below LET allows you to specify severity level of an error to determine whether the load module is to be marked as unusable. MAP | NOMAP Use map if you want a generated map of the load module NCAL Do not make an automatic search of the object libraries when linking. Make sure you remove it RENT Indicates module is re-entrant, NORENT marks it as non re-entrant AMODE 24|31|ANY . Use this parameter to override the attribute established by the assembler in the assembly process RMODE 24|ANY overrides this attribute as set by the assembly process Assembler OBJECT and LIST are the usual compilation options. ALIGN instructs assembler to check for alignment where it is required default ALIGN DECK ESD Assembler generates object deck on SYSPUNCH default NODECK The External symbol dictionary is produced in the listing default ESD

OBJECT instructs the assembler to generate an object data set on SYSLIN default OBJECT RENT instructs the assembler to check for possible violations of re-entrant default NORENT RLD the assembler outputs the relocation dictionary in the listing default RLD

SYSPARM SYSPARM ( parmvalue) max 255 chars XREF(FULL) Ordinary symbol and literal cross reference listing produced including symbols that are not referred to . XREF(SHORT) Omits symbols not referred to. Default XREF(SHORT,UNREFS) Special Considerations when the member name and the CSECT name do not match. Source File-1 TEST6 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE WTO 'IN ASM3 BEFORE CALL TO SUB1',ROUTCDE=(11) L 15,ASUB1 BALR 14,15 WTO 'IN ASM3 AFTER CALL TO SUB1',ROUTCDE=(11) L 13,SAVE+4

ASSEMBLY LANGUAGE - 25/09/2004

43 / 116

SAVE ASUB1 ASUB2

LM SR BR DS DC DC END

14,12,12(13) 15,15 14 18F V(SUB1) Does not pose problems V(SUB2) Does pose a problem

Source File-2, compiled and stored as SUB1 in the Object Library. It contains both SUB1 as well as SUB2 CSECT. SUB1 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE WTO 'IN SUB 1',ROUTCDE=(11) DC F'0' L 13,SAVE+4 LM 14,12,12(13) SR 15,15 BR 14 SAVE DS 18F * * NEW CSECT * SUB2 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE1+4 LA 13,SAVE1 WTO 'IN SUB 2',ROUTCDE=(11) L 13,SAVE1+4 LM 14,12,12(13) SR 15,15 BR 14 SAVE1 DS 18F * * note that duplicate labels are not permitted in the same * source file * END If you are calling SUB2 , the linkage editor cannot resolve the external reference unless you make the editor explicitly include module with the control statement below:-

//LKED.SYSIN INCLUDE /*

DD * SYSLIB(SUB1)

Alternately, you can link edit the file containing SUB1 and SUB2 into a load module. Give the Load module a primary name of SUB1 and an ALIAS of SUB2. The syntax of the ALIAS linkage editor control statement is

ASSEMBLY LANGUAGE - 25/09/2004

44 / 116

ALIAS directory-name[(external symbol)]


Example

//LKED.SYSIN DD ALIAS SUB2 /*

Other Linkage editor control statements of interest are MODE Sets the mode for the Load Module

MODE

AMODE(31),RMODE(ANY)

LIBRARY specifies explicitly the Library to be used for specific external references

LIBRARY TESTLIB(DATE,TIME)
NAME Specifies the load module name. The (R) specifies that any existing module with the same name in the load library is to be replaced.

NAME

MYMOD(R)

SETSSI This sets the system service index of the module which is shown in a 3.4 DSLIST of the members of the LOAD Library members. It is represented as 8 hex digits.

SETSSI

00000001

In addition to AMODE, RMODE and SSI which are stored in the directory entry for the load module the following attributes can be set through the Linkage Editor PARM field:REUS The program is serially reusable. The system queues requests to use the module (via LINK, XCTL, ATTACH) if it is in use RENT The program is re-entrant. It means that more than one task can concurrently use the program. REFR The program is refreshable (it can be refreshed by a new copy from the PDS anytime , even while it is executing. If none of these are specified, it means that the program must be fetched afresh from the load library every time it is required. REFR implies RENT and REUS as well. RENT implies REUS as well. Note that using the program via BALR instruction can defeat the purpose of these attributes.

ASSEMBLY LANGUAGE - 25/09/2004

45 / 116

SUBROUTINES AND LINKAGES 24 BIT MODE

back SUBROUTINE Entry point Identified by a CSECT,START OR ENTRY assembler directives. An entry is made in the ESD for each Entry point. A CSECT can have multiple entry points specified by ENTRY directive Internal Subroutine :-A subroutine present in the source module from which it is called. External Subroutine :-A subroutine present in a different source module. Assembled and link edited separately Static Subroutine :- A subroutine which is known at the link edit time. Can be an internal or an external subroutine. Dynamic Subroutine:- A subroutine which is loaded at program run time using LOAD, LINK macros V-type address constant:- To refer a symbol defined in another CSECT. External symbol directory (ESD) :- A table containing information about the name, location and size off each all external symbols Linking to subroutine BALR R1,R2 Branch and link register (R1) <--PC,PC <--R2) BAL R1,S2 Branch and link (R1) <--PC,PC <--S2

The next instruction address is loaded in the register specified by the first operand and the branch is taken to the address specified by the second operand. If R2 is zero, then no branch is taken Return from subroutine BR R1 Branch register PC <--(R1) Branch unconditionally to the address specified in the operand 1 Example: MAIN START 0 . . BAL 14,SUB1 . L 15,SUB2 BALR 14,15 * RETURN. . * SUB1 DS OH BR 14 SUB2 DC V(SUBROUT2) END Saving and restoring environment Programs uses registers as base registers, index registers, and accumulators. If a program calls a subprogram, when the control returns, these register values should not be altered. To achieve this, the calling program provides a SAVEAREA into which the called program saves the registers. Before the control is returned from the subprogram, the registers are restored to their original values. Some subprograms return to the called program a return code (set in GPR15) and a reason code. It is a good programming practice to save and restore the environment. If this is done any subroutine can be used by any program with out the need to identify which registers are modified by the subroutine.

ASSEMBLY LANGUAGE - 25/09/2004

46 / 116

Convention for saving registers Every calling routine has a save area of 18 full-words for the use of called routine The calling routine passes the save area address in register 13 Every called routine saves the registers in this area before establishing addressability Address of called routine is in register 15 Register 14 has the return address SAVEAREA (18 Full words) layout Savearea+0 Reserved for PL/1 Savearea+4 Address of save-area of program which called this sub-program Savearea+8 Address of save-area of another program called by this program Savearea+12 This programs Register 14 contents saved by called program savearea+16 This programs Register 15 contents saved by called program savearea+20 This programs Register 0 contents saved by called program . . . . . . Savearea+64 This programs Register 11 contents saved by called program Savearea+68 This programs Register 12 contents saved by called program Example MAIN START STM BALR USING ST LR LA ST . . . LA L L LM BR DS END 0 14,12,12(13) 12,0 *,12 13,SAVE+4 2,13 13,SAVE 13,8(2)

15,0 13,SAVE+4 14,12(0,13) 0,12,20(13) 14 18F

* SAVE

Advantages of SAVEAREA Forward and backward pointers running through the save areas useful for trace-back Called program can first save the environment before acquiring storage in case of re-entrant program Parameter passing Fixed and variable number of parameters can be passed to a subprogram Parameters value are not passed directly Each parameter is saved in the storage. An array is created containing the addresses of the parameters in the order they are expected in the called program. Register 1 is loaded with the starting address of this address array. The last address in the array should have bit ' 0' set to ' 1' For variable number of parameters, the high order bit of the last parameter is set to one to indicate the end of parameter list

ASSEMBLY LANGUAGE - 25/09/2004

47 / 116

Example This example illustrates how three parameters P1,P2 and P3 may be passed by reference. . LA 2,P1 ST 2,PARM LA 2,P2 ST 2,PARM+4 LA 3,P3 ST 3,PARM+8 LA 1,PARM L 15,=V(PROC1) BALR 14,15 . . LA 1,=A(P2,P1,P3) L 15,=V(PROC2) BALR 14,15 . P1 DS CL8 P2 DC F'20' P3 DC C'ABCDEFGHIJKL' PARM DS 3F Accessing the parameters On entry to the subprogram, R1 contains the base address of the array of pointers. Each element of this array points to one of the parameters. Access the parameter pointer from the array and using this access the parameter itself. If a structure is passed as in the case of a COBOL program calling an Assembler program, the address list contains only the address of the first byte of the structure. You can use this address and map a DSECT over the calling programs data structure. The DSECT defines the same structure as that of the data structure in the calling program. Example of three parameters being passed to a sub program. LM 4,6,0(1) Fetch address of P1-P3 L 4,0(4) R4 has P1 L 4,0(5) R4 has P2 L 4,0(6) R4 has P3 Functions in Assembly language To pass back a return value from function set register 0 to that value The return value in R15 can be used to indicate an error condition A return code of 0 means successful completion Return codes are usually a multiple of 4, so that it can be used to index into an address Example MAIN

table

CSECT . . . LA L BALR ST .

entry linkages 1,=A(I,J) 15,=V(MIN) 14,15 0,K

ASSEMBLY LANGUAGE - 25/09/2004

48 / 116

I J K SAVE1 * MIN

. BR DC DC DS DS CSECT . . LM L L CR BGE LR B LR EQU . . . BR DS END

14 F'100' F'120' F 18F entry linkages 4,5,0(1) 4,0(4) 5,0(5) 4,5 BIG 0,5 RESTORE 0,4 * exit linkages 14 18F

BIG RESTORE

SAVE2

Example of capturing PARM data from JCL PARM CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE L 13,SAVE+4 L 2,0(0,1) LH 3,0(0,2) STCM 3,B'0011',MSG S 3,=F'1' EX 3,IN1 LA 4,MSG WTO TEXT=(4) LM 14,12,12(13) LA 15,0 BR 14 SAVE DS 18F IN1 MVC MSG+2(0),2(2) MSG DC AL2(0) DS CL100 END Example A different style of achieving addressability through R15!! TEST7 CSECT STM 14,12,12(13) USING TEST13,15 ST 13,SAVE+4

ASSEMBLY LANGUAGE - 25/09/2004

49 / 116

* * * * *

LR 2,13 LA 13,SAVE ST 13,8(0,2) LR 12,15 DROP 15 USING TEST13,12

SAVE

L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) BR 14 DS 18F END

Passing Structures (like a COBOL 01 level item) TEST8 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE L 15,ASUB LA 1,=A(PARMS) BALR 14,15 L 5,RES CVD 5,DW UNPK MSG+2(16),DW OI MSG+17,X'F0' WTO 'RESULT IS' LA 4,MSG WTO TEXT=(4) L 13,SAVE+4 LM 14,12,12(13) LA 15,0 BR 14 SAVE DS 18F MSG DC AL2(16) DS CL16 ASUB DC V(SUB2) DW DS D DS 0F PARMS DS 0CL12 A DC F'100' B DC F'200' RES DS F END SUB2 CSECT STM USING ST LA LR 14,12,12(13) SUB,15 13,SAVE+4 13,SAVE 12,15

ASSEMBLY LANGUAGE - 25/09/2004

50 / 116

SAVE PARMS A B RES

DROP USING LR WTO LR L USING L A ST L LM LA BR DS DSECT DS DS DS END

15 SUB,12 2,1 'IN SUB' 1,2 2,0(1) PARMS,2 5,A 5,B 5,RES 13,SAVE+4 14,12,12(13) 15,0 14 18F F F F

Standard Entry and Exit Linkages TEMP CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) * * * L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) BR 14 SAVE DS 18F END Standard Entry and Exit Linkages using GETMAINED storage TEMP1 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 LR 3,1 GETMAIN R,LV=LEN,LOC=BELOW ST 13,4(0,1) LR 2,13 LR 13,1 ST 13,8(0,2) USING WS,13 LR 1,3 * BUSINESS LOGIC STARTS * * BUSINESS LOGIC ENDS

ASSEMBLY LANGUAGE - 25/09/2004

51 / 116

WS SAVE LEN

LR 2,13 L 13,4(0,2) FREEMAIN R,LV=LEN,A=(2) RETURN (14,12),,RC=0 DSECT DS 18F EQU *-WS END

ASSEMBLY LANGUAGE - 25/09/2004

52 / 116

MACROS AND CONDITIONAL ASSEMBLY


Macro Macro

Back

An extension of assembler language. Provides convenient way to generate a sequence of assembler language statements A macro definition is written only once Macro invocation expands to the desired sequence of statements Conditional assembly statements can be used to tailor the statements generated Parameters can be passed to the macro Expanded during the pre-assembly time and generates inline code definition Can appear at beginning of a source module in which case it is called a source MACRO System macros reside in a system library (ddname SYSLIB) User macros reside in a user library or in the source program itself Nested macro invocations possible

Format of a Macro definition Header. Indicates the beginning of a macro definition (MACRO) Prototype statement. Defines the macro name and the symbolic parameters Body. Contains model statements, processing statements, comments statements and conditional assembly statements. Trailer. Indicates the end of a macro definition (MEND) Prototype Must be the second non-comment statement in every macro definition. Only internal comments are allowed between the macro header and the macro prototype. Format of the prototype statement: {Name} Name field : Operation {Operands}

Operation field: Operands : Macro

A variable symbol. The name entry in the calling macro instruction is assigned to this symbol. The name of the macro. The macro is invoked with this name. Specify positional or keyword parameters. Maximum 240 parameters can be passed

body : Contains the sequence of statements that are generated in the macro expansion. Model statements from which assembler language statements are generated. Processing statements that can alter the content and sequence off the statements generated or issue error messages. Comments statements. Conditional assembly instructions to compute results to be displayed in the message created by the MNOTE instruction, without causing any assembler language statements to be generated

Model Statement Assembler language statements are generated at pre-assembly time from model statement Variable symbols can be specified to vary the contents of the statements generated Statements generated must not be conditional assembly instructions Variable Symbols Prefixed with '&' character Can appear in macros and in conditional assembly statements Can be symbolic parameters, system variables or set symbols System variables are read only and their value is maintained by the Assembler

ASSEMBLY LANGUAGE - 25/09/2004

53 / 116

Example USER: SYSTEM:

&L &NAME &VARI &PARAM(1) &SYSNDX &SYSDATE &SYSECT

Concatenation (".") Used when a character string has to be concatenated to a variable symbol Concatenation character is mandatory 1) when an alphanumeric character is to follow a variable symbol 2) A left parenthesis that does not enclose a subscript is to follow a variable symbol To generate a period, two periods must be specified in the concatenated string following the variable symbol Concatenation character is not required 1) when an ordinary character string precedes a variable symbol 2) A special character, except a left parenthesis or a period, is to follow a variable symbol 3) A variable symbol follows another variable symbol 4) Between a variable symbol and its subscript String Symbol &FLD.A &FLD &FLDA &FLDA SUM &B &D.(&B) 10 &D &I &F D'&I..&F' D'&I.&F' &A+3 &A Value AREA SUM 100 99 98 A D'99.98' D'9988' A+3 Result AREAA

100(10)

Symbolic Parameters Variable symbols included in macro prototype are supplied values by the macro call Actual value supplied for a formal parameters is a character string (max=255chars) Two kinds of symbolic parameters Positional Parameters Keyword Parameters Null string for the omitted parameters Defaults can be specified for keyword parameters Parameters can be subscribed Have local scope Read only Example MACRO MAC1 &P1,&K1=10 . MEND Invocation of above Macro: START 0 . . . MAC1 ONE,K1=12 . MAC1 TWO .

ASSEMBLY LANGUAGE - 25/09/2004

54 / 116

. END Example MACRO DIVIDE M D&TYPE MEND Invocation MAIN

&R1,&R2,&TYPE &R1,=F`1' &R1,&R2

+ +

+ +

CSECT . . . DIVIDE M D . . DIVIDE M . . DR 4,6 END

8,NUM 8,=F`1' 8,NUM 4,6,R 4,=F'1'

Processing Statements Macro instruction Conditional assembly instructions Macro instructions MNOTE instruction <SEQ SYM> MNOTE <opt> <message> To generate error messages or display intermediate values of variable symbols Can be used in open code or in a macro Opt specifies a severity code. If"," is specified then the severity code value is "1" If opt is omitted or a `*' is specified, then the message is generated as a comment Example: MNOTE 2, `Error in syntax' MNOTE ,`Error, severity 1' MNOTE *, `A comment' MNOTE `Another comment' MEXIT instruction <SEQ SYM> MEXIT Exit from the current macro definition Can be used only inside a macro definition Comments A "*" in column generates an ordinary comment which will appear in the listing A ".*" sequence in column 1 generates an internal comment which will not appear in the listing System Variables Variables set by the system &SYSDATE, &SYSPARM, and &SYSNDX can be used only within a macro

ASSEMBLY LANGUAGE - 25/09/2004

55 / 116

Name Description &SYSLIST Provides alternate way of accessing positional parameters &SYSPARM To obtain the compile time parm value passed thru JCL EXEC statement &SYSECT To get the name of CSECT from where macro is invoked &SYSTIME To get time in HH.MM format &SYSDATE To get date in MM/DD/YY format Example Prototype statement : LOOP VNAME V1,V2,,V4,(V5,V6) &SYSLIST(0) = LOOP &SYSLIST(1) = V1 &SYSLIST(2) = V2 &SYSLIST(3) = NULL STRING &SYSLIST(4) = V4 &SYSLIST(5) = (V5,V6) &SYSLIST(5,1) = V5 &SYSLIST(5,2) = V6 N'&SYSLIST = 5 N'&SYSLIST(5) = 2 Sublists To specify variable number of parameters to a macro One or more entries separated by commas and enclosed in parenthesis Including the parenthesis, maximum length is 255 characters Example MACRO &L VAR &P1,&P2,&KEY=(F0,F,0) . &KEY(1) DC &KEY(2)'&KEY(3)' &P1(1) DC &P1(2) '&P1(3)' DC A&P2 . MEND invocation: MAIN +F1 +H20 + START . VAR DC DC DC END 0 (H20,H,200), (A,B,C),KEY=(F1,F,1) F' 1' H'200' A(A,B,C)

Labels in macro If ordinary symbols are used as label, then for each macro invocation, the same label will be generated and duplicate symbol error will occur at assembly time. To avoid this &SYSNDX system variable can be concatenated with a symbol, so that the label generated is unique. Example MACRO LOOP LOOP&SYSNDX EQU * BNE LOOP&SYSNDX MEND Invocation MAIN START LOOP 0

ASSEMBLY LANGUAGE - 25/09/2004

56 / 116

+LOOP0001 + +LOOP0002 +

EQU BNE LOOP EQU BNE

* LOOP0001 * LOOP0002

Conditional Assembly Selectively assemble a sequence of instructions Can be used in the open code or in the macros Processed at the pre-assembly time Many functions like a programming language is available Variable declarations and assigning values Arithmetic and logic functions Character processing Control facilities Conditional assembly statement labels are called sequence symbols and are prefixed with "." Set Symbols Provides arithmetic, binary, or character data Values can be varied at pre-assembly time Can be subscripted (set symbol array) Can be local(within a macro) or global (across other macros in this assembly)set symbols Used as Terms in conditional assembly expressions Counters, Switches and character strings Subscripts for variable symbol Values for substitution Global set symbols Values can be accessed any where in the source Has to be defined in each part of the program in which it is accessed (macro, open code) Declared using GBLA, for global arithmetic set symbols GBLB, for global binary set symbols GBLC, for global character set symbols GBLA and GBLB have a default value 0 (zero) GBLC has null string as default value SYNTAX GBLA <VARLIST> GBLB <VARLIST> GBLC <VARLIST> Example GBLA &TEST,&VAL GBLC &NAME,&ID GBLB &TRUE Local set symbols Values can be accessed only in the macro in which it is defined Declared using LCLA, for local arithmetic set symbols LCLB, for local binary set symbols LCLC, for local character set symbols LCLA and LCLB have default value 0 (zero) LCLC has null string as default value SYNTAX LCLA <VARLIST> LCLB <VARLIST>

ASSEMBLY LANGUAGE - 25/09/2004

57 / 116

LCLC <VARLIST> Example LCLA &CNT,&VAL LCLC &STR1 LCLB &TRUE Conditional Assembly Expressions Three kinds Arithmetic Character Binary Can be used as operands of conditional branch instruction To assign values to set symbols Arithmetic expressions are formed using arithmetic operators Character expressions can produce strings of up to 255 chars Parameter substitution within quoted strings Duplication factor for quoted strings Boolean expression by combining arithmetic or character expressions using relational operators Assigning Values to Set Symbols Global set symbols have to be defined before assigning values Undeclared set symbols are defined as local set symbols More than one element in an array can be assigned values in a single set statements Set Arithmetic <VAR SYMBOL> SETA <arithmetic expression> To assign an arithmetic value to a SETA symbol Value represented by SETC symbol variable string can be used as a term in an arithmetic expression provided they contain only numeric digits. Value represented by SETB symbol variable can also be used in arithmetic expression Valid unary operators are +,-.Binary operators are +,-,*,/ Examples &A SETA 10 10 &B SETA 2 2 &C SETA &A + 10/&B 15 &D SETA (&A+10)/&B 10 &A SETA 11 11 &B SETA &A/2 5 &A SETA 1 1 &B SETA &A/2 0 Set Binary <VAR SYMBOL> SETB <Boolean expression> Example &B SETB 1 &A SETB 0 To assign an binary bit value to a SETB symbol

Set Character <VAR SYMBOL> SETC <expression> To assign characters value to a SETC symbol The expression could be A type attribute reference A character expression A sub string notation

ASSEMBLY LANGUAGE - 25/09/2004

58 / 116

A concatenation of sub string notations, or character expressions, or both A duplication factor can precede any of the first three options Example: &C SETC 'STRING0' * * &C="STRING0" * &D SETC &C(4,2) * * &D = "IN" * &E SETC 'L''SYMBOL' * * &E = "L'SYMBOL" * &F SETC 'HALF&&' * * &F="HALF&" * &G SETC '&D.NER' * * &G="INNER" * &C1 SETC 3('ABC') * * &C1 = ABCABCABC * Example MACRO &NAME MOVE &TO,&FROM LCLA &A1 LCLB &B1,&B2 LCLC &C1 &B1 SETB (L'&TO EQ 4) &B2 SETB (S'&TO EQ 0) &A1 SETA &B1 &C1 SETC '&B2' &NAME ST 2,SAVEAREA L 2,&FROM&A1 ST 2,&TO&C1 L 2,SAVEAREA MEND Invocation MAIN HERE +HERE + + + START MOVE ST L ST L AIF 0 FLDA,FLDB 2,SAVEAREA 2,FLDB1 2,FLDAO 2,SAVEAREA (<LOGICAL EXPR>).<SEQ SYMBOL>

Conditional Branch <SEQ SYMBOL>

The logical expression in the operand field is evaluated at pre-assembly time to determine if it is true or false. If the expression is true, the statement named by the sequence symbol in the operand field is the

ASSEMBLY LANGUAGE - 25/09/2004

59 / 116

next statement processed. If the expression is false, the next sequential statement is processed by the assembler. Logical operators are EQ,NE,LE,LT,GE,GT Example AIF (`&C' EQ `YES').OUT .ERROR ANOP . . . .OUT ANOP Unconditional branch <SEQ SYMBOL> AGO <SEQ SYM2> Branches to the statement identified by "SEQ SYM2" Conditional Assembly Loop Counter <SEQ SYMBOL> ACTR <ARITHMETIC EXPRESSION> Set a conditional assembly loop counter either within a macro definition or in open code. Can appear any where in the program. Each time AGO or AIF is executed the counter value is decremented by one and if its is zero exit from the macro or stop processing the statements in the open code Avoids excessive looping Assembler has a default counter and it is initialised with 4096 NOP <sequence symbol> ANOP Performs no operation Used to define a sequence symbol which can be used in AIF and AGO

Data Attributes <c> 'SYMBOL Attribute Description T Type of the symbol Values returned by assembler are A,V,S,Q For the various address constants B Binary constant C Character constant D,E,L Floating point constant F,H Integer constants P Packed decimal constant H Hexadecimal constant Z Zoned decimal constant I Machine instruction M Macro J Control section T EXTRN symbol N Self defining term O undefined (omitted) L Length of symbol number of bytes C Number of characters contained by the variable symbol N Number of element in a sublist associated with the symbol D Defined attribute, indicates whether or not the symbol has been defined prior Example MACRO

ASSEMBLY LANGUAGE - 25/09/2004

60 / 116

LCLA &SYSLIST(0) .WHILE &I .DONE Macro

TABLE &I DS AIF DC SETA AGO MEND

0D (&I GT N'SYSLIST).DONE D'&SYSLIST(&I) &I+1 .WHILE

help facility <name> MHELP <value> Controls a set of trace and dump facilities Can occur anywhere in open code or in macro definitions Remains in effect until superseded by another MHELP statement More than one facility can be specified Value Function 1 Macro Call Trace 2 Macro Branch Trace 4 Macro AIF Dump 8 Macro Exit Dump 16 Macro Entry Dump 32 Global Suppression 64 Macro Hex Dump 128 Mhelp Suppression

ASSEMBLY LANGUAGE - 25/09/2004

61 / 116

Example of SAVE macro MACRO &LABEL SAVE .*

&REGS, &T, &ID

X X

AIF ('&LABEL' EQ '').NOLAB DS 0H ANOP AIF ('&ID' EQ '').CONTINU .* This is a macro comment B 12(15) * This is a normal assembler comment AIF ('&ID' EQ '*').IDHERE DC CL8'&ID' AGO .CONTINU .IDHERE ANOP AIF ('&LABEL' EQ '').NOID DC CL8'&LABEL' AGO .CONTINU .NOID ANOP DC CL8'&SYSECT' .CONTINU ANOP .* AIF ('&REGS' EQ '').NOREGS STM &REGS(1),&REGS(2),12(13) .NOREGS ANOP MEND &LABEL .NOLAB

ASSEMBLY LANGUAGE - 25/09/2004

62 / 116

Example of RETURN macro MACRO &LABEL RETURN .* LCLA .* &LABEL .NOLAB .* AIF DS ANOP AIF AIF AIF AIF AIF LA ANOP LM BR MEXIT ANOP SETA LR LM BR MEXIT ANOP AIF SETA AIF LA ST ANOP LM BR MEXIT ANOP SETA ST LM BR MEXIT ANOP AIF AIF LA ANOP BR MEXIT ANOP SETA LR BR

&REGS, &T, &RC= &WORK,&VALU ('&LABEL' EQ '').NOLAB 0H ('&REGS' EQ '').NOREGS (&REGS(1) GE &REGS(2)).RET1 (&REGS(2) EQ 15).RET1 ('&RC' EQ '').RCT3 ('&RC'(1,1) EQ '(').RCT2 15,&RC &REGS(1),&REGS(2),12(13) 14 &RC(1) 15,&VALU &REGS(1),&REGS(2),12(13) 14

X X

.RCT3

.RCT2 &VALU

.* .RET1 &WORK

('&RC' EQ '').RCT4 (15-&REGS(1))*4 ('&RC'(1,1) EQ '(').RCT1 15,&RC 15,12+&WORK.(13) &REGS(1),&REGS(2),12(13) 14 &RC(1) &VALU,12+&WORK.(13) &REGS(1),&REGS(2),12(13) 14

.RCT4

.RCT1 &VALU

.* .NOREGS

('&RC' EQ '').RCT6 ('&RC'(1,1) EQ '(').RCT5 15,&RC 14 &RC(1) 15,&WORK 14

.RCT6 .RCT5 &WORK

ASSEMBLY LANGUAGE - 25/09/2004

63 / 116

MEXIT MEND

ASSEMBLY LANGUAGE - 25/09/2004

64 / 116

MVS SYSTEM MACROS


QSAM

back

DCB Macro Included for every data set accessed by the program Access method depends upon the parameters passed to the DCB All parameters are keyword parameters specifying various options for the data set Generates non executable code (control block) and should therefore be coded in the data area Name DCB DDNAME =External DD name in JCL, DSORG =PS | PO, MACRF={{(G{M|L})} {(P{M|L})}} {(G{M|L},P{M|L})}} G specifies that GET macros are used. Specifying G also provides the routines that allow the problem program to issue RELSE macros. G is required if the OPEN option is INPUT or UPDAT. It has no effect if the OPEN option is OUTPUT or EXTEND. L specifies that the locate transmittal mode is used; the system provides the address of the buffer containing the data. M specifies that the move transmittal mode is used; the system moves the data from the buffer to the work area in the problem program. P specifies that PUT or PUTX macros are used. P is required if the OPEN option is OUTPUT or EXTEND. It has no effect if the OPEN option is INPUT. P may be specified if the OPEN option is UPDAT. LRECL =, BLKSIZE=, RECFM =F | FB | FBA | V |VBA, EODAD=, Notes:G P G,P M L F FB FBA V VB Get, Put, Get and PUT Move mode I/O Locate mode I/O Fixed unblocked Fixed blocked Fixed blocked with first character as a ASA control character. Used only for printer output Variable unblocked Variable blocked

Notes:In MOVE mode the data is transferred to or from a data area in your program. In LOCATE mode if you issue a GET the address of the record in the system buffer is returned in register 1. You can load it into a work register and map a DSECT over the system buffer by a USING instruction. If you issue a PUT in LOCATE mode the system returns you an address in register 1 where you can build the new record. The next PUT will write the previously built record and return you a new buffer address in register 1. DCBE Macro

ASSEMBLY LANGUAGE - 25/09/2004

65 / 116

This macro is used (optionally) to extend the DCB functionality. The most common use is when the program is changed from AMODE 24 to AMODE 31. See a sample program that illustrates this usage in the chapter on 24 / 31 bit programming issues. RDJFCB Macro This macro is used to change the JFCB (Job file control block) that the system creates, one for each DD statement. This macro copies the JFCB to a user defined 176 byte area where the information from the DD statement may be modified before the file is opened. Be aware that some operations need your program to be in authorised mode. The following program uses the same DD statement to open and read three PS files one at a time. Example This example illustrates how one single DD statement can be serially used to open and read three different files in the same VOLUME. RDJFCB CSECT SAVE (14,12) BALR 9,0 USING *,9 ST 13,SAVE+4 LA 13,SAVE * OPEN (SYSPRINT,OUTPUT),MODE=31 LTR 15,15 BNZ OPENERR * USING INFMJFCB,10 USING IHADCB,11 USING DSTBLMAP,12 * BAL 6,RDJFCB NEXTFILE BAL 6,MDFYJFCB BAL 6,OPEN BAL 6,PROCESS BAL 6,CLOSE B NEXTFILE CLOSE SYSPRINT VOLEND B RETURN * RDJFCB RDJFCB (FILEDCB,INPUT) LTR 15,15 BNZ NODD BR 6 NODD WTO 'FILE DD NOT SPECIFIED IN JCL' ABEND 901 * MDFYJFCB LA 10,JFCB L 12,DSTBLPTR CLI DSNAME,X'00' BE VOLEND MVC JFCBDSNM,DSNAME LA 14,TBLENLEN(0,12) ST 14,DSTBLPTR * OPEN LA 11,FILEDCB OPEN (FILEDCB,INPUT),TYPE=J LTR 15,15

ASSEMBLY LANGUAGE - 25/09/2004

66 / 116

BNZ BR * CLOSE * OPENERR * PROCESS

OPENERR 6

CLOSE (FILEDCB) BR 6 WTO 'OPENERROR' L 13,SAVE+4 RETURN (14,12),,RC=16 GET MVC PUT B BR FILEDCB,BUFFER OUTREC(80),BUFFER SYSPRINT,OUTCARD PROCESS 6

EOF * RETURN * SAVE DSTBLPTR * DSNTBL TBLENTBG

L 13,SAVE+4 RETURN (14,12),,RC=0 DS DC 18F A(DSNTBL) 0F * A(L'DS01) C'userid.FILE1' CL(45-L'DS01)' ' 0F * A(L'DS02) C'userid.FILE2' CL(45-L'DS02)' ' A(L'DS02) C'userid.FILE3' CL(45-L'DS03)' ' A X'00' TBLENTX-TBLENTBG CL8'SYSDSN' CL44 44F X'87' AL3(JFCB) CL80 /* this must be on a fullword boundary */

DS EQU DC DS01 DC DC DS TBLENTX EQU DC DS02 DC DC DC DS03 DC DC NULL DS DC TBLENLEN EQU * * QNAME DC RNAME DS * JFCB DS JFCBPTR DC DC BUFFER DS * FILEDCB DCB

DSORG=PS,MACRF=GM,EXLST=JFCBPTR,EODAD=EOF, DDNAME=INFILE

* OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, LRECL=137,BLKSIZE=1370,RECFM=VB *

ASSEMBLY LANGUAGE - 25/09/2004

67 / 116

DCBD DSORG=PS DSECT IEFJFCBN * DSTBLMAP DSECT DSNMLEN DS CL4 DSNAME DS CL44 DS CL1 END The JCL for the above program //userid1 JOB NOTIFY=&SYSUID,CLASS=A,MSGLEVEL=(1,1) // JCLLIB ORDER=(userid.PROCLIB) //STEP1 EXEC ASMACL,REGION=0M //ASM.SYSIN DD DSN=userid.ASM.SOURCE(RDJFCB),DISP=SHR //LKED.SYSLMOD DD DSN=userid.LOADLIB(RDJFCB),DISP=SHR //LKED.SYSLIB DD DSN=userid.OBJECT,DISP=SHR // DD DSN=CEE.SCEELKED,DISP=SHR //RUN EXEC PGM=RDJFCB //STEPLIB DD DSN=userid.LOADLIB,DISP=SHR // DD DSN=CEE.SCEERUN,DISP=SHR //SYSPRINT DD SYSOUT=* //INFILE DD VOL=SER=(volser),DISP=SHR OPEN Macro Name OPEN (DCB-name,{options...}) Logically connect a data set Data set identified in the DCB is prepared for processing Option Meaning INPUT Input data set OUTPUT Output data set UPDAT Data set to be updated in place EXTEND Add records to the end of the data set DISP Disp options (PASS,KEEP,DELETE,CATLG,UNCATLG) Example OPEN (EMPLOYEE,(INPUT),SALES,(OUTPUT)) CLOSE Macro Name CLOSE (DCB-NAME {,option),...}) Logically disconnect a data set Option Meaning REREAD Position to the beginning of the data set LEAVE Position to the logical end of the data set REWIND Magnetic tape has to be positioned at the beginning DISP Disp options like PASS,KEEP,DELETE,CATLG, and UNCATLG Example CLOSE (EMPLOYEE,SALES) GET Macro (QSAM) Name GET DCB-NAME, {area name} Retrieve the next record Control is returned after the record is read In locate mode the address of the record is returned in R1 In move mode the record is moved to the user area Example GET EMPLOYEE, EMPREC

ASSEMBLY LANGUAGE - 25/09/2004

68 / 116

PUT Macro (QSAM) Name PUT DCB-NAME,{area name} Write a record. Control is returned after the record is written In locate mode the area name parameter is omitted and the system returns the address of the I/O buffer in R 1. The data has to be moved to this area and it is written in the next PUT call. In moved mode, the system moves the record to an output buffer before the control is returned. Example PUT EMPLOYEE,EMPREC Example This example illustrates how a SYSPRINT (SYSOUT) file may be defined and created. PRINT CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE OPEN (SYSPRINT,OUTPUT) LTR 15,15 BNZ OPENERR LA 5,20 MVC OUTREC+1(132),=CL132'THIS IS LINE ONE.' LOOP PUT SYSPRINT,OUTCARD BCT 5,LOOP CLOSE SYSPRINT L 13,SAVE+4 RETURN (14,12),,RC=0 OPENERR L 13,SAVE+4 RETURN (14,12),,RC=16 OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, X LRECL=137,BLKSIZE=1370,RECFM=VBA SAVE DS 18F END Required JCL statement //SYSPRINT DD SYSOUT=* Example of LOCATE mode I/O GET QSAMLOCR CSECT SAVE (14,12) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) * OPEN (SYSPRINT,OUTPUT)

ASSEMBLY LANGUAGE - 25/09/2004

69 / 116

LTR 15,15 BNZ OPENERR1 * OPEN (INFILE,INPUT) LTR 15,15 BNZ OPENERR2 * USING INREC,2 * LOOP GET INFILE LR 2,1 MVC DATA+1(80),INDATA PUT SYSPRINT,RECORD B LOOP CLOSE SYSPRINT CLOSE INFILE L 13,SAVE+4 RETURN (14,12),,RC=0

* EOF

* OPENERR1 L 13,SAVE+4 RETURN (14,12),,RC=16 * OPENERR2 L 13,SAVE+4 RETURN (14,12),,RC=20 * SAVE DS 18F RECORD DC AL2(137),AL2(0) DATA DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,DSORG=PS,MACRF=PM,RECFM=VBA,LRECL=137, BLKSIZE=1370 INFILE DCB DDNAME=INFILE,DSORG=PS,MACRF=GL,EODAD=EOF * INREC DSECT INDATA DS CL80 END PUT in locate mode QSAMLOCW CSECT SAVE (14,12) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) * OPEN (SYSPRINT,OUTPUT) LTR 15,15 BNZ OPENERR1 * OPEN (INFILE,INPUT) LTR 15,15 BNZ OPENERR2 * OPEN (OUTFILE,OUTPUT)

ASSEMBLY LANGUAGE - 25/09/2004

70 / 116

LTR 15,15 BNZ OPENERR3 * USING INREC,2 * LOOP GET INFILE LR 2,1 PUT OUTFILE LR 3,1 MVC DATA+1(80),INDATA MVC 0(80,3),INDATA PUT SYSPRINT,RECORD B LOOP CLOSE SYSPRINT CLOSE INFILE CLOSE OUTFILE L 13,SAVE+4 RETURN (14,12),,RC=0

* EOF

* OPENERR1 L 13,SAVE+4 RETURN (14,12),,RC=16 * OPENERR2 L 13,SAVE+4 RETURN (14,12),,RC=20 * OPENERR3 L 13,SAVE+4 RETURN (14,12),,RC=24 * SAVE DS 18F RECORD DC AL2(137),AL2(0) DATA DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,DSORG=PS,MACRF=PM,RECFM=VBA,LRECL=137, BLKSIZE=1370 INFILE DCB DDNAME=INFILE,DSORG=PS,MACRF=GL,EODAD=EOF OUTFILE DCB DDNAME=OUTFILE,DSORG=PS,MACRF=PL,RECFM=FB,LRECL=80, BLKSIZE=800 * INREC DSECT INDATA DS CL80 END UPDATE (GET/PUTX) QSAMLOCU CSECT SAVE (14,12) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) * OPEN (INFILE,UPDAT) LTR 15,15 BNZ OPENERR *

X X

ASSEMBLY LANGUAGE - 25/09/2004

71 / 116

GET INFILE LR 2,1 MVC 0(4,2),=CL4'9999' PUTX INFILE * EOF * OPENERR * SAVE INFILE * INREC INDATA CLOSE INFILE L 13,SAVE+4 RETURN (14,12),,RC=0 L 13,SAVE+4 RETURN (14,12),,RC=16 DS 18F DCB DDNAME=INFILE,DSORG=PS,MACRF=(GL,PL),EODAD=EOF DSECT DS CL80 END

Memory Management GETMAIN To allocate virtual storage Can be allocated on double word or page boundary Storage is not initialised Storage allocation above or below 16MB line Use FREEMAIN to release the storage Register 1 contains the storage address Syntax Name GETMAIN RC,LV=lv,BNDRY=bndry,LOC=Loc R Register form LV Length value BNDRY DBLWD / PAGE LOC BELOW / ANY (16MB line) Example GETMAIN RC,LV=4096,BNDRY=PAGE,LOC=ANY

A simple Illustration of GETMAIN / FREEMAIN TEST9 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 GETMAIN R,LV=LEN,LOC=BELOW ST 13,4(0,1) LR 13,1 USING WS,13 LH 3,=H'16' STH 3,MSG MVC MSG+2(16),MSG1 LA 3,MSG WTO TEXT=(3) * * show where we getmained storage * CVD 13,DW UNPK MSG+2(16),DW

ASSEMBLY LANGUAGE - 25/09/2004

72 / 116

OI MSG+17,X'F0' LA 3,MSG WTO TEXT=(3) LR 2,13 L 13,4(0,2) FREEMAIN R,LV=LEN,A=(2) RETURN (14,12),,RC=0 * * constants can be part of CSECT like this * MSG1 DC CL16'THIS IS MSG 1' MSG2 DC CL16'THIS IS MSG 2' MSG3 DC CL16'THIS IS MSG 3' MSG4 DC CL16'THIS IS MSG 4' MSG5 DC CL16'THIS IS MSG 5' * * This DSECT maps over getmained storage * WS DSECT SAVE DS 18F MSG DS AL2 DS CL16 DW DS D ARRAY DS 1000D LEN EQU *-WS END Example DXD, CXD and Q Type Address Constant This example illustrates the use of DXD, CXD data types and Q type address constants. DXD refers to storage allocated in an external dummy section. A DSECT can also be considered an external dummy section if it is used in a Q type constant. The CXD is initialised by the linkage editor to the sum of the lengths of all external dummy sections in the load module. It is used to getmain storage for the external dummy sections at run time. The Q type address constants are set to the offset of the corresponding dummy sections. ROUTINE A A CSECT . L 3,LEN GETMAIN R,LV=(3) LR 11,1 . L 15,=V(C) BALR 14,15 . L 15,=V(B) BALR 14,15 . AX DXD 2DL8 BX DXD 4FL4 LEN CXD . DC Q(AX) DC Q(BX) .

ASSEMBLY LANGUAGE - 25/09/2004

73 / 116

ROUTINE B B CSECT . L AR ST . G DXD D DXD . GOFFS DC DOFFS DC . ROUTINE E ITEM NO SUM C C DSECT DS DS DS CSECT . L AR USING ST . . DC . .

3,DOFFS 3,11 2,0(0,11) 5D 10F Q(G) Q(D)

F F F 3,EOFFS 3,11 E,3 9,SUM Q(E)

EOFFS

FREEMAIN Releases the acquired virtual storage Address should be on a double word boundary Syntax Name FREEMAIN RC,LV=lv,A=addr RC Register form lv Length value A Virtual storage address Example FREEMAIN RC,LV=4096,A=(1)

Example of a program that dynamically acquires its working storage and initialises it with constants from static read only storage. TEST10 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 LR 2,1 GETMAIN R,LV=LEN,LOC=BELOW ST 13,4(0,1) USING WS,13 LR 13,1 LR 1,2

ASSEMBLY LANGUAGE - 25/09/2004

74 / 116

* * initialise the getmained storage at one shot * MVC WS+72(LEN-72),WSCONST+72 * * some initialisations, notably addresses of data items in * getmained storage can be done only at run time * BAL 2,INIT LOAD EP=ADD,ERRET=LOADERR LR 15,0 LA 1,PARM BASSM 14,15 WTO 'BACK' L 5,RES CVD 5,DW UNPK MSG+2(16),DW OI MSG+17,X'F0' WTO 'RESULT IS' LA 4,MSG WTO TEXT=(4) LR 2,13 L 13,SAVE+4 FREEMAIN R,LV=LEN,A=(2) LM 14,12,12(13) LA 15,0 BR 14 LOADERR WTO FAILED TO LOAD ADD L 13,SAVE+4 LM 14,12,12(13) LA 15,16 BR 14 WSCONST DS 0F DS 18F DC F'100' DC F'200' DS F DS F DS F DS F DC AL2(16) DS CL16 DS D LEN EQU *-WSCONST INIT DS 0H LA 3,A ST 3,PARM LA 3,B ST 3,PARM+4 LA 3,RES ST 3,PARM+8 BR 2 WS DSECT SAVE DS 18F A DS F B DS F

ASSEMBLY LANGUAGE - 25/09/2004

75 / 116

RES PARM MSG DW ADD

DS DS DS DS DS DS DS END CSECT STM BALR USING ST LA LR WTO LR LM L A ST WTO L LM LA BSM DS END

F F F F AL2 CL16 D

SAVE

14,12,12(13) 12,0 *,12 13,SAVE+4 13,SAVE 2,1 'IN ADD' 1,2 2,4,0(1) 5,0(0,2) 5,0(0,3) 5,0(0,4) 'EXITING ADD' 13,SAVE+4 14,12,12(13) 15,0 0,14 18F

Program Management LOAD Brings the load module into virtual storage Module contains program or table Placed above or below line Returns Authorisation code Length of the module Entry point to the module AMODE of the module Control is not passed to the module Used in dynamic subroutine call Modules can be shared

Name LOAD EP=entry name On return to caller the registers contain the following 0 Entry point address of requested load module. The high order bit reflects the load modules AM (1 for 31 bit AMODE, else 0 for 24 bit AMODE). If AMODE is any then the bit reflects callers AMODE. 15 Zero if no error, else reason code Example LOAD EP=MYPROG,ERRET=LERROR LR 15,0 stick to using register 15 for entry point BSSM 14,15 BSSM takes care of switch of AMODE if reqd.

ASSEMBLY LANGUAGE - 25/09/2004

76 / 116

. WTO LOAD OF MYPROG FAILED L 13,SAVE+4 RETURN (14,12),,RC=16 An important point to note is that if the module has already been loaded into the callers address space because of a earlier request ( Possibly from some asynchronous exit routine) then control is given to the existing copy of the module. Since we branch to the entry point directly, we can have a problem if the module is in use and it is not re-entrant or is only serially reusable. For this reason XCTL or LINK is preferred as the control is passed via system which checks for this possible source of error. DELETE Remove a module from virtual storage Entry name same as used in load macro Task termination removes the module Name DELETE EP=entry name Register 15 is zero on successful completion. CALL Name CALL entry-name | (n),(parm1,parm2,.),VL Notes Control returns only after called program returns. Hence register 15 reflects return code of called program If entry name is used, the called program gets link edited into the main program (caller) at linking time XCTL To transfer control to another module Module loaded if not in virtual storage Handles the addressing mode Control does not return back name XCTL (reg1,reg2), EP=entry name, PARAM=(parm1,parm2,),VL=1, MF=(E, user area | (n)) LERROR

Notes:- The reg1,reg2 indicates the registers that are to be restored from save area before the called routine gets control . Usually coded (2,12). MF=(E,User area). User area points to an area where the parameter list can be generated .Since the transfer is through the system, the system takes care of the AMODE switch if required. The system also takes care of re-entrancy of the module transferred to. Control does not return back to caller in any case. The caller has to dynamically acquire storage for the user area where the system generates the parameter list. Additionally parm1, parm2 etc must be in getmained storage so that the data areas are available even after the calling program transfers control to the target program. The receiving program gets control with register 1 pointing to the user area where the XCTL macro builds the parameter list. Example: This example illustrates how an XCTL may be issued. The point to note is that you must set up any parameters that are passed in GETMAINED storage. That is because the invoking programs storage is released on XCTL and cannot be used to set up parameters. XCTL CSECT STM 14,12,12(13)

ASSEMBLY LANGUAGE - 25/09/2004

77 / 116

BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE GETMAIN RC,LV=LEN,LOC=BELOW * LR USING LA ST LA ST * L L XCTL L LM SR BR DS DSECT DS DS DS EQU END CSECT STM BALR USING ST LA LR USING WTO L L L A CVD UNPK OI WTO L LM SR BR DS DS DC DS DSECT 13,SAVE+4 14,12(0,13) (2,12),EP=XCTL1,MF=(E,(2)),PARAM=(A1,A2) 13,SAVE+4 14,12,12(13) 15,15 14 18F 2A F F *-PARMS 2,1 PARMS,2 3,100 3,A1 3,200 3,A2

SAVE * PARMS A1 A2 LEN XCTL1

14,12,12(13) 12,0 *,12 13,SAVE+4 13,SAVE 2,1 PARMS,2 'IN XCTL1',ROUTCDE=(11) 6,ADDR 5,0(0,6) 6,ADDR+4 5,0(0,6) 5,DW MSG+2(8),DW MSG+9,X'F0' TEXT=MSG,ROUTCDE=(11) 13,SAVE+4 14,12,12(13) 15,15 14 18F D AL2(8) CL8

SAVE DW MSG PARMS

ASSEMBLY LANGUAGE - 25/09/2004

78 / 116

ADDR A1 A2

DS DS DS END

2A F F

LINK Name

To pass control to an entry point Module loaded if not in virtual storage Handles the addressing mode Parameter list could be passed Control returns back Error handling could be specified LINK EP=entry name, PARAM=(parm1,parm2,..),VL=1, ERRET=error routine

Called routine gets control with the following values in the register 1 address of parameter list 15 Entry address of called program If the link was unsuccessful the error routine gets control with the following 1 Abend Code that would have been issued if the caller had not provided error exit 2-12 unchanged 15 Address of the error exit 14 used as work register by system Example LINK . . DS DS EP=MYPROG,PARAM=(parm1,parm2), ERRET=ERROR F F

PARM1 PARM2 ERROR

Process Management ABEND Name ABEND compcode,REASON=,DUMP,STEP compcode REASON value 0 to 4095.Register notation (2) to (12) permitted This code is passed to subsequent user exits if specified. 32 bit hexadecimal value or 31 bit decimal number DUMP Requests a dump of virtual storage assigned to task. Needs //SYSABEND, //SYSDUMP or //SYSUDUMP DD statement to be present in the JCL for the job step. STEP Requests all tasks associated with this Job step of which this task is a part to abend ATTACH To create a new task New task is the subtask Parameter list could be passed ECB can be provided Limit priority same as that of the creating task Dispatching priority same as that of the creating task Use DETACH macro to remove the sub task Returns TCB address in register 1 Name ATTACH EP=entry name,

ASSEMBLY LANGUAGE - 25/09/2004

79 / 116

PARAM=(parm1,parm2,), VL=1, ECB=ecb-addr, EXTR=Address of end of task routine Registers on entry to subtask are 0 Used as work area by system 1 Used by macro to point to parameter list 2-12 Used as work registers by System 13 Should point to a 18F save area in callers module 14 Return address. Bit 0 is 0 if subtask gets control in 24 bit mode else 1 if subtask gets control in 31 bit mode 15 Entry point address of subtask Registers on return to caller after issue of ATTACH 1 address of TCB of subtask 15 A return code of non zero means subtask could not be attached Load Libraries searched are Job pack area Requesting tasks task library and all unique task libraries of parent tasks Step library Job library Link Pack area Link Library In simplest form usage can be : ATTACH EP=PROG1,ECB=ECB1 ECB1 DS F Notes: This macro creates a separate thread of execution in callers address space Within the Address space this subtask will compete for processor resources 1) There is a despatching priority for address space 2) At a lower level there is a despatching priority for the subtasks The attaching task has to wait for subtasks to end before terminating else it will abend when attempting to terminate The attaching task has to wait on the ECB which is posted by the system when the subtask ends The attaching task then issues a DETACH macro. EXTR exit routine gets control with the following register values 0 used as a work register by the system 1 Address of TCB of subtask. Needed for issuing DETACH macro 2-12 Work registers 13 18F save area provided by system 14 return address 15 entry point of exit routine DETACH Removes a subtask If issued before task completion, terminate the task Should be issued if ECB or ETXR is used in ATTACH Removing a task removes all its dependent tasks also If ECB or ETXR is used, and the parent task does not issue DETACH, then the parent task will abend Name DETACH tcb address | (n)

ASSEMBLY LANGUAGE - 25/09/2004

80 / 116

Operand can be in register notation in which case regs 1 thru 12 may be used. The TCB address should have been previously obtained by EXTR exit routine Example ATTACH LTR BNZ ST . . TCB1 DC ENDOFTSK DETACH BR WAIT EP=PROG1,EXTR=ENDOFTSK 15,15 ERROR 1,TCB1 save address of TCB for later use F'0' (1) 14

Wait for completion of events Initialise the ECB before calling A list of ECBs can be specified for waiting on any number of events

Example WAIT 1,ECB=ECB1 . . ECB1 DC F0 POST Posts a ECB through a system call Example LA 4,ECB1 POST (4) . . ECB1 DC F0 Example of MAIN creating two subtasks TASK1 and TASK2. The job step task waits for the sub tasks to complete before detaching the subtasks and exiting. MAIN1 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE WTO 'MAIN1 STARTING' ATTACH EP=TASK1,ECB=ECB1 LTR 15,15 BNZ ERROR1 ST 1,TCB1 ATTACH EP=TASK2,ECB=ECB2 LTR 15,15 BNZ ERROR2 ST 1,TCB2 WTO 'MAIN1 ENTERING WAIT FOR TASK1 COMPLETION' WAIT 1,ECB=ECB1 WTO 'MAIN1 ENTERING WAIT FOR TASK2 COMPLETION' WAIT 1,ECB=ECB2

ASSEMBLY LANGUAGE - 25/09/2004

81 / 116

ERROR1 ERROR2 SAVE ECB1 ECB2 TCB1 TCB2 TASK1

LA 4,TCB1 DETACH (4) LA 4,TCB2 DETACH (4) L 13,SAVE+4 RETURN (14,12),,RC=0 L 13,SAVE+4 RETURN (14,12),,RC=4 L 13,SAVE+4 RETURN (14,12),,RC=8 DS 18F DC F'0' DC F'0' DS F DS F END CSECT STM BALR USING ST LA LA WTO BCT L LM SR BR DS END CSECT STM BALR USING ST LA LA WTO BCT L LM SR BR DS END 14,12,12(13) 12,0 *,12 13,SAVE+4 13,SAVE 5,50 'TASK1 REPORTING' 5,LOOP 13,SAVE+4 14,12,12(13) 15,15 14 18F

LOOP

SAVE TASK2

LOOP

SAVE

14,12,12(13) 12,0 *,12 13,SAVE+4 13,SAVE 5,50 'TASK2 REPORTING' 5,LOOP 13,SAVE+4 14,12,12(13) 15,15 14 18F

Example This example illustrates how a main task and sub task can work in a synchronized fashion writing every alternate record to a shared SYSPRINT dataset. The synchronisation is achieved using WAIT and POST macros. ATTACH3 CSECT STM 14,12,12(13)

ASSEMBLY LANGUAGE - 25/09/2004

82 / 116

12,0 *,12 13,SAVE+4 13,SAVE (SYSPRINT,OUTPUT) EP=SUBTASK3,PARAM=(SYSPRINT,ECBM,ECBS), ECB=ECB1 ST 1,TCB1 LTR 15,15 BNZ ATTERR LA 4,50 MVC OUTREC+1(132),=CL132'MAIN MESSAGE' SR 5,5 LA 6,ECBS LA 7,ECBM POST (7) LOOP WAIT 1,ECB=ECBM PUT SYSPRINT,OUTCARD ST 5,ECBM POST (6) BCT 4,LOOP WAIT 1,ECB=ECB1 LA 4,TCB1 DETACH (4) CLOSE SYSPRINT L 13,SAVE+4 RETURN (14,12),,RC=0 ATTERR L 13,SAVE+4 RETURN (14,12),,RC=10 OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,DSORG=PS,MACRF=PM, LRECL=137,BLKSIZE=1370,RECFM=VBA SAVE DS 18F ECB1 DC F'0' ECBM DC F'0' ECBS DC F'0' TCB1 DS F END SUBTASK CODE: Compile and linkedit this first separately then, compile, linkedit and run 'attach3' SUBTASK3 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE MVC OUTREC+1(132), =CL132'Message from Subtask' SR 5,5 L 4,0(0,1) SYSPRINT L 6,4(0,1) ECBM L 7,8(0,1) ECBS LA 3,50

BALR USING ST LA OPEN ATTACH

ASSEMBLY LANGUAGE - 25/09/2004

83 / 116

LOOP1

SAVE OUTCARD OUTREC

WAIT PUT ST POST BCT L L LM BR DS DC DC END

1,ECB=(7) (4),OUTCARD 5,0(0,7) (6) 3,LOOP1 13,SAVE+4 14,12(0,13) 0,12,20(13) 14 18F AL2(137),AL2(0) CL133' '

RETURN Name RETURN (reg1,reg2),T,RC=retcode restores reg1 to reg2 from save area pointed by R13 T sets a flag in the save area in the called program for dump analysis if required Maximum value for return code is 4095 which is set in R15 (see example of implementation under MACROS and conditional assembly) SAVE Name SAVE (reg1,reg2) Saves reg1 thru reg2 in save area pointed to by R13 (see example of implementation under MACROS and conditional assembly) SNAP This macro enables you to take a snap shot of your program when it is running. It is useful for debugging run time errors. You can issue calls for the snap dump as often as you wish and specify the range of addresses, from one byte to your whole program. You can also request for a register dump and save area trace by coding PDATA=(REGS,SA) Here is a sample program skeleton for issuing a SNAP macro:BEGIN CSECT SAVE BALR USING ST LA . . OPEN LTR BNZ . . SNAP . . SNAP . . . (14,12) 3,0 *,3 13,SAVE+4 13,SAVE (SNAPDCB,OUTPUT) 15,15 ERROR3 DCB=SNAPDCB,ID=1,PDATA=(REGS,SA), STORAGE=(BEGIN,LAST) DCB=SNAPDCB,ID=2,PDATA=(REGS,SA), STORAGE=(BEGIN,LAST) X

ASSEMBLY LANGUAGE - 25/09/2004

84 / 116

ERROR3 SNAPDCB LAST

L 13,SAVE+4 RETURN (14,12),,RC=0 L 13,SAVE+4 RETURN (14,12),,RC=3 . DCB DSORG=PS,RECFM=VBA,BLKSIZE=882,LRECL=125, MACRF=W,DDNAME=SNAPDMP EQU * END BEGIN

REENTERABILITY For load modules which may be shared amongst more than one concurrent task, re-entrancy is important. Most macros (in standard form) generate an inline parameter list of data areas which are used for passing as well as receiving information from the macro call. Obviously inline parameter list makes the load module non re-entrant and at best serially re-entrant. For this reason to make a load module re-entrant, do not define data areas in the program which will be part of the load module. Instead at run time (using GETMAIN or STORAGE OBTAIN) to dynamically acquire storage. A typical example of this would be to acquire the 18 full word save area dynamically. Where the acquired area needs to be accessed by field you can use a DSECT to format the block of storage. As for MACROS IBM provides, apart from standard form which develops inline parameter lists, LIST and EXECUTE (MF=L or MF=E) form of the macro exist. The list form does not generate any executable code. Instead it generates only a parameter list. At run time you acquire storage equivalent in size to this list and copy the list to this area. This way each thread of execution will have it's own discrete parameter area. At run time use the execute form of the macro (which can also be used to change some of the parameters generated earlier) with a pointer to the parameter list built up in virtual storage. The list form of the macro is signalled to the assembler by the parameter MF=L The execute form is signalled to the assembler by using the parameter MF=E Example . . LA 3,MACNAME load address of the list generated LA 5,NSIADDR load address of end of list SR 5,3 GPR5 will now have length of list BAL 14,MOVERTN go to rtn to move list DEQ ,MF=(E,(1)) GPR1 points to parm list, execute form . . processing here . BR 14 * acquire storage sufficient to hold the list MOVERTN GETMAIN R,LV=(5) LR 4,1 address of area in gpr4 BCTR 5,0 subtract 1 from gpr5 EX 5,MOVEINST BR 14 MOVEINST MVC 0(0,4),0(3) change the length field and copy the list MACNAME DEQ (NAME1,NAME2,8,SYSTEM),RET=HAVE,MF=L NSIADDR EQU * NAME1 DC CL8'MAJOR' NAME2 DC CL8'MINOR'

ASSEMBLY LANGUAGE - 25/09/2004

85 / 116

Example using WTO The following example GETMAINS storage for the WTO parameter list as well as writable storage for the program (SAVE, MSG and the 16 byte display area. The ultimate test of the reentrancy of the program is in making it an RSECT and ensuring that the assembler does not detect any violations of re-entrancy. WTORENT RSECT STM 14,12,12(13) BALR 12,0 USING *,12 LR 2,1 GETMAIN RC,LV=LEN,LOC=BELOW ST 13,4(0,1) LR 3,13 LR 13,1 ST 13,8(0,3) LR 1,2 USING WS,13 GETMAIN RC,LV=WTOLEN,LOC=BELOW LR 2,1 MVC 0(WTOLEN,2),WTOL * LH 3,=H'40' STH 3,MSG MVC MSG+2(40),=CL40'THIS IS FROM WTORENT' * LA 3,MSG WTO TEXT=(3),MF=(E,(2)) * LR 2,13 L 13,SAVE+4 FREEMAIN RC,LV=LEN,A=(2) RETURN (14,12),,RC=0 * WTOL WTOLEN WS SAVE MSG LEN WTO TEXT=,ROUTCDE=(11),MF=L EQU *-WTOL DSECT DS 18F DS AL2 DS CL40 EQU *-WS END

ASSEMBLY LANGUAGE - 25/09/2004

86 / 116

VSAM MACROS
Macros Name ACB

back AM=VSAM, BUFND=, BUFNI=, BUFSP=, DDNAME=, MACRF=([ADR],[,CNV][,KEY][,DIR][,SEQ][,SKP][,IN][,OUT] ) EXLST= Always code VSAM for access to VSAM data sets Number of data buffers, default=2,override possible through JCL Number of Index buffers, default=1,override possible through JCL Size of area for Index and Data Buffers. Defaults to specification in catalogue Connects a DD statement in run time JCL with this ACB Address of EXLST macro ADR Access by RBA CNV Access by Control Interval KEY Access by Record Key DIR Direct Processing SEQ Sequential Processing SKP Skip Sequential Processing IN Input only OUT Input / Output

NOTES: AM BUFND BUFNI BUFSP DDNAME EXLST MACRF

: : : : : : :

Note: This macro generates a control block and should therefore be placed in Data area of your program Name EXLST [AM=VSAM] [,EODAD=(address[,A|N][,L] )] [,JRNAD=(address[,A|N][,L] )] [,LERAD=(address[,A|N][,L] )] [,SYNAD=(address[,A|N][,L] )] Is the exit routine for end of file exit routine for journal file updates/deletions/insertions Logical error exit Physical error exit Routine is active Routine is inactive Routine is to be dynamically loaded when required ACB=, AREA=, AREALEN=, RECLEN=, ARG=, KEYLEN=, OPTCD=, NXTRPL= : : Address of ACB macro (label) Always code VSAM (used for documentation purposes only)

Notes EODAD JRNAD LERAD SYNAD A N L Name RPL

NOTES : ACB AM

ASSEMBLY LANGUAGE - 25/09/2004

87 / 116

AREA

: In move mode address of work area for record (label of data area) : In locate mode is used by VSAM to set address of record in VSAM buffer AREALEN : Length of work area. In locate mode will be at least 4.(Full word) RECLEN : For a PUT request is length of record for variable length record : For a GET request is updated by VSAM to indicate length of record read ARG : Label of Argument Field (Key | RBA) field used with GET,PUT, : POINT KEYLEN : Used to specify key length if Generic key is used (OPTCD=GEN) NXTRPL : address of next RPL in chain if chained RPL'S are used. OPTCD : ( [ADR|CNV|KEY],[DIR|SEQ|SKP],[FWD|BWD],[ARD|LRD], : [NSP|NUP|UPD],[LOC|MVE],[ASY|SYN],[KEQ|KGE], : [FKS|GEN]) : : ADR Access by RBA : CNV Access by control interval : KEY Access by record key : : DIR Direct processing : SEQ Sequential Processing : SKP Skip sequential processing : : FWD Forward Sequential processing : BWD Backward Sequential processing : : : : : : : : : : : : : : : : : : : ARD LRD NSP NUP UPD LOC MVE ASY SYN FKS GEN KEQ KGE Start sequential processing forward or backward with the record identified by the ARG field For Backward processing start from the last record in the file No updating(for Direct processing VSAM is positioned at the next record in the file). No updating, VSAM is not positioned for subsequent processing Retain position for Updating Locate mode I/O(record is processed in VSAM Buffers) Move mode I/O(records are processed in programs data area) Asynchronous operation. Program can continue with other processing. Later uses CHECK macro to wait on completion synchronous operation. Program waits until operation is complete full key search generic search. KEYLEN must be specified search key equal search key greater than or equal.

You can code only one option from each group The options must be consistent with one another and with ACB parameters The first two groups correspond to the MACRF parameter in the ACB macro The third group specifies direction of processing The fourth group specifies whether processing is to start with last record in file or record identified by the ARG field

ASSEMBLY LANGUAGE - 25/09/2004

88 / 116

The fifth group specifies whether the record is being read with intention to update. If not which record is to be read next. The last group specifies whether the MOVE or LOCATE mode of I/O is to be used. This macro generates a control block and should therefore be placed in Data area of your program OPEN Address of ACB Macro CLOSE Address of ACB Macro GET RPL=Label of RPL macro PUT RPL=Label of RPL macro POINT RPL=Label of RPL macro ERASE RPL=Label of RPL macro

| (register) retrieve a record | (register) write a record | (register) position for subsequent access | (register) Delete a record

Note : These MACROS generate executable code and should therefore be in the Instruction area of the Program MACROS FOR CONTROL BLOCK MANIPULATION. SHOWCB TESTCB MODCB This macros is fetch control block fields This macro is used to test control block fields This macro used to modify control block fields ACB|EXLST|RPL=, AM=VSAM, only for documentation purpose AREA=, LENGTH=, FIELDS=(keyword[,keyword])

Name SHOWCB

Notes: ACB | EXLST | RPL AREA LENGTH FIELDS FOR RPL FOR EXLST FOR ACB

: Address (label) of specified Macro : Area into which VSAM will put the contents of field specified : Length of Data area specified under AREA. Each field of the ACB|EXLST| RPL macro fields are 4 bytes long except : DDNAME which is 8 bytes : Can be most of any field specified in the ACB|EXLST|RPL macro; : ACB,AREA,AREALEN,FDBK,KEYLEN,RECLEN : RBA,NXTRPL all one full word of data : EODAD,JRNAD,LERAD,SYNAD : ACBLEN length of ACB

Can be attributes of an open file as below AVSPAC number of bytes of available space BUFNO Number of buffers in use for this file CINV Size of Control Interval FS Percent of Free control intervals KEYLEN Length of key field LRECL Maximum record length NCIS Number of Control Interval Splits NDELR Number of deleted records from file NEXT Number of Extents allocated to file NINSR Number of records inserted in file NLOGR Number of records in file NRETR Number of records retrieved from file

ASSEMBLY LANGUAGE - 25/09/2004

89 / 116

NUPDR Number of records updated in file RKP Position of record key relative to start of record

Name TESTCB

ACB|EXLST|RPL=, AM=VSAM, ERET=, keyword=, OBJECT=

only for documentation purpose

ACB|EXLST|RPL ERET keyword OBJECT Example TESTCB

: Address(label) of any of the control block macros : Address of error handler to be executed if test cannot be executed : Any field of the ACB,EXLST,RPL macro; The length of any ACB,EXLST,RPL macro using the keywords ACBLEN,EXLLEN,RPLLEN : DATA or INDEX

RPL1

RPL=RPL1,FDBK=8 BE DUPKEY . . . RPL .

Notes: Some common VSAM FDBK codes are 8 Duplicate key 12 Record out of sequence 16 No record found 68 Access requested does not match access specified 92 A put for update without a corresponding get for update 104 Invalid or conflicting RPL options Name MODCB Example: MODCB . . . RPL . RPL=RPL1,OPTCD=(DIR) ACB|EXLST|RPL=, AM=VSAM, only for documentation purpose Operand keyword= new value

RPL1

Example to load a KSDS from a QSAM PS file Sample JCL to create the Cluster //userid1 JOB NOTIFY=&SYSUID,CLASS=A,MSGLEVEL=(1,1) // JCLLIB ORDER=(userid.PROCLIB) //STEP1 EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD * DELETE userid.KSDS1 DEFINE CLUSTER (NAME(userid.KSDS1) INDEXED KEYS(5,0) RECORDSIZE(80,80) TRACKS(1,1) VOLUME(USR001)) DATA(CONTROLINTERVALSIZE(2048))

ASSEMBLY LANGUAGE - 25/09/2004

90 / 116

// Sample JCL to print contents of the cluster //userid1 JOB MSGCLASS=A,NOTIFY=&SYSUID //MYSTEP EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD * PRINT INDATASET(userid.KSDS1) CHAR /* // The program that loads the file in sequential mode VSAMLS CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE OPEN (VSAMACB) LTR 15,15 BNZ ERR1 OPEN (QSAMDCB,INPUT) LTR 15,15 BNZ ERR2 LOOP GET QSAMDCB,BUFFER PUT RPL=RPL1 LTR 15,15 BZ OK WTO 'PUT ERROR FOR VSAM' OK B LOOP ERR1 WTO 'ERROR OPENING VSAM FILE' L 13,SAVE+4 RETURN (14,12),,RC=16 ERR2 WTO 'ERROR OPENING QSAM FILE' L 13,SAVE+4 RETURN (14,12),,RC=16 EOF WTO 'EOF ON INPUT' CLOSE (QSAMDCB) CLOSE (VSAMACB) L 13,SAVE+4 RETURN (14,12),,RC=0 SAVE DS 18F VSAMACB ACB AM=VSAM,DDNAME=OUTFILE,MACRF=(KEY,SEQ,OUT) RPL1 RPL AM=VSAM,ACB=VSAMACB,AREA=BUFFER,AREALEN=80,RECLEN=80, ARG=KEYFLD,OPTCD=(KEY,SEQ,FWD,MVE) BUFFER DS CL80 KEYFLD DS CL5 QSAMDCB DCB DDNAME=INFILE,DSORG=PS,EODAD=EOF,MACRF=GM END Example to read a VSAM KSDS sequentially VSAMRS CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4

ASSEMBLY LANGUAGE - 25/09/2004

91 / 116

LA 13,SAVE OPEN (VSAMACB) LTR 15,15 BNZ ERR1 OPEN (SYSPRINT,OUTPUT) LTR 15,15 BNZ ERR2 LOOP GET RPL=RPL1 MVC OUTREC+1(80),BUFFER PUT SYSPRINT,OUTCARD B LOOP ERR1 WTO 'ERROR OPENING VSAM FILE' L 13,SAVE+4 RETURN (14,12),,RC=16 ERR2 WTO 'ERROR OPENING SYSPRINT FILE' L 13,SAVE+4 RETURN (14,12),,RC=16 EOF WTO 'EOF ON INPUT' CLOSE (SYSPRINT) CLOSE (VSAMACB) L 13,SAVE+4 RETURN (14,12),,RC=0 SAVE DS 18F VSAMACB ACB AM=VSAM,DDNAME=INFILE,MACRF=(KEY,SEQ,IN),EXLST=EXLST1 RPL1 RPL AM=VSAM,ACB=VSAMACB,AREA=BUFFER,AREALEN=80,RECLEN=80, OPTCD=(KEY,SEQ,FWD,MVE) EXLST1 EXLST AM=VSAM,EODAD=EOF BUFFER DS CL80 OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, LRECL=137,BLKSIZE=1370,RECFM=VBA END Example to read a VSAM KSDS in direct mode VSAMRD CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE OPEN (VSAMACB) LTR 15,15 BNZ ERR1 OPEN (SYSPRINT,OUTPUT) LTR 15,15 BNZ ERR2 OPEN (KEYFILE,INPUT) LTR 15,15 BNZ ERR3 LOOP GET KEYFILE,KEYBUFF MVC KEYFLD,KEYBUFF GET RPL=RPL1 LTR 15,15 BZ OK MVC OUTREC,=CL133' '

ASSEMBLY LANGUAGE - 25/09/2004

92 / 116

SHOWCB AM=VSAM,RPL=RPL1,AREA=FDBKAREA,FIELDS=(FDBK),LENGTH=4 L 4,FDBKAREA CVD 4,DW UNPK STATUS,DW OI STATUS+15,X'F0' MVC OUTREC+40(16),STATUS MVC OUTREC+1(15),=CL15'INVALID KEY' MVC OUTREC+20(5),KEYFLD PUT SYSPRINT,OUTCARD B LOOP OK MVC OUTREC+1(80),BUFFER PUT SYSPRINT,OUTCARD B LOOP ERR1 WTO 'ERROR OPENING VSAM FILE' L 13,SAVE+4 RETURN (14,12),,RC=16 ERR2 WTO 'ERROR OPENING SYSPRINT FILE' L 13,SAVE+4 RETURN (14,12),,RC=16 ERR3 WTO 'ERROR OPENING KEYFILE' L 13,SAVE+4 RETURN (14,12),,RC=16 EOF WTO 'EOF ON INPUT' CLOSE (SYSPRINT) CLOSE (VSAMACB) CLOSE (KEYFILE) L 13,SAVE+4 RETURN (14,12),,RC=0 VSAMACB ACB AM=VSAM,DDNAME=INFILE,MACRF=(KEY,DIR,IN) RPL1 RPL AM=VSAM,ACB=VSAMACB,AREA=BUFFER,AREALEN=80,RECLEN=80, OPTCD=(KEY,DIR,MVE),ARG=KEYFLD SYSPRINT DCB DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, LRECL=137,BLKSIZE=1370,RECFM=VBA KEYFILE DCB DSORG=PS,MACRF=GM,DDNAME=KEYFILE,EODAD=EOF SAVE DS 18F BUFFER DS CL80 KEYFLD DS CL5 KEYBUFF DS CL80 OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' FDBKAREA DS F STATUS DS CL16 DW DS D END Example of direct insertion VSAMUD CSECT SAVE (14,12) BALR 3,0 USING *,3 ST 13,SAVE+4 LA 13,SAVE OPEN (FILE1,INPUT) LTR 15,15 BNZ ERROR1 OPEN (VSAMACB)

X X

ASSEMBLY LANGUAGE - 25/09/2004

93 / 116

LOOP

ERROR1 ERROR2 EOFRTN INBUFF OUTBUFF OUTKEY SAVE FILE1 VSAMACB VSAMRPL

VSAMKEY

LTR 15,15 BNZ ERROR2 GET FILE1,INBUFF MVC OUTBUFF,INBUFF MVC VSAMKEY,OUTKEY PUT RPL=VSAMRPL B LOOP L 13,SAVE+4 RETURN (14,12),,RC=1 L 13,SAVE+4 RETURN (14,12),,RC=2 CLOSE (FILE1,,VSAMACB) L 13,SAVE+4 RETURN (14,12),,RC=0 DS CL80 DS 0CL80 DS CL5 DS CL75 DS 18F DCB DSORG=PS,RECFM=FB,BLKSIZE=800, LRECL=80,MACRF=GM,DDNAME=INFILE, EODAD=EOFRTN ACB AM=VSAM,DDNAME=OUTFILE, MACRF=(KEY,DIR,OUT) RPL AM=VSAM,ACB=VSAMACB, AREA=OUTBUFF,AREALEN=80, ARG=VSAMKEY,KEYLEN=4, OPTCD=(KEY,DIR),RECLEN=80 DS CL5 END VSAMUD

X X X X X X

ASSEMBLY LANGUAGE - 25/09/2004

94 / 116

FRAMEWORK OF ASSEMBLER PROGRAMS TO ACCESS VSAM FILES Keyed Direct Deletion DELETE ACB MACRF=(KEY,DIR,OUT) LIST RPL ACB=DELETE,AREA=WORK,AREALEN=50, ARG=KEYFIELD,OPTCD=(KEY,DIR,SYN,UPD,MVE,FKS,KEQ) . . LOOP MVC KEYFIELD,source GET RPL=LIST LTR 15,15 BNZ ERROR . . B LOOP if you do not want to delete this record ERASE RPL=LIST LTR 15,15 BNZ ERROR ERROR . WORK DS CL50 KEYFIELD DS CL5

Note that when you GET a record with UPD in the OPTCD option of the RPL vsam maintains position after the get anticipating either an ERASE or PUT (update). Instead if you issue a GET it goes ahead with the GET and position for the previous record is lost. Keyed sequential retrieval (backward) INPUT ACB DDNAME=INPUT,EXLST=EXLST1 RETRVE RPL ACB=INPUT,AREA=IN,AREALEN=100, OPTCD=(KEY,SEQ,LRD,BWD) EXLST1 EXLST EODAD=EOD POINT RPL=RETRVE LTR 15,15 BNZ ERROR LOOP GET RPL=RETRVE LTR 15,15 BNZ ERROR . . process the record here B LOOP EOD EQU * . . come here for end of file ERROR . . come here for any error . IN DS CL100 Keyed Direct Retrieval in LOCATE mode(KSDS, RRDS) INPUT ACB MACRF=(KEY,DIR,IN) RETRVE RPL ACB=INPUT,AREA=IN,AREALEN=4,OPTCD=(KEY, DIR,SYN,NUP,KEQ,GEN,LOC),ARG=KEYAREA, KEYLEN=5 . . LOOP MVC KEYAREA,source GET RPL=RETRVE

X X

ASSEMBLY LANGUAGE - 25/09/2004

95 / 116

ERROR IN KEYAREA

LTR BNZ . . B .. . DS DS

15,15 ERROR Address of record is now in IN LOOP CL4 CL5 Where VSAM puts the address of the record in the I/O buffer

Notes: In LOCATE mode (LOC) there is no transfer of the record from the VSAM buffer to the data area in your program. Instead VSAM supplies your program the address of the record in the VSAM (Control Interval) buffer. When Generic (GEN) is specified also specify KEYLEN=, and condition like KEQ. VSAM positions at first record which meets the condition. To continue in the sequence Change to sequential mode and issue GET(s). Or use GET with KGE using the key of the current record If the data set is a RRDS the ARG field the search argument is a relative record number Position with POINT macro BLOCK ACB DDNAME=IO POSITION RPL ACB=BLOCK,AREA=WORK,AREALEN=50, ARG=SRCHKEY,OPTCD=(KEY,SEQ,SYN,KEQ,FKS) LOOP MVC SRCHKEY,source POINT RPL=POSITION LTR 15,15 BNZ ERROR LOOP1 GET RPL=POSITION LTR 15,15, BNZ ERROR . process record . B LOOP1 continue in sequential mode ERROR . SRCHKEY DS CL5 WORK DS CL50 Keyed Sequential insertion KSDS variable length BLOCK ACB DDNAME=OUTPUT,MACRF=(KEY,SEQ,OUT) LIST RPL ACB=BLOCK,AREA=BUILDRCD,AREALEN=250, OPTCD=(KEY,SEQ,SYN,NUP,MVE) LOOP L 2,source-length MODCB RPL=LIST,RECLEN=(2) * * alter record length field * LTR 15,15 BNZ ERROR PUT RPL=LIST LTR 15,15 BNZ ERROR B LOOP ERROR . BUILDRCD DS CL250

ASSEMBLY LANGUAGE - 25/09/2004

96 / 116

Keyed direct insertion OUTPUT ACB MACRF=(KEY,DIR,OUT) RPL1 RPL ACB=OUTPUT,AREALEN=80, OPTCD=(KEY,DIR,SYN,NUP,MVE), AREA=WORK * * set up record in WORK * LOOP PUT RPL=RPL1 LTR 15,15 BNZ ERROR * set up next record B LOOP ERROR .. WORK DS 80C Note VSAM extracts the key field from the record area. Keyed Direct Update INPUT ACB MACRF=(KEY,DIR,OUT) UPDTE RPL ACB=INPUT,AREA=IN,AREALEN=120, OPTCD=(KEY,DIR,SYN,UPD,KEQ,FKS,MVE), ARG=KEYAREA,KEYLEN=5 * * set up search argument * LOOP GET RPL=UPDTE LTR 15,15 BNZ ERROR SHOWCB RPL=UPDTE,AREA=RLNGTH,FIELDS=RECLEN,LENGTH=4 LTR 15,15 BNZ ERROR * * update the record * does the new record have a different length BE STORE If not go to PUT L 5,length set R5 for new length MODCB RPL=UPDTE,RECLEN=(5) LTR 15,15 BNZ ERROR STORE PUT RPL=UPDTE LTR 15,15 BNZ ERROR B LOOP ERROR .. IN DS CL120 KEYAREA DS CL5 RLGTH DS F

X X

X X

ASSEMBLY LANGUAGE - 25/09/2004

97 / 116

LINKAGE CONVENTIONS 24 / 31 BIT ADDRESSING

back

LINKAGE CONVENTIONS Another program can be invoked through BALR, BASR, BASSM or LINK, XCTL and CALL macros A primary mode program is one which operates in primary Address Space Control mode or primary ASC for short. In this mode access of machine instructions is only in the primary address space. All your application programs run in this mode. System programs, like the DB2 subsystem, etc can switch to Address Space modes. The called program needs to save the registers when it receives control and restore them when returning. For this the caller provides a 18 Full word save area pointed to by R13. When a caller provides a 18F save area the area is used as below Word Usage 0 Used by language products 1 Address of previous ( caller) save area 2 Address of next save area 3 GPR14 4 GPR15 5-17 GPR0-12 Example of using the caller provided save area Calling program linkage . LA 1,=A(P1,P2,P3+X80000000) L 15,=V(PGM) BALR 14,15 . Called program linkage PGM CSECT PGM AMODE 31 PGM RMODE ANY STM 14,12,12(13) save callers registers in callers save area LR 12,15 set up base register LR 2,1 USING PGM,12 GETMAIN RC,LV=72 obtain save area ST 13,4(,1) and store callers R13 point in it ST 1,8(,13) store this programs save area in callers save area LR 13,1 set R13 to point to this save programs area LR 1,2 LM 2,4,0(1) set R2 thru R3 to address of P1,P2 and P3 . . . LR 2,13 Set R1 to the address of this programs save area L 13,4(,13) set R13 to point to callers save area FREEMAIN RC,A=(2),LV=72 release this programs save area SR 15,15 Zero R15 L 14,12(0,13) Restore R14 of caller LM 0,12,20(13) Restore R2 to R12 of caller BR 14 Return END

ASSEMBLY LANGUAGE - 25/09/2004

98 / 116

Calling program must do the following On entry: Save callers registers 14 thru 12 in the save area pointed to by R13 + 12 bytes Offset. Establish a GPR as a base register. Establish a base area of 18 Full words of its own. Save callers R13 into our own save area + 4. Set GPR 13 to point to its own save area Set our save area address into callers save area + 8 (optional). On exit Place parameter information that may be returned to caller in R1, R0 Load R13 with callers save area address and restore R0-R12,R14 Load R15 with return code Issue the BR 14 instruction. Passing Parameters Use R1 to point to a parameter list which is an array of 32 bit addresses which point to parameters. The last element of the Address List array should have bit 0 set to 1 to indicate it is the last element. GPR1 A(PARM1) A(PARM2) A(PARM3) 2 BYTE LENGTH 2 BYTE LENGTH PARM FIELD PARM FIELD

B1+ A(PARMN) Example if control is passed to another program in same mode. L CNOP BAL PARMLIST DS DCBADDR DC DC ANSWERAD DC NEXTADDR DC GOOUT BALR RETURN . . P1 DC P2 DC P3 DC 15,NEXTADDR 0,4 1,GOOUT 0A A(P1) A(P2) A(P3+X'80000000) V(SUBPGM) 14,15 12F'0' . .

Addressing AMODE is the mode in which a program expects to receive control. AMODE = 31 means that the program expects to receive control in 31 bit mode (bit 32 of PSW on) and any addresses are passed as 32 bit values with bit 0 on to represent 31 bit addressing mode. AMODE = 24 means

ASSEMBLY LANGUAGE - 25/09/2004

99 / 116

that the program expects to receive control in 24 bit addressing mode. In this case the high order 8 bits are not reckoned for computing the effective address. The mode of operation affects operation of some machine instructions like BAL, BALR, LA In the case of BAL and BALR, in 24 bit mode the link register (first operand) which contains the return address in low order 24 bits, has the high order 8 bits set to the ILC (Instruction length code, CC (Condition code) and Program mask. When in 31 bit addressing mode the link register has bit 0 set to 1 and rest of the 31 bits represent the address. In the case of LA, in 24 bit mode the high order 8 bits are cleared and low order 24 bits are set to represent a 24 bit address. In 31 bit mode, bit 0 is set to 0 and rest of the bits represent a 31 bit address. RMODE of a program indicate where it can be loaded by the system for execution. A RMODE of any indicates it can be loaded either above or below what is known as the 16MB line or simply the line. A RMODE of 24 indicates that it is to be loaded only below the line. AMODE and RMODE can be set in the assembler source as below: MAIN MAIN MAIN CSECT AMODE RMODE 31 24 AMODE can be 24 / 31 / any.Default=24 RMODE can be 24 or any.Default=24.

Note that the attributes are propagated by the assembler, Linkage editor to the Directory entry for the load module in the PDS. The following instructions are used for linkage: BAL Branch and Link BAL Branch and Link Register BAS Branch and Save BASR Branch and Save register BSM Branch and Set mode BASSM Branch and save and set mode BAS and BASR perform as BAL and BALR when in 31 bit mode. Note that BAL and BALR will set the Link register as below in 24 bit mode: Prog ILCCC Mask Instruction Address 0 2 4 8 31 BAS and BASR set the high order byte to X00 in 24 bit mode. This is how BAS and BASR differ from BAL and BALR. BSM provides an unconditional branch to the address in operand 2, saves the current AMODE in the high order bit of the Link register (operand 1) and sets the AMODE to agree with the high order bit in the to address. address. BASSM does all that BSM does and in addition the link register contains the return If we need to transfer control without a change of addressing mode use the following combinations Transfer Return

ASSEMBLY LANGUAGE - 25/09/2004

100 / 116

BAL/BALR BAS/BASR

BR BR

If we need to change the AMODE as well use BASSM to call and BSM to return. Example This code program. TEST TEST TEST snippet switches a AMODE 24 program to 31 bit mode while calling a AMODE 31 CSECT AMODE RMODE . . L BASSM . . EXTRN DC . . END CSECT AMODE RMODE . . SLR BSM END 24 24 15,EPA 14,15 Obtain transfer address switch AMODE and branch

EPA

SUB31 A(X'80000000+SUB31) set high order bit to 1 to switch

AMODE

SUB31 SUB31 SUB31

31 ANY 15,15 0,14 set return code to 0 return and switch to callers

AMODE

31 Bit addressing A 370/XA or a 370/ESA processor can operate in 24 or 31 bit mode (Bimodal operation). The following kinds of programs must operate below the 16MB line Programs with AMODE 24 Programs with AMODE any Programs that use system services that require their callers to be in 24 bit mode Programs that use system services that require their caller to have RMODE 24 Programs that must be addressable by 24 bit callers Rules and conventions for 31 bit operation Addresses are treated as 31 bit values Any data passed by a program in 31 bit mode to a program in 24 bit mode must lie below the 16MB line The AMODE bit affect the way some H/W instructions work (BAL,BALR,LA) A program must return control in the same mode in which it gained control A program expects a 24 bit address from a 24 bit mode program and 31 bit addresses from a 31 bit mode program A program must validate the high order byte of any address passed by a 24 bit mode program before using it as an address in 31 bit mode. CALL, BALR Calling module AMODE 24 RMODE 24

Called module AMODE 24 RMODE 24

ASSEMBLY LANGUAGE - 25/09/2004

101 / 116

LINK, XCTL, ATTACH Calling module AMODE 24 RMODE 24 Called module AMODE 31 RMODE 24

At Execution time only the following combinations are valid AMODE 24, RMODE 24 AMODE 31,RMODE 24 AMODE 31,RMODE any

AMODE/RMODE can be controlled and set at following levels In the assembler source MAIN CSECT MAIN AMODE 31 MAIN RMODE 24 In the EXEC statement invoking the linkage editor //LKED EXEC PGM=HEWL,PARM='AMODE=31,RMODE=24' Linkage editor control statement MODE AMODE(31),RMODE(24) The Linkage editor creates indicators in the load module from inputs from Object Decks and Load modules input to it It indicates the attributes in the PDS member to reflect PARM and LKED control statements. System obtains the AMODE and RMODE information from the PDS entry. MVS support for AMODE and RMODE MVS obtains storage for the module as indicated in RMODE ATTACH,LINK,XCTL gives control as per the AMODE LOAD brings in a module into storage as per it's RMODE and sets bit 0 in R0 to indicate the AMODE CALL passes control in the AMODE of its caller Programs in 24 bit mode can switch mode to access data above 16MB line as follows Example USER1 CSECT USER1 AMODE 24 USER1 RMODE 24 L 15,. . . L 1,LAB1 BSM 0,1 LAB1 DC A(LAB2+X'80000000) LAB2 DS 0H L 2,4,(,15) LA 1,LAB3 BSM 0,1 LAB3 DS 0H . . END

Examples

ASSEMBLY LANGUAGE - 25/09/2004

102 / 116

TEST11 is coded to be AMODE31 and RMODE Any. It calls a sub program TEST11A which is a AMODE24, RMODE24 program. The examples illustrate how this may be done. TEST11 TEST11 TEST11 CSECT RMODE ANY AMODE 31 STM 14,12,12(13) BALR 12,0 USING *,12 GETMAIN RC,LV=LEN,LOC=BELOW ST 13,4(0,1) LR 13,1 USING WS,13 * BUSINESS LOGIC STARTS L 3,=F'100' ST 3,A1 L 3,=F'200' ST 3,A2 LOAD EP=TEST11A,ERRET=LOADERR * LOAD WAS OK IF YOU ARE HERE LR 15,0 LA 3,A1 ST 3,AA1 LA 1,AA1 BASSM 14,15 * BACK FROM DYNAMIC CALL WTO 'BACK FROM CALL',ROUTCDE=(11) LH 4,=H'16' STH 4,MSG L 3,RES CVD 3,DW UNPK MSG+2(16),DW OI MSG+17,X'F0' LA 3,MSG WTO TEXT=(3),ROUTCDE=(11) LR 2,13 L 13,4(0,2) FREEMAIN R,LV=LEN,A=(2) RETURN (14,12),,RC=0 LOADERR LR 2,13 L 13,4(0,2) FREEMAIN R,LV=LEN,A=(2) RETURN (14,12),,RC=16 WS DSECT SAVE DS 18F MSG DS AL2 DS CL16 AA1 DS A DW DS D A1 DS F A2 DS F RES DS F LEN EQU *-WS END

ASSEMBLY LANGUAGE - 25/09/2004

103 / 116

Change LOC= above to demonstrate the need for being able to access the arguments TEST11A CSECT STM 14,12,12(13) BALR 12,0 USING *,12 LR 3,1 GETMAIN R,LV=LEN,LOC=BELOW ST 13,4(0,1) LR 13,1 USING WS,13 LR 1,3 * BUSINESS LOGIC STARTS L 3,0(0,1) USING ARGS,3 L 4,A1 A 4,A2 ST 4,RES * BUSINESS LOGIC ENDS LR 2,13 L 13,4(0,2) FREEMAIN R,LV=LEN,A=(2) L 14,12(0,13) LM 0,12,20(13) LA 15,0 BSM 0,14 WS DSECT SAVE DS 18F LEN EQU *-WS ARGS DSECT A1 DS F A2 DS F RES DS F END

ASSEMBLY LANGUAGE - 25/09/2004

104 / 116

AMODE 31
OK

AMODE 31

OK

16 MB LINE

OK

OK

AMODE 31

AMODE 31

AMODE 31
possible problem

AMODE 31
16 MB line definitely a problem

AMODE 24

AMODE 24

possible problem

AMODE 31

ASSEMBLY LANGUAGE - 25/09/2004

A A A

CSECT 105 / 116 AMODE 31 RMODE ANY . . BSM 0,14

16MB LINE

B B B

CSECT AMODE 24 RMODE 24 LOAD EP=A ST 0,EPA L 15,EPA BASSM 14,15

The above method can be used for dynamic loading and branching to a module with a different AMODE. The following example indicates how to make a static call where the called module has a different AMODE. Example RTN1 CSECT EXTRN EXTRN . . L L BASSM . . L L BASSM . . END CSECT AMODE ENTRY . BSM DC

RTN2AD RTN3AD 15,=A(RTN2AD) 15,0(,15) 14,15 15,=A(RTN3AD) 15,0(,15) 14,15

RTN2 RTN2

24 RTN2AD 0,14 A(RTN2)

RTN2AD

ASSEMBLY LANGUAGE - 25/09/2004

106 / 116

RTN3 RTN3

RTN3AD

CSECT AMODE ENTRY . BSM DC

31 RTN3AD 0,14 A(X'80000000+RTN3)

Effect of AMODE on QSAM macros. See the two samples below to illustrate what changes are needed to migrate a AMODE 24 application that uses QSAM macros to a AMODE 31 application. The PRINT PRINT31 PRINT31 PRINT31 sample CSECT AMODE 31 RMODE ANY STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE GETMAIN RC,LV=LEN,LOC=BELOW LR 2,1 MVC 0(LEN,2),SYSPRINT OPEN ((2),OUTPUT),MODE=31 LTR 15,15 BNZ OPENERR LA 5,20 MVC OUTREC+1(132),=CL132'THIS IS A PRINT LINE.' LOOP PUT (2),OUTCARD BCT 5,LOOP CLOSE (2),MODE=31 L 13,SAVE+4 RETURN (14,12),,RC=0 OPENERR L 13,SAVE+4 RETURN (14,12),,RC=16 OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, LRECL=137,BLKSIZE=1370,RECFM=VBA LEN EQU *-SYSPRINT SAVE DS 18F END A sample that copies one QSAM PS file to another. QSAM31 CSECT QSAM31 AMODE 31 QSAM31 RMODE ANY STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE GETMAIN RC,LV=LENI,LOC=BELOW LR 2,1 MVC 0(LENI,2),INFILE GETMAIN RC,LV=LENO,LOC=BELOW

ASSEMBLY LANGUAGE - 25/09/2004

107 / 116

LOOP

ERROR1 ERROR2 EOFRTN INBUFF OUTBUFF SAVE OUTFILE LENO INFILE LENI INDCBE

LR 3,1 MVC 0(LENO,3),OUTFILE OPEN ((2),INPUT),MODE=31 LTR 15,15 BNZ ERROR1 WTO 'INFILE OPENED' OPEN ((3),OUTPUT),MODE=31 LTR 15,15 BNZ ERROR2 WTO 'OUTFIL OPENED' GET (2),INBUFF MVC OUTBUFF,INBUFF PUT (3),OUTBUFF B LOOP L 13,SAVE+4 RETURN (14,12),,RC=1 L 13,SAVE+4 RETURN (14,12),,RC=2 CLOSE ((2),,(3)),MODE=31 L 13,SAVE+4 RETURN (14,12),,RC=0 DS CL80 DS CL80 DS 18F DCB DSORG=PS,RECFM=FB,BLKSIZE=800, LRECL=80,MACRF=PM,DDNAME=OUTFILE EQU *-OUTFILE DCB DSORG=PS,RECFM=FB,BLKSIZE=800, LRECL=80,MACRF=GM,DDNAME=INFILE, DCBE=INDCBE EQU *-INFILE DCBE EODAD=EOFRTN END QSAM31

X X X

Sample that uses the RDJFCB macro RDJFCB31 CSECT RDJFCB31 AMODE 31 RDJFCB31 RMODE ANY SAVE (14,12) BALR 9,0 USING *,9 ST 13,SAVE+4 LA 13,SAVE * GETMAIN RC,LV=SYSPL,LOC=BELOW LR 3,1 MVC 0(SYSPL,3),SYSPRINT OPEN ((3),OUTPUT),MODE=31 LTR 15,15 BNZ OPENERR * GETMAIN RC,LV=FILDCBL,LOC=BELOW LR 11,1 MVC 0(FILDCBL,11),FILEDCB USING IHADCB,11 *

ASSEMBLY LANGUAGE - 25/09/2004

108 / 116

GETMAIN RC,LV=RDJL,LOC=BELOW LR 5,1 MVC 0(RDJL,5),RDJ * GETMAIN RC,LV=JFCBL,LOC=BELOW LR 10,1 MVC 0(JFCBL,10),JFCB STCM 10,B'0111',177(10) USING INFMJFCB,10 LA 4,176(10) STCM 4,B'0111',DCBEXLSA * USING BAL BAL BAL BAL BAL CLOSE B * RDJFCB DSTBLMAP,12 6,RDJFCB 6,MDFYJFCB 6,OPEN 6,PROCESS 6,CLOSE (3),MODE=31 RETURN

NODD

STCM 11,B'0111',1(5) RDJFCB MF=(E,(5)) LTR 15,15 BNZ NODD BR 6 WTO 'FILEDD NOT SPECIFIED IN JCL' ABEND 901

* MDFYJFCB LA 12,DSNTBL MVC JFCBDSNM,DSNAME BR 6 * OPEN OPEN ((11),INPUT),TYPE=J,MF=(E,(5)) LTR 15,15 BNZ OPENERR BR 6 * CLOSE CLOSE (11),MODE=31 BR 6 * OPENERR WTO 'OPENERROR' L 13,SAVE+4 RETURN (14,12),,RC=16 * PROCESS WTO 'IN PROCESS' GET (11),BUFFER MVC OUTREC(80),BUFFER PUT (3),OUTCARD B PROCESS EOF BR 6 * RETURN L 13,SAVE+4 RETURN (14,12),,RC=0 * SAVE DS 18F

ASSEMBLY LANGUAGE - 25/09/2004

109 / 116

* DSNTBL DS01 * JFCB JFCBPTR JFCBL BUFFER * RDJ RDJL * FILEDCB FILDCBL DCBED * OUTCARD OUTREC SYSPRINT SYSPL

DC DC DC DS DS DC DC EQU DS

A(L'DS01) C'userid.FILE1' CL(45-L'DS01)' ' 0F 44F X'87' AL3(JFCB) *-JFCB CL80

RDJFCB (FILEDCB,INPUT),MF=L EQU *-RDJ DCB EQU DCBE DC DC DCB DSORG=PS,MACRF=GM,DCBE=DCBED,EXLST=JFCBPTR, DDNAME=INFILE *-FILEDCB EODAD=EOF AL2(137),AL2(0) CL133' ' DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, LRECL=137,BLKSIZE=1370,RECFM=VB *-SYSPRINT DSORG=PS X

EQU DCBD DSECT IEFJFCBN

* DSTBLMAP DSECT DSNMLEN DS CL4 DSNAME DS CL44 DS CL1 END JCL, Note the INFILE DD Statement //userid1 JOB NOTIFY=&SYSUID,CLASS=A,MSGLEVEL=(1,1) // JCLLIB ORDER=(userid.PROCLIB) //STEP1 EXEC ASMACL,REGION=0M //ASM.SYSIN DD DSN=userid.ASM.SOURCE(RDJFCB2),DISP=SHR //LKED.SYSLMOD DD DSN=userid.LOADLIB(RDJFCB2),DISP=SHR //LKED.SYSLIB DD DSN=userid.OBJECT,DISP=SHR // DD DSN=CEE.SCEELKED,DISP=SHR //RUN EXEC PGM=RDJFCB2 //STEPLIB DD DSN=userid.LOADLIB,DISP=SHR // DD DSN=CEE.SCEERUN,DISP=SHR //SYSPRINT DD SYSOUT=* //INFILE DD VOL=SER=(volser),DISP=SHR

ASSEMBLY LANGUAGE - 25/09/2004

110 / 116

MIXED MODE PROGRAMMING WITH COBOL AND ASSEMBLER

back

This first example is an Assembler program calling a COBOL program. There are many ways to prepare a COBOL / Assembler program. Methods:1. Prepare the COBOL program first into an object module. Then compile and link edit the Assembler program, making the COBOL object code available to the link edit step via SYSLIB. 2. Prepare the Assembler program as an object module. Then compile and link edit the COBOL program, making the assembler object code available to the link edit step via SYSLIB. 3. Prepare both the COBOL and Assembler programs as Object code. Then have a separate Link edit only job and use Linkage editor control statements to prepare the Load module, name the module and specify an Entry point. The following illustrates method (1) and illustrates an Assembler program(TEST11) calling a COBOL sub program SUMCOB Use the following JCL to compile the COBOL program. The IGYWC procedure is supplied by IBM and will be available in the system. Compile the COBOL source //userid1 JOB CLASS=C, // MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID // JCLLIB ORDER=(userid.PROCLIB) //COMPILE EXEC IGYWC //COBOL.SYSIN DD DSN=userid.COBOL.SOURCE(SUMCOB),DISP=SHR //COBOL.SYSLIN DD DSN=userid.COBOL.OBJECT(SUMCOB),DISP=SHR // See your system for understanding the IGYWC procedure used for compiling a COBOL program. The IGYWCL procedure compiles and link edits a COBOL program. Here is the assemble and run JCL //userid1 JOB CLASS=C, // MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID,REGION=0M // JCLLIB ORDER=userid.PROCLIB //STEP1 EXEC PROC=ASMACL //C.SYSIN DD DSN=userid.ASM.SOURCE(TEST11),DISP=SHR //L.SYSLMOD DD DSN=userid.LOADLIB(TEST11),DISP=SHR //L.SYSLIB DD DSN=userid.COBOL.OBJECT,DISP=SHR // DD DSN=CEE.SCEELKED,DISP=SHR //L.SYSIN DD * ENTRY asm-csect-name /* //STEP EXEC PGM=TEST12 //STEPLIB DD DSN=userid.LOADLIB,DISP=SHR // DD DSN=CEE.SCEERUN,DISP=SHR //SYSPRINT DD SYSOUT=* // This COBOL program SUMCOB is called from an assembler module

ASSEMBLY LANGUAGE - 25/09/2004

111 / 116

IDENTIFICATION DIVISION. PROGRAM-ID. SUMCOB. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. LINKAGE SECTION. 01 LS-VARS. 03 ARG1 PIC S9(8) COMP. 03 ARG2 PIC S9(8) COMP. 03 RES PIC S9(8) COMP. PROCEDURE DIVISION USING LS-VARS. PERFORM MAIN-PARA PERFORM END-PARA. MAIN-PARA. COMPUTE RES = ARG1 + ARG2. END-PARA. STOP RUN. Here is the Assembler program that calls SUMCOB TEST12 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) LA 1,=A(ARG1) L 15,=V(SUMCOB) BALR 14,15 L 5,RES CVD 5,DW UNPK MSG+2(16),DW OI MSG+17,X'F0' LA 4,MSG WTO TEXT=(4) SR 15,15 L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) BR 14 SAVE DS 18F ARG1 DC F'100' ARG2 DC F'200' RES DS F MSG DC AL2(16) DS CL16 DW DS D END Here is the assembler version of SUMCOB , doesnt make a difference from the COBOL version. SUMCOB CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4

ASSEMBLY LANGUAGE - 25/09/2004

112 / 116

ARGS A1 A2 RES SUMASM SAVE

LR 2,13 LA 13,SAVE ST 13,8(0,2) L 2,0(0,1) USING ARGS,2 L 5,A1 A 5,A2 ST 5,RES SR 15,15 L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) BR 14 DSECT DS F DS F DS F CSECT DS 18F END

The following Illustrates Method (2) with a COBOL program calling an Assembler program First Compile the Assembler program //userid1 JOB CLASS=C, // MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID,REGION=0M // JCLLIB ORDER=userid.PROCLIB //STEP1 EXEC PROC=ASMAC //C.SYSIN DD DSN=userid.ASM.SOURCE(SUMASM),DISP=SHR //C.SYSLIN DD DSN=userid.ASM.OBJECT(SUMASM),DISP=SHR // Then you run this JCL that compiles the COBOL program, link edits it with the Assembler code and runs it. //userid1 JOB CLASS=C, // MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID // JCLLIB ORDER=(userid.PROCLIB) //COMPILE EXEC IGYWCL //COBOL.SYSIN DD DSN=userid.COBOL.SOURCE(TEST11CB),DISP=SHR //LKED.SYSLMOD DD DSN=userid.LOADLIB(TEST11CB),DISP=SHR //LKED.SYSLIB DD // DD DSN=userid.ASM.OBJECT,DISP=SHR //* //RUN EXEC PGM=TEST11CB //STEPLIB DD DSN=userid.LOADLIB,DISP=SHR // DD DSN=CEE.SCEERUN,DISP=SHR // TEST11CB COBOL PROGRAM (Main) IDENTIFICATION DIVISION. PROGRAM-ID. TEST11CB. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-VARS.

ASSEMBLY LANGUAGE - 25/09/2004

113 / 116

03 ARG1 PIC S9(8) COMP VALUE 100. 03 ARG2 PIC S9(8) COMP VALUE 200. 03 RES PIC S9(8) COMP. PROCEDURE DIVISION. PERFORM MAIN-PARA PERFORM END-PARA. MAIN-PARA. DISPLAY "EXECUTING TEST11CB" CALL "SUMASM" USING WS-VARS DISPLAY "RESULT IS:-" RES. END-PARA. STOP RUN.

Assembler Sub Program SUMASM SUMASM CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) L 2,0(0,1) USING ARGS,2 L 5,A1 A 5,A2 ST 5,RES SR 15,15 L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) BR 14 ARGS DSECT A1 DS F A2 DS F RES DS F SUM CSECT SAVE DS 18F END Method (3) Here compile the COBOL program SUMCOB into userid.COBOL.OBJECT. Compile the Assembler program TEST11 into userid.ASM.OBJECT. Then run the link edit and run Job shown below. //userid1 JOB CLASS=C, // MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID //LKED EXEC PGM=HEWL,REGION=1024K //SYSLMOD DD DSN=userid.LOADLIB,DISP=SHR //SYSLIB DD DSNAME=CEE.SCEELKED,DISP=SHR //MYLIB DD DSN=userid.ASM.OBJECT,DISP=SHR // DD DSN=userid.COBOL.OBJECT,DISP=SHR //SYSPRINT DD SYSOUT=* //SYSLIN DD *

ASSEMBLY LANGUAGE - 25/09/2004

114 / 116

INCLUDE MYLIB(TEST11) INCLUDE MYLIB(SUMCOB) ENTRY TEST11 NAME TEST11(R) /* //GO //STEPLIB //

include card include card entry card name card

EXEC PGM=TEST11 DD DSN=userid.LOADLIB,DISP=SHR DD DSN=CEE.SCEERUN,DISP=SHR

Any Storage that is either statically defined in the assembler program, getmained or is a COM area can be shared with a COBOL program. Here is how a COBOL program can access a COM area defined in an Assembler program. COBOL and COM Area IDENTIFICATION DIVISION. PROGRAM-ID. TEST12CB. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. LINKAGE SECTION. 01 LS-VAR-ONE. 03 ARG1 USAGE IS POINTER. 01 LS-VAR-TWO. 03 MSG PIC S9(4) COMP. 03 MSG-DATA PIC X(16). PROCEDURE DIVISION USING LS-VAR-ONE. PERFORM MAIN-PARA PERFORM END-PARA. MAIN-PARA. SET ADDRESS OF LS-VAR-TWO TO ARG1. MOVE 16 TO MSG MOVE "TEST12CB" TO MSG-DATA. END-PARA. STOP RUN. TEST12C CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) L 4,ACOM1 USING DCOM1,4 LA 1,=A(ACOM1) L 15,=V(TEST12CB) BALR 14,15 LA 5,MSG WTO TEXT=(5) SR 15,15 L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) BR 14 DS 18F

SAVE

ASSEMBLY LANGUAGE - 25/09/2004

115 / 116

ACOM1 DCOM1 MSG COM1

DC A(COM1) DSECT DS AL2 DS CL16 COM DS CL128 END TEST12C

COBOL sees only 18 bytes

ASSEMBLY LANGUAGE - 25/09/2004

116 / 116

Recommended for Reference and further reading 1. High level assembler for MVS & VM & VSE, Programmers Guide MVS & VM edition 2. High level assembler for MVS & VM & VSE, Language Reference MVS & VM edition 3. MVS Programming Assembler Services guide 4. MVS Programming Assembler Services reference 5. MVS assembly language by Mc.Quillen and Prince 6. Assembly language programming for the IBM370 and compatible computers by Michael D. Kudlick. 7. Advanced Assembler Language and MVS Interfaces by Carmine A. Cannatello 1 through 4 are IBM Manuals which are available for access at the IBM web site.

You might also like