assembler book

119
IBM 370 ASSEMBLY LANGUAGE 1 / 119 IBM 370 ASSEMBLY LANGUAGE BASIC COURSE

Upload: jitender-saini

Post on 18-Jan-2016

183 views

Category:

Documents


24 download

DESCRIPTION

Z/OS MVS ASSEMBLER BOOK that describe about assembly language for mainframe application programming.

TRANSCRIPT

Page 1: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 1 / 119

IBM 370 ASSEMBLY

LANGUAGE

BASIC COURSE

Page 2: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 2 / 119

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. Floating point operations 8. Data transfer and Logical operations 9. Bit manipulations 10. Branching 11. Assembler Directives 12. JCL aspects 13. Subroutines, linkage 24 bit mode 14. Macros and conditional assembly 15. MVS system Macros 16. VSAM Macros 17. Linkage Conventions, 24 & 31 bit addressing, mixed mode

addressing issues References

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 McQuillen and Prince

6. Assembly language programming for the IBM370 and compatible computers by

Michael D. Kudlick.

Page 3: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 3 / 119

INTRODUCTION back 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

More Difficult to use than a high-level language Advantages over high-level language

Very efficient and tight code can be developed Disadvantages

Applications development time is more

Applications are machine dependent

Difficult to learn and understand Advantages over machine language

Use of mnemonic operation codes helps remembering the instructions

Symbols can be used

Macros can be used to generate repeated codes

Conditional assembly enables tailoring the code generated

Page 4: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 4 / 119

BASIC CONCEPTS back

IBM-370 MACHINE ARCHITECTURE

Main storage Addressed by 24 bits or 31 bits

One single address space contains code and data

Byte is the least addressable unit

Instruction execution is faster if data is aligned on a full word boundary

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

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

Page 5: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 5 / 119

ASSEMBLY STATEMENT FORMAT

1 10 16 72

Fixed Format. Can be changed only through ICTL Assembler Directive

Blank lines are invalid

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

NAME FIELD OPERATION FIELD OPERAND FIELD REMARK

S

* SEQUENCE

Page 6: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 6 / 119

INSTRUCTIONS back

TYPES OF INSTRUCTIONS

machine instructions

Assembler instructions (directives)

Macro instructions

Example : PRINT NOGEN TEST1 CSECT Assembler Directive STM 14,12,12(13) Machine instruction

BALR 12,0 Machine instruction USING *,12 Assembler Directive ST 13,SAVE+4 Machine instruction LA 13,SAVE Machine instruction MVC DATA1,DATA2 Machine Instruction

PUTMSG WTO 'message' Macro instruction L 13,SAVE+4 Machine instruction LM 14,12,12(13) Machine instruction SR 15,15 Machine instruction BR 14 Machine Instruction DATA1 DS CL100 Data Definition DATA2 DS CL100 Data Definition SAVE DS 18F Data Definition END 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 AR 3,2

immediate operand

Example MVI DATA,X'F1'

Storage operand

Example L 3,FIELD1

Implied operand,

Example 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

IMMEDIATE OPERAND

Contained with in the instruction itself

Page 7: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 7 / 119

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

Page 8: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 8 / 119

INSTRUCTIONS CLASSIFICATION

RR FORMAT

0 8 12 15

RRE FORMAT

0 16 24 28 31

RX FORMAT

0 8 12 16 20 31

RS FORMAT

0 8 12 16 20 31

SI FORMAT

0 8 16 20 31

S FORMAT

0 16 20 31

SS FORMATS

0 8 12 16 20 32 36 47

0 8 16 20 32 36 47

EXAMPLES :

RR type instruction AR 2,3 reg 2 <== reg 2 + reg 3

RS type instruction BXH 1,3,D2(B2) reg 1 <== reg 1 + reg 3 If reg1>reg3 then branch

RX type instruction L 1,D2(X2,B2) reg 1 < == memory referenced by (D2 +X2 +B2)

FIRST HALF WORD SECOND HALF WORD THIRD HALF WORD

OP CODE R1 R2

OP CODE R1 R2

OP CODE R1 X2 B2 D2

OP CODE R1 R3 B2 D2

OP CODE I 2 B1 DI

OP CODE B2 D2

OP CODE L1 L2/I3 B1 D1 B2 D2

OP CODE L B1 D1 B2 D2

Page 9: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 9 / 119

S type instruction LPSW D2(B2)

SI type instruction NI D1(B1),I2

Storage type instruction MVC D1(L,B1),D2(B2) PACK D1(L1,B1),D2(L2,B2)

Page 10: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 10 / 119

SYMBOLS, LITERALS, CONSTANTS, 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 MVC S1,S2

BR QUIT QUIT BR 14 S1 DS CL100 S2 DC CL100'THE QUICK BROWN FOX' COUNT EQU 10

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 CL80 L'TO = 80 FROM DS CL240 L'FROM = 240 ADCON DC A(OTHER) L'ADCON = 4 CHAR DC C'YUKON' L'CHAR = 5 DUPL DC 3F'200' L'DUPL = 4

Page 11: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 11 / 119

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

Character self-defining term

A character string within apostrophes and preceded by a C

Maximum number of characters 256

EXAMPLES: 15 UPTO 2,147,483,647 241 B'1101' UPTO 32 BITS X'F' UPTO 8 HEX DIGITS X'F1F2' C'ABCD' UPTO 4 CHARACTERS C'&&' TWO AMPERSANDS TO REPRESENT ONE C'''''' TWO APOSTROPHES TO REPRESENT ONE Literals

L 1,=F'200' L 2,=A(SUBRTN) MVC MESSAGE(16),=C'THIS IS AN ERROR' L 3,=F'33' BOTH ARE SAME L 3,FIELD BOTH ARE SAME FIELD DC F'33'

MVC FLAG,=X'00' SAME EFFECT MVI FLAG,X'00' SAME EFFECT MVI FLAG,ZERO SAME EFFECT . . ZERO EQU X'00' FLAG DS C LA 4,LOCORE SAME EFFECT LA 4,1000 SAME EFFECT . LOCORE EQU 1000 Absolute expressions An expression is absolute if it's value is unchanged by program relocation FIRST CSECT A DC F'2' B DC F'3' C DC F'4' ABSA EQU 100 ABSB EQU X'FF'

Page 12: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 12 / 119

ABSC EQU B-A ABSD EQU *-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 constant is assembled to the next available location

Assembler checks boundary alignment and adjusts location counter if reqd.

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 *+80 . . . B LOOP

Page 13: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 13 / 119

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.

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

Example : length A DS F 4 DS 20FL4 4 DS XL3 3

AR 1,2 2 AA EQU A+4 4 S1 EQU 102 1 S2 EQU X'FF +A' 1 S3 EQU C'YUK' 1 BUF EQU A,256 256 BUF2 EQU *+10 1 BUF3 EQU *,80 80

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

SYNTAX

DUPLICATING FACTOR TYPE LENGTH MODIFIER CONSTANT

Page 14: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 14 / 119

{NAME} DC {DUP}TYPE{MOD}{V1,V2,...VN}

Run time constant

TYPE BYTES ALLOC DC F'100,-10,200' 12 DC F'123' 4 DC F'-123' 4 DC 3F'23' 12 DC H'20' 2 DC H'123,23,-34' 6 DC B'11000001' 1 DC X'FFFFFFFF' 4 DC X'FF01FF01' 4 DC C'ABCDEF' 6 DC C'abcdefg''A&&SS@#..' 16 , note double & and ' DC P'-1234' 3 DC P'1234' 3 DC P'-34' 2 DC Z'1234' 4 DC E'-3.25E10' 4 DC E'+.234E-10' 4 DC E'-2.3E15' 4 DC A(LOOP1) 4 DC V(LOOP1) 4 DC S(FIELD2) 2 DC C'USER01' 6

DC F'100,200' Two full words with value 100,200 DC CL3'JAN,FEB' Months contain 3 bytes value "JAN'

DC 3H'2,4,8,16' 12 half words with the given value DC B'10001000' 1

DC C'SAMPLE STRING' 13 DC P'123' 2

DC ZL10'123' 10 DC PL4'123' 4 DC E'1.25' 4 DC D'2.57E65' 8 DC AL3(THERE) 3 DC V(EXTSYM) 4

DEFINE STORAGE (DS)

To reserve storage

Storage is not initialised

Location counter advanced by bytes allocated

DS

SYNTAX

{NAME} DS {DUP}TYPE{MOD}

EXAMPLES DS F Bytes allocated 4

DS 10F 40 DS H 2

DS 2CL3 6 A DS 80C 80 L'A=1 DS CL80 80 L'A=80

DUPLICATING FACTOR TYPE LENGTH MODIFIER

Page 15: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 15 / 119

DS 4D 32 DS 0F 0 used to force a word Boundary DS 0D 0 used to force a double word boundary DS 0CL8 0 length attribute is 8 DS 100H 200

A self defining term is an absolute constant that can be written as a

A binary integer B'1001'

A decimal integer 3

A hexadecimal integer X'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 FCON DC F'1' L 5,FCON L 5,=F'1' LOAD L 2,=F'-4'

MOVE MVC MSG,=C***Error ***' 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). 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 EQU 1 HERE EQU * OFF EQU X'00' ON EQU X'FF' Y DC F'4' Z EQU 4 W EQU Y W is equivalent to Y

CLI STATUS,ON BE POWERON CLI STATUS,OFF BE 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'

Page 16: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 16 / 119

000103 skipped 000104 DC F'4' 000108 DC C'A' 000109 skipped 000110 skipped 000111 skipped 000112 DC F'560'

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 LOCTN COUNTER 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. LOCTN COUNTER PROGRAM 000010 DATA DC C'ABC' 000013 DS F ASSM. AT NEXT LOC

Example FIRST CSECT

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

LA 13,SAVE

WTO 'ASM1 REPORTING'

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'

DC CL20'ABCDEFGH'

DC 10C'AB'

DC P'123'

DC P'-123'

Page 17: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 17 / 119

DC PL5'-123'

DC 3PL5'-123'

DATA1 DS CL20

END

Page 18: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 18 / 119

INTEGER OPERATIONS back

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

Page 19: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 19 / 119

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 Two's Complement Decimal Binary Decimal Binary 0 0000 0 0000 +1 0001 -1 1111 +2 0010 -2 1110 +3 0011 -3 1101 +4 0100 -4 1100 +5 0101 -5 1011 +6 0110 -6 1010 +7 0111 -7 1001 Addition and Subtraction +6 0110 -6 1010 +5 0101 -5 1011 +(+1) 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 R1,D2(X2,B2) L 3,A GPR3 Memory Field A Before 0246 0357 000A 00B0 After 000A 00B0 000A 00B0 ST Copy a full word from GPR to memory RX R1,D2(X2,B2) ST 3,A GPR3 Memory field A Before 0123 0456 0ABC 0DEF 0123 0456 0123 0456 LH Copies a half word from memory to GPR RX R1,D2(X2,B2) LH 3,A GPR3 Memory Field A Before 0159 0260 4321 After 0000 4321 4321 STH Copy a half word from GPR to memory RX R1,D2(X2,B2) STH 3,A GPR3 Memory field A Before 0123 0456 0DEF 0123 0456 0456

Page 20: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 20 / 119

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 STM Copies 1 to 16 Full words to memory RS R1,R3,D2(B2) From consecutive GPR,s STM 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:00001234 A+0:00001234 3:00003456 A+4:00003456 4:00005678 A+8:00005678 LR Copies one GPR to another RR R1,R2 LR 3,4 GPR3 GPR4 Before ABCD EF00 1234 5678 After 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 S 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 AR Adds a GPR to another GPR RR R1,R2 Example 4096+(-1)=4095 AR 6,5 GPR6 GPR5 Before 0000 1000 FFFF FFFF After 0000 0FFF FFFF FFFF SR Subtracts a GPR from another GPR RR R1,R2 Example 4096-(-1)=4097 SR 6,5 GPR6 GPR5 Before 0000 1000 FFFF FFFF After 0000 1001 FFFF FFFF

AH Adds a half word memory field to a GPR RX R1,D2(X2,B2) Example 80+8=88 AH 10,=H'8' GPR10 Memory Before 0000 0050 0008

Page 21: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 21 / 119

After 0000 0058 0008 Example 80+(-8)=72 AH 10,=H'8' GPR10 Memory Before 0000 0050 FFF8 After 0000 0048 FFF8 SH 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 AL Add Logical RX R1,D2(X2,B2) ALR Adds a GPR logically to another GPR RR R1,R2

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)

MULTIPLICATION |--------------consecutive GPR'S------------------------| |---even numbered GPR--|--odd numbered GPR---|

Before multiplication

After multiplication

M Multiply RX R1,D2(X2,B2)

Example 2 X 3 = 6 L 7,=F'2' M 6,=F'3' GPR6 GPR7 Memory Before any number 0000 0002 0003 After 0000 0000 0000 0006 0003 MR Multiply one GPR with another RX R1,D2(X2,B2)

Example 65536 X 65536 L 4,=F'65536' MR 6,4 GPR6 GPR7 GPR4 Before 0000 0000 0001 0000 0001 0000 After 0000 0001 0000 0000 0001 0000 MH 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

Any number V1

64 bit product V1 X V2

Page 22: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 22 / 119

After 0000 000A 0005

DIVISION |--------------consecutive GPR'S-----------------------------| |---even numbered GPR----|----odd numbered GPR----|

Before Division

After Division

D DIVIDE even odd GPR pair by memory RX R1,D2(X2,B2)Field

Example 7 / 2 = quotient =3, remainder=1 L 9,=F'7' L 8,=F'0' D 8,=F'2' GPR8 GPR9 Memory Before 0000 0000 0000 0007 0002 After 0000 0001 0000 0003 0002 Rem +1 Quot +3 Divisor +2 DR Divide one even/odd pair GPR with another GPR R1,R2

Example 150 / -40 L 9,=F'150' L 8,=F'0' L 10,=F'-40' DR 8,10 GPR8 GPR9 GPR10 Before 0000 0000 0000 0096 FFFF FFD4 After 0000 001E FFFF FFFD FFFF FFD4 rem +30 Quot -3 Divisor -40 Note: Since the dividend was a positive number extending the 32 bit positive quantity to 64 bit was achieved by simply setting the high order bits (next reg) to F'0'. However for a negative dividend sign extension is needed and this can be done by multiplying the low order reg by +1. 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 RX R1,D2(X2,B2) CR Compare a GPR with another RR R1,R2 CH Compare GPR with a memory half word RX R1,D2(X2,B2)

Condition code is set ( equal, V1<V2, V2>V2) LCR Load complement register RR R1,R2

Example LCR 3,3 GPR3 Before FFFFFFFA After 00000006 LCR 3,4 GPR3 GPR4 Before 87654321 80000000 After 80000000 80000000

32 BIT REMAINDER 32 BIT QUOTIENT

64 BIT DIVIDEND V1

Page 23: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 23 / 119

**ovfl set LPR Load positive register RR R1,R2

Example LPR 5,4 GPR5 GPR4 Before 000000AB FFFFFFFA After 00000006 FFFFFFFA LPR 4,5 GPR4 GPR5 Before FFFFFFFA 000000AB After 0000000AB 000000AB LPR 8,7 GPR8 GPR7 Before 12345678 80000000 After 80000000 80000000 ***ovflw LNR Load negative register RR R1,R2

Example LNR 4,5 GPR4 GPR5 Before FFFFFFFA 000000AB After FFFFFF55 000000AB LPR 4,5 GPR4 GPR5 Before 00000011 FFFFFF55 After 000000AB FFFFFF55 Condition code is set( zero, positive , negative, overflow)

Page 24: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 24 / 119

DECIMAL OPERATIONS back ADD AP SUBTRACT SP MULTIPLY MP DIVIDE DP DECIMAL COMPARE CP MOVE DECIMAL DATA WITH 4 BIT OFFSET MVO SHIFT DECIMAL DATA SRP SET TO ZERO AND ADD ZAP CONVERT ZONED TO PACKED PACK CONVERT PACKED TO ZONED UNPK Constants used Type Decimal P Zoned Z BCD Representation (Packed Decimal) 0011 0010 0101 1100 +325 X’325C’ 0111 1000 1001 1101 -789 X’789D’ AREA1 DS PL5 AREA2 DC 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 SS2

Example ZAP A(3),B(4) A B Before Dont Care 0023456C After 23456C 0023456C AP Add packed SS2

Example AP A(2),B(3) A B Before 099C 00001C After 100C 00001C

Before 999C 00001C After 000C 00001C (ovfl cond)

SP Subtract packed SS2 SP A(2),B(3) A B Before 099D 00001C After 100D 00001C

Page 25: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 25 / 119

Before 999C 00001C After 000C 00001C (ovfl cond)

Before 123C 00010C After 113C 00010C MP 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

Example MP A(4),B(2) A B Before 0000999C 999D After 0998001D 999D MP A(3),B(2) Before 00999C 999D After 98001D 999D **ovflw** MP A(2),B(2) Before 012C 012C After 012C 012C **error** 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

Example A B DP A(4),B(2) Before 0000999C 998D After 001D001C 998D | DP A(4),B(2) Before 0000999C 3C After 00333C0C 3C | DP A(2),B(1) Before 999C 3C After 999C 3C **Divide exception** ***L1-L2=1 (insufficient length for quotient) DP A(2),B(3) Before 999C 00003C After 999C 00003C **specification exception** ***L1-L2=-1(impossible length for quotient)

QUOTIENT REMAINDER

L1-L2 BYTES L2 BYTES

DIVIDEND FIELD

Page 26: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 26 / 119

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 SS2 D1(L1,B1),D2(L2,B2) BE V1=V2 BH V1>V2 BL V1<V2 SRP Shift and Round Packed D1(L1,B1),D2(B2),I3 SS1 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,=X’FFFFFFFD’ 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 5,A REG5 A Before 80 00 00 00 dont care

after 80 00 00 00 00 00 02 14 74 83 64 8D CVB 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 A Before dont care 00 00 00 00 00 00 01 6D after FF FF FF F0 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

Page 27: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 27 / 119

Before any F1 F2 F3 C4 after 00 01 23 4C F1 F2 F3 C4 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 1

st 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

Example of Packed Decimal Divide FIRST 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

LM 14,12,12(13)

LA 15,0

BR 14

SAVE DS 18F

MSG DC AL2(LEN)

DC C'QUOT='

QUOT DS CL4

DC C','

DC C'REM='

REM DS CL4

LEN EQU *-MSG-2

A DC PL4'+0000999'

Page 28: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 28 / 119

B DC PL2'-998'

END

Example of displaying a Integer FIRST 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

Page 29: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 29 / 119

FLOATING POINT OPERATIONS back ADD ADR,AD,AER,AE,AWR,AW,AUR,AU,AXR SUBTRACT SDR,SD,SER,SE,SWR,SW,SUR,SU,SXR MULTIPLY MDR,MD,MER,ME,MXR,MXDR,MXD DIVIDE DDR,DD,DER,DE ARITHMETIC COMPARE CDR,CD,CER,CE LOAD INTO FPR LDR,LD,LER,LTDR,LTER,LCDR,LCER,LPDR,LPER LNDR,LDER,LRDR,LRER STORE INTO AREAS STD,STE Constants used Type Floating point E,D,L

Floating-point Number representation

Consists of a signed hexadecimal fraction and an unsigned seven-bit binary integer ,called as characteristic

Characteristic represents signed exponent in excess-64 notation

A normalised floating -point number has a nonzero leftmost hexadecimal fraction digit.

If one or more leftmost fraction digits are zeros, the number is said to be un-normalised.

A normalised number represents a quantity with the greatest precision.

Un-normalised numbers are normalised by shifting the fraction left, one digit at a time, until the leftmost hexadecimal digit is nonzero and reducing the characteristic by the number of hexadecimal digits shifted.

Addition and subtraction with extended operands, as well as the multiply, divide, and halve operations, are performed only with normalisation. Addition and subtraction with short or long operands may be specified as either normalised or not normalised.

Floating-Point Data format

Short floating-point number

Represented by 32 bits

Bit 0 is sign bit

Bits 1-7 are characteristic

Bits 8-31 are digit fraction

Can reside in the storage or in the floating point registers

Long floating-point number

Represented by 64 bits

Bit 0 is sign bit

Bits 1-7 are characteristic

Bits 8-63 are digit fraction

Can reside in the storage or in the floating point registers

extended floating point number

Represented by 128 bits

Bit 0 of high-order 64 bits is the sign bit

Bits 1-7 of high-order 64 bits contains are characteristic

Bits 8-63 of high-order 64 bits and bits 72-127 of low order 64 bits contains the 28 digit fraction

Can only reside in the floating point registers

Floating Point instructions

Floating point registers 0,2,4,6 are used in the instructions

Only left half of FPR is used if short floating point number is specified

FPR 0 & 2,4 & 6 can be used to contain extended floating point

Page 30: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 30 / 119

Instructions are available for data loading, arithmetic and comparison number

Page 31: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 31 / 119

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

BYTE AND STRING MANIPULATIONS IC Insert character RX Copies 1 byte from memory to 8 right most bits of a GPR

R1,D2(X2,B2) STC store Character RX Copies 1 byte (right most 8 bits) from GPR to Memory

R1,D2(X2,B2) ICM Insert Characters under mask RS Copies 1 to 4 bytes depending on the mask from memory to GPR

R1,Mask,D2(B2) STCM Store characters under mask RS Copies 1 to 4 bytes depending on the mask from GPR to memory

R1,R3,D2(B2) MVI Move Immediate SI Copies 1 byte from immediate

field of the instruction to memory D1(B1),I2

MVC Move Characters SS Copies 1 to 256 chars from one memory field to another

D1(L,B1),D2(B2)

MVCL Move Characters Long RR Copies 1 to 2**24 chars from one memory field to another

R1,R2 MVCIN Move Inverse SS Copies 1 to 256 bytes from one memory field to

another reversing the order of bytes Comparison

COMPARISON (LOGICAL)

Unsigned 8 bit numbers (logical quantity)

Smallest byte is X’00’, Largest is X’FF’

Comparison starts from left most position (high order) CL Compare logical RX Compares a 4 byte string in memory to contents of a GPR

R1,D2(X2,B2)

Page 32: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 32 / 119

CLR Compare Logical Register RR Compares 4 bytes from two GPR’S R1,R2 CLM Compare Logical under mask RS Compares 1 to 4 bytes (determined by mask) from a GPR to a memory field

R1,M,D2(B2) CLI Compare Logical Immediate SI Compares an 1 byte immediate operand to a byte in memory

D1(B1),I2 CLC Compare Logical Characters SS Compares 1 to 256 bytes from one memory field to another

D1(L,B1),D2(B2) CLCL Compare Logical Characters long RR Compares 1 to 2**24 characters from one memory field to another.

BRANCHING

CC 0 CC 1 CC 2 CC3 CL,CLC,CLCL, CLI,CLM,CLR OPR1=OPR2 OPR1<OPR2 OPR1>OPR2 NA.

Opcode Meaning BE OPR1=OPR2 BNE OPR1!=OPR2 BL OPR1<OPR2 BNL OPR1=>OPR2 BH OPR1>OPR2 BNH 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 OR’ing bits 8-15(length field) with bits 24-31 of R1 If the target instruction is a branch then the branch is made. If it is a BALR / BAL then the return from the branch is made to the instruction following the EX instruction. LH 4,=H’20’ SH 4,=H’1’ EX 4,MOVEV | | MOVEV MVC TO(0),FROM | | FROM DS 10F TO DS 10F CLCL and MVCL instructions CLCL R1,R2 MVCL R1,R2

Page 33: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 33 / 119

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 LA 2,S L 3,=L’S LA 4,T L 5,=L’T ICM 5,X’8’,=X’00’ CLCL 2,4 | | | S DS CL1000 T DS CL2000 TR and TRT instructions TR Translate SS instructions can be used to replace certain bytes of the string with other bytes D1(L,B1),D2(B2) TRT Translate & test SS instruction can be used to find one of a set of characters in a string D1(L,B1),D2(B2)

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 CL256 ORG FN1+C’+’ DC X’FF’ ORG ARG1 DS CL256 | TRT ARG1(256),FN1 BC 8,NONE BC 4,MORE BC 2,ONE

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

Page 34: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 34 / 119

BIT MANIPULATIONS back SRA Shift Right Single Arithmetic RS SLA Shift Left Single Arithmetic RS SRDA Shift Right Double Arithmetic RS (first operand is even odd GPR pair) SLDA Shift Left Double Arithmetic 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 Shift Right Single Logical RS SLL Shift Left Single Logical RS SRDL Shift Right Double Logical RS (first operand is even odd GPR pair) SLDL Shift Left Double Logical 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 Or RX N And RX X Exclusive Or RX

OR Or GPR’S RR NR And GPR’S RR XR XOR GPR’S RR OI Or Immediate SI NI And Immediate SI XI Exclusive Or Immediate SI OC Or Memory fields SS NC And Memory Fields SS XC Exclusive Or Mem Flds SS

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

Page 35: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 35 / 119

BRANCHING INSTRUCTIONS back BRANCH ON CONDITION CODE BCR,BC BRANCH AND LINK BALR,BAL BRANCH ON COUNT BCTR,BCT BRANCH ON INDEX COMPARE BXH,BXLE TEMPORARY BRANCH EX 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 L 7,LIMIT L 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 INCR EQU 4

ASSEMBLER DIRECTIVES back

Page 36: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 36 / 119

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

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

Page 37: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 37 / 119

ORG BUFFER A DS CL80 B DS CL80 C DS CL80 D DS CL80

ORG

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 See example below. FIRST CSECT

ENTRY DATA

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

LA 13,SAVE

WTO 'IN ASM4 BEFORE CALL TO SUB4'

LA 3,MSG

WTO TEXT=(3)

L 15,ASUB1

BALR 14,15

WTO 'IN ASM4 AFTER CALL TO SUB4'

LA 3,MSG

WTO TEXT=(3)

L 13,SAVE+4

LM 14,12,12(13)

LA 15,4

BR 14

SAVE DS 18F

DC A(SAVE)

ASUB1 DC V(SUB4)

MSG DC AL2(L'DATA)

DATA DC CL20'DATA BEFORE CALL'

END

SUB4 CSECT

Page 38: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 38 / 119

EXTRN DATA

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

LA 13,SAVE

WTO 'IN SUB 4 BEFORE CHANGING DATA'

L 3,ADATA

MVC 0(20,3),=CL20'DATA AFTER CHANGE'

WTO 'IN SUB 4 AFTER CHANGING DATA'

L 13,SAVE+4

LM 14,12,12(13)

SR 15,15

BR 14

SAVE DS 18F

ADATA DC A(DATA)

END

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.

Example FIRST CSECT

WXTRN SAVE1

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

LA 13,SAVE

WTO TEXT=DATA

L 13,SAVE+4

LM 14,12,12(13)

SR 15,15

BR 14

SAVE DS 18F

DATA DC AL2(L'MSG)

MSG DC CL30'ASM1 REPORTING'

END

COM

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.

SUB CSECT

SUB AMODE 31

SUB RMODE ANY

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

Page 39: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 39 / 119

LA 13,SAVE

L 4,ACOM

LA 5,15

STH 5,0(0,4)

MVC 2(15,4),=CL15'THIS IS SUB'

L 13,SAVE+4

LM 14,12,12(13)

LA 15,0

BR 14

SAVE DS 18F

ACOM DC A(COMMON)

COMMON COM

MSG DS AL2

DS CL100

END

FIRST CSECT

FIRST AMODE 31

FIRST 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

Page 40: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 40 / 119

JCL ASPECTS back

program consists of Machine instructions Assembler instructions Macro Instructions. Development cycle Coding Pre Assembly Assembly Linkage Edit Program fetch JCL:- IBM supplied catalogued procedures can be used. ASMACL is given below which assembles and links a assembler program //ASMACL PROC //* //*** ASMACL //* //* THIS PROCEDURE RUNS THE HIGH LEVEL ASSEMBLER AND LINKS //* THE NEWLY ASSEMBLED PROGRAM //* //C EXEC PROG=ASMA90,PARM=(OBJECT,NODECK) //SYSLIB DD DSN=SYS1.MACLIB,DISP=SHR //SYSUTI DD DSN=&&SYSUT1,SPACE=(4096,(120,120),,,ROUND),UNIT=VIO, // DCB=BUFNO=1 //SYSPRINT DD SYSOUT=* //SYSPUNCH DD SYSOUT=B

SOURCE

ASSEMBLER

MACLIBS COPY BOOKS

OBJECT DECK OBJECT LIBRARIES

LINKER

LOAD MODULE

LOAD IN MAIN STORAGE FOR EXECUTION

Page 41: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 41 / 119

//SYSLIN DD DSN=&&OBJ,SPACE=(3040,(40,40),,,ROUND),UNIT=VIO, // DISP=(MOD,PASS), // DCB=(BLKSIZE=3040,LRECL=80,RECFM=FBS,BUFNO=1) //L EXEC PGM=HEWL,PARM='MAP,LET,NCAL',COND=(8,LT,C) //SYSLIN DD DSN=&&OBJ,DISP=(OLD,DELETE) // DD DDNAME=SYSIN //SYSLMOD DD DISP=(,PASS),UNIT=SYSDA,SPACE=(CYL,(1,1,1)), // DSN=&&GOSET(GO) //SYSUT1 DD DSN=&SYSUT1,SPACE=(1024,(120,120),,,ROUND), // DCB=BUFNO=1,UNIT=VIO //SYSPRINT DD SYSOUT=*

Important linkage editor parameters

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

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

ALIGN instructs assembler to check for alignment where it is required default ALIGN

DECK Assembler generates object deck on SYSPUNCH default NODECK

ESD 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 55 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)

Page 42: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 42 / 119

Special Considerations when the member name and the CSECT name do not match.

Source File-1

FIRST 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'

L 15,ASUB1

BALR 14,15

WTO 'IN ASM3 AFTER CALL TO SUB1'

L 13,SAVE+4

LM 14,12,12(13)

SR 15,15

BR 14

SAVE DS 18F

ASUB1 DC V(SUB1) Does not pose problems

*ASUB2 DC V(SUB2) Does pose a problem

END

Source File-2 SUB1 CSECT

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

LA 13,SAVE

WTO 'IN SUB 1'

DC F'0'

L 13,SAVE+4

LM 14,12,12(13)

SR 15,15

BR 14

SAVE DS 18F

SUB2 CSECT

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE1+4

LA 13,SAVE1

WTO 'IN SUB 2'

L 13,SAVE1+4

LM 14,12,12(13)

SR 15,15

BR 14

SAVE1 DS 18F note that labels cannot be the same

END

The solution is to explicitly make the Linkage Editor include the module by the linkage editor control statement input as below:- //LKED.SYSIN DD *

Page 43: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 43 / 119

INCLUDE SYSLIB(SUB1) /*

Page 44: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 44 / 119

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 SETUP . BAL 14,SUB1 . L 15,SUB2 BALR 14,15 * EOJ * SUB1 DS OH BR 14 SUB2 DC V(SUBROUT2) END

Saving and restoring environment Programs uses registers as base, index, and accumulators. If a program calls a subprogram, and 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

Page 45: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 45 / 119

can be used by any program with out the need to identify which registers are modified by the subroutine.

IBM 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 save-area of program which called this sub-program Savearea+8 save-area of called sub-program called by this program Savearea+12 Register 14 savearea+16 Register 15 savearea+20 Register 0 . . . . . . Savearea+64 Register 11 Savearea+68 Register 12

Example MAIN START 0 STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(2) . . . LA 15,0 L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) * BR 14 SAVE DS 18F END

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 then an array is created containing he address of the parameters in the order they are expected in the called program and the register 1 is loaded

Page 46: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 46 / 119

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

Example LA 2,PI 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 the subprogram, R 1 contains the base address to the array of pointers pointing to the parameters

Access the parameter pointer address from the array and using this access the parameter

If lot of parameters need to be accessed, them a DSECT can be used to access the parameters in which case the parameters have to be stored using the same DSECT in the calling program

Example 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 can be used to indicate error condition

A return code 0 means successful completion (return codes passed in GPR15)

Return codes are multiple of 4, so that it could be used to index into address table

Example MAIN CSECT . entry linkages . . LA 1,=A(I,J) L 15,=V(MIN) BALR 14,15 ST 0,K .

Page 47: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 47 / 119

. . BR 14 I DC F'100' J DC F'120' K DS F SAVE1 DS 18F * MIN CSECT . entry linkages . LM 4,5,0(1) L 4,0(4)

L 5,0(5) CR 4,5 BGE BIG LR 0,5 B RESTORE

BIG LR 0,4 RESTORE EQU *

.

. exit linkages .

BR 14 SAVE2 DS 18F

END

Example of capturing PARM data from JCL PICKING UP PARMS

FIRST 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

Passing Structures (like a COBOL 01 level item) SUB CSECT

STM 14,12,12(13)

Page 48: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 48 / 119

USING SUB,15

ST 13,SAVE+4

LA 13,SAVE

LR 12,15

DROP 15

USING SUB,12

LR 2,1

WTO 'IN SUB'

LR 1,2

L 2,0(1)

USING PARMS,2

L 5,A

A 5,B

ST 5,RES

L 13,SAVE+4

LM 14,12,12(13)

LA 15,0

BR 14

SAVE DS 18F

PARMS DSECT

A DS F

B DS F

RES DS F

END

FIRST 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(SUB)

DW DS D

DS 0F

PARMS DS 0CL12

A DC F'100'

B DC F'200'

Page 49: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 49 / 119

RES DS F

END

Page 50: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 50 / 119

MACRO AND CONDITIONAL ASSEMBLY Back

Macro

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

Macro 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} Operation {Operands} Name field : A variable symbol. The name entry in the calling macro instruction is assigned to this symbol. Operation field: The name of the macro. The macro is invoked with this name. Operands : Specify positional or keyword parameters. Maximum 240 parameters can be passed Macro 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

Page 51: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 51 / 119

Can be symbolic parameters, system variables or set symbols

System variables are read only and their value is maintained by the Assembler

Example USER: &L &NAME &VARI &PARAM(1) SYSTEM: &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 Value Result &FLD.A &FLD AREA AREAA &FLDA &FLDA SUM SUM &B 10 &D.(&B) &D 100 100(10) &I 99 &F 98 D'&I..&F' D'99.98' D'&I.&F' D'9988' &A+3 &A A A+3

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 . . .

Page 52: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 52 / 119

MAC1 ONE,K1=12 . MAC1 TWO . . END

Example MACRO DIVIDE &R1,&R2,&TYPE M &R1,=F`1' D&TYPE &R1,&R2 MEND

Invocation MAIN CSECT

.

. . DIVIDE 8,NUM + M 8,=F`1' + D 8,NUM

.

. DIVIDE 4,6,R

+ M 4,=F'1' . .

+ DR 4,6 END

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

Page 53: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 53 / 119

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

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(O) = 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=(FO,F,O) .

&KEY(1) DC &KEY(2)'&KEY(3)' &P1(1) DC &P1(2) '&P1(3)'

DC A&P2 . MEND

invocation: MAIN START O

. VAR (H20,H,200), (A,B,C),KEY=(F1,F,1)

+F1 DC F' 1' +H20 DC H'200' + DC A(A,B,C)

END

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

Page 54: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 54 / 119

LOOP&SYSNDX EQU * BNE LOOP&SYSNDX MEND

Invocation MAIN START 0

LOOP +LOOP0001 EQU * + BNE LOOP0001

LOOP +LOOP0002 EQU * + BNE 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

Page 55: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 55 / 119

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> 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>

Page 56: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 56 / 119

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

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

Page 57: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 57 / 119

Invocation MAIN START 0 HERE MOVE FLDA,FLDB +HERE ST 2,SAVEAREA + L 2,FLDB1 + ST 2,FLDAO + L 2,SAVEAREA

Conditional Branch

<SEQ SYMBOL> AIF (<LOGICAL EXPR>).<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 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

Page 58: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 58 / 119

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 TABLE

LCLA &I &SYSLIST(0) DS 0D .WHILE AIF (&I GT N'SYSLIST).DONE

DC D'&SYSLIST(&I) &I SETA &I+1

AGO .WHILE .DONE MEND

Macro 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

Page 59: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 59 / 119

Example of TPUT MACRO MACRO

&LABEL TPUT &ADDR, X &LEN, X &FULLSCR LCLC &TEMPREG

* AIF ('&LABEL' EQ '').NOLAB

&LABEL DS 0H .NOLAB ANOP .*

AIF ('&ADDR' EQ '').NOADDR AIF ('&ADDR'(1,1) EQ '(').ADDRREG LA 0,&ADDR GET ADDRESS IN R0 AGO .NOADDR

.ADDRREG ANOP &TEMPREG SETC '&ADDR'(2,K'&ADDR-2)

LR 0,&TEMPREG GET ADDRESS IN R0 .NOADDR ANOP .*

AIF ('&LEN'(1,1) EQ '(').LENREG LA 1,&LEN GET LENGTH IN R1 AGO .CONT

.LENREG ANOP &TEMPREG SETC '&LEN'(2,K'&LEN-2)

LR 1,&TEMPREG GET LENGTH IN R1 .* .CONT ANOP

AIF ('&FULLSCR' EQ '').NFS AIF ('&SYSCHARSET' EQ 'E').FLS MNOTE 4,'TPUT OPTION FULLSCR MUST USE EBCDIC CHARACTER SET'

.FLS ANOP SVC 96 MEXIT

.*

.NFS ANOP SVC 94 MEND

Page 60: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 60 / 119

Example of SAVE macro MACRO

&LABEL SAVE &REGS, X &T, X &ID

.* AIF ('&LABEL' EQ '').NOLAB

&LABEL DS 0H NOLAB 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

Page 61: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 61 / 119

Example of RETURN macro MACRO

&LABEL RETURN &REGS, X &T, X &RC=

.* LCLA &WORK,&VALU

.* AIF ('&LABEL' EQ '').NOLAB

&LABEL DS 0H .NOLAB ANOP .*

AIF ('&REGS' EQ '').NOREGS AIF (&REGS(1) GE &REGS(2)).RET1 AIF (&REGS(2) EQ 15).RET1 AIF ('&RC' EQ '').RCT3 AIF ('&RC'(1,1) EQ '(').RCT2 LA 15,&RC

.RCT3 ANOP LM &REGS(1),&REGS(2),12(13) BR 14 MEXIT

.RCT2 ANOP &VALU SETA &RC(1)

LR 15,&VALU LM &REGS(1),&REGS(2),12(13) BR 14 MEXIT

.*

.RET1 ANOP AIF ('&RC' EQ '').RCT4

&WORK SETA (15-&REGS(1))*4 AIF ('&RC'(1,1) EQ '(').RCT1 LA 15,&RC ST 15,12+&WORK.(13)

.RCT4 ANOP LM &REGS(1),&REGS(2),12(13) BR 14 MEXIT

.RCT1 ANOP &VALU SETA &RC(1)

ST &VALU,12+&WORK.(13) LM &REGS(1),&REGS(2),12(13) BR 14 MEXIT

.*

.NOREGS ANOP AIF ('&RC' EQ '').RCT6 AIF ('&RC'(1,1) EQ '(').RCT5 LA 15,&RC

.RCT6 ANOP BR 14 MEXIT

.RCT5 ANOP &WORK SETA &RC(1)

LR 15,&WORK

Page 62: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 62 / 119

BR 14 MEXIT MEND

Page 63: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 63 / 119

MVS SYSTEM MACROS back

QSAM

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) | (P) | (G,P),M|L) LRECL =, BLKSIZE=, RECFM =F | FB | FBA | V |VB, DEVD=DA | TA | PR, EODAD=, Notes:- G Get, P Put, G,P Get and PUT M Move mode I/O L Locate mode I/O F Fixed unblocked FB Fixed blocked FBA Fixed blocked with first character as a ASA control character. Used only for printer output V Variable unblocked VB Variable blocked

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)

Page 64: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 64 / 119

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

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 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=VB

SAVE DS 18F

END

JCL //SYSPRINT DD SYSOUT=*

Memory Management

GETMAIN

Page 65: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 65 / 119

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 R,LV=lv,BNDRY=bndry,LOC=1oc R Register form LV Length value BNDRY DBLWD/PAGE LOC BELOW/ANY (16MB line)

Example GETMAIN R,LV=4096,BNDRY=PAGE,LOC=ANY Note: More details on GETMAIN are available in the chapter VIRTUAL STORAGE MANAGEMENT

Example This example uses DXD, CXD data types and Q type address constant 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

Page 66: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 66 / 119

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) . ROUTINE B Name Operation Operand B CSECT . L 3,DOFFS AR 3,11 ST 2,0(0,11) . G DXD 5D D DXD 10F . GOFFS DC Q(G) DOFFS DC Q(D) . ROUTINE C Name Operation Operand E DSECT ITEM DS F NO DS F SUM DS F C CSECT . L 3,EOFFS AR 3,11 USING E,3 ST 9,SUM . . EOFFS DC Q(E) . .

FREEMAIN

Releases the acquired virtual storage

Address should be on a double word boundary

Page 67: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 67 / 119

Syntax Name FREEMAIN R,LV=lv,A=addr

R Register form lv Length value A Virtual storage address

Example FREEMAIN R,LV=4096,A=(1) Note: More details on FREEMAIN are available in the chapter VIRTUAL STORAGE MANAGEMENT

Example of a program that dynamically acquires its working storage and initialises it with

constants from static read only storage. FIRST CSECT

FIRST AMODE 31

FIRST RMODE ANY

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

MVC WS+72(LEN-72),WSCONST+72

BAL 2,INIT

LOAD EP=ADD

LTR 15,15

BNZ 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 L 13,SAVE+4

LM 14,12,12(13)

LA 15,16

BR 14

WSCONST DS 0F

DS 18F

DC F'100'

Page 68: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 68 / 119

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

RES DS F

PARM DS F

DS F

DS F

MSG DS AL2

DS CL16

DW DS D

END

ADD CSECT

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

LA 13,SAVE

LR 2,1

WTO 'IN ADD'

LR 1,2

LM 2,4,0(1)

L 5,0(0,2)

A 5,0(0,3)

ST 5,0(0,4)

WTO 'EXITING ADD'

L 13,SAVE+4

LM 14,12,12(13)

LA 15,0

BSM 0,14

SAVE DS 18F

END

Program Management

LOAD

Brings the load module into virtual storage

Module contains program or table

Page 69: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 69 / 119

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 AMODE (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 LTR 15,15 BNZ ERROR LR 15,0 stick to using register 15 for entry point BSSM 14,15 BSSM takes care of switch of AMODE if reqd. 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))

Page 70: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 70 / 119

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.

Example: XCTL (2,12),EP=MYPROG,MF=(E,ADDRDATA) . . ADDRDATA DC A(PARM1) DC A(PARM2)

LINK

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

Name LINK EP=entry name, PARAM=(parm1,parm2,…..),VL=1, ERRET=errroutine 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 EP=MYPROG,PARAM=(parm1,parm2), ERRET=ERROR . . PARM1 DS F PARM2 DS F ERROR …

Process Management

ABEND Name ABEND compcode,REASON=,DUMP,STEP compcode value 0 to 4095.Register notation (2) to (12) permitted REASON 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

Page 71: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 71 / 119

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 reg 1 Name ATTACH EP=entry name,

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 regs 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

Page 72: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 72 / 119

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) 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 EP=PROG1,EXTR=ENDOFTSK LTR 15,15 BNZ ERROR ST 1,TCB1 save address of TCB for later use

. . TCB1 DC F'0' ENDOFTSK DETACH (1) BR 14

WAIT

Wait for completion of events

Initialise the ECB before calling

A list of ECB’s can be specified for waiting on any number of events

Example of MAIN creating two subtasks TASK1 and TASK2 FIRST 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 ECB=ECB1

WTO 'MAIN1 ENTERING WAIT FOR TASK2 COMPLETION'

WAIT ECB=ECB2

LA 4,TCB1

Page 73: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 73 / 119

DETACH (4)

LA 4,TCB2

DETACH (4)

L 13,SAVE+4

RETURN (14,12),,RC=0

ERROR1 L 13,SAVE+4

RETURN (14,12),,RC=4

ERROR2 L 13,SAVE+4

RETURN (14,12),,RC=8

SAVE DS 18F

ECB1 DC F'0'

ECB2 DC F'0'

TCB1 DS F

TCB2 DS F

END

TASK1 CSECT

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

LA 13,SAVE

LA 5,50

LOOP WTO 'TASK1 REPORTING'

BCT 5,LOOP

L 13,SAVE+4

LM 14,12,12(13)

SR 15,15

BR 14

SAVE DS 18F

END

TASK2 CSECT

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

LA 13,SAVE

LA 5,50

LOOP WTO 'TASK2 REPORTING'

BCT 5,LOOP

L 13,SAVE+4

LM 14,12,12(13)

SR 15,15

BR 14

SAVE DS 18F

END

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)

Page 74: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 74 / 119

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)

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 for 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'

Example using WTO FIRST CSECT

Page 75: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 75 / 119

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

GETMAIN R,LV=LMSG

LR 2,1

LA 3,MSG

LA 4,LMSG

BCTR 4,0

EX 4,MV

WTO ,MF=(E,(2))

LA 13,SAVE

L 13,SAVE+4

LM 14,12,12(13)

SR 15,15

BR 14

SAVE DS 18F

MV MVC 0(0,2),0(3)

MSG WTO 'THIS IS THE MESSAGE',MF=L

LMSG EQU *-MSG

END

Re-entrancy and writable storage FIRST CSECT

STM 14,12,12(13)

BALR 12,0

USING *,12

LR 2,1

GETMAIN R,LV=WSLENGTH,LOC=BELOW

USING WS,1

ST 13,SAVE+4

LA 13,SAVE

DROP 1

LR 13,1

LR 1,2

USING WS,13

WTO 'ASM1 REPORTING'

MVC MSG+2(6),=C'ABCDEF'

LA 6,6

STH 6,MSG

LA 6,MSG

WTO TEXT=(6)

LA 15,4

LR 2,13

L 13,SAVE+4

FREEMAIN R,LV=WSLENGTH,A=(2)

L 14,12(0,13)

LM 0,12,20(13)

BR 14

WS DSECT

SAVE DS 18F

MSG DS AL2

DS CL100

WSLENGTH EQU *-WS

Page 76: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 76 / 119

END

Page 77: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 77 / 119

ACCESSING VSAM DATA SETS USING ASSEMBLER LANGUAGE back

Macros

Name ACB AM=VSAM,

BUFND=,

BUFNI=,

BUFSP=,

DDNAME=,

MACRF=([ADR],[,CNV][,KEY][,DIR][,SEQ][,SKP][,IN][,OUT] )

EXLST=,

PASSWD=,

NOTES: AM : Always code VSAM for access to VSAM data sets BUFND : Number of data buffers, default=2,override possible through JCL BUFNI : Number of Index buffers, default=1,override possible through JCL BUFSP : Size of area for Index and Data Buffers. Defaults to specification in catalogue DDNAME : Connects a DD statement in run time JCL with this ACB EXLST : Address of EXLST macro MACRF : 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 PASSWD : Address(label) of an area which contains password for the Data

set 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] )]

Notes EODAD Is the exit routine for end of file JRNAD exit routine for journal file updates/deletions/insertions LERAD Logical error exit SYNAD Physical error exit A Routine is active N Routine is inactive L Routine is to be dynamically loaded when required

Name RPL ACB=,

AREA=,

AREALEN=,

RECLEN=,

ARG=,

KEYLEN=,

OPTCD=,

NXTRPL=

Page 78: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 78 / 119

NOTES : ACB : Address of ACB macro (label) AM : Always code VSAM (used for documentation purposes only) 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|IPD],[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 Start sequential processing forward or backward with the : record identified by the ARG field : LRD For Backward processing start from the last record in the file : NSP No updating(for Direct processing VSAM is positioned at : the next record in the file). : NUP No updating, VSAM is not positioned for subsequent

: processing : UPD Retain position for Updating : LOC Locate mode I/O(record is processed in VSAM Buffers) : MOV Move mode I/O(records are processed in programs data area) : ASY Asynchronous operation. Program can continue with : other processing. Later uses CHECK macro to wait on : completion : SYN synchronous operation. Program waits until operation is : complete : FKS full key search : GEN generic search. KEYLEN must be specified

: KEQ search key equal : KGE 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

Page 79: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 79 / 119

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

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 | (register) retrieve a record

PUT RPL=Label of RPL macro | (register) write a record

POINT RPL=Label of RPL macro | (register) position for subsequent access

ERASE RPL=Label of RPL macro | (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 This macros is fetch control block fields

TESTCB This macro is used to test control block fields

MODCB This macro used to modify control block fields

GENCB This macro is used to dynamically generate a control block at run time

Name SHOWCB ACB|EXLST|RPL=,

AM=VSAM, only for documentation purpose

AREA=,

LENGTH=,

FIELDS=(keyword[,keyword]…)

Notes: ACB|EXLST|RPL : Address (label) of specified Macro AREA : Area into which VSAM will put the contents of field specified LENGTH : 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

FIELDS : Can be most of any field specified in the ACB|EXLST|RPL macro; FOR RPL : ACB,AREA,AREALEN,FDBK,KEYLEN,RECLEN

: RBA,NXTRPL all one full word of data FOR EXLST : EODAD,JRNAD,LERAD,SYNAD FOR ACB : 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

Page 80: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 80 / 119

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 NUPDR Number of records updated in file RKP Position of record key relative to start of record

Name TESTCB ACB|EXLST|RPL=,

AM=VSAM, only for documentation purpose

ERET=,

keyword=,

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

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

RPL1 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 ACB|EXLST|RPL=,

AM=VSAM, only for documentation purpose

Operand keyword= new value

Example: MODCB RPL=RPL1,OPTCD=(DIR) . . . RPL1 RPL …. FRAMEWORK OF ASSEMBLER PROGRAMS TO ACCESS VSAM FILES Keyed Direct Deletion

Page 81: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 81 / 119

DELETE ACB MACRF=(KEY,DIR,OUT) LIST RPL ACB=DELETE,AREA=WORK,AREALEN=50, X ARG=KEYFIELD,OPTCD=(KEY,DIR,SYN,UPD, X

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.

Example Keyed Sequential retrieval (Forward) INPUT ACB MACRF=(KEY,SEQ,IN) RETRVE RPL ACB=INPUT,AREA=IN,AREALEN=100, X OPTCD=(KEY,SEQ,SYN,NUP,MVE) LOOP GET RPL=RETRVE LTR 15,15 BNZ ERROR . . process the record B LOOP ERROR …… error handler . IN DS CL100 Example Keyed sequential retrieval (backward) INPUT ACB DDNAME=INPUT,EXLST=EXLST1 RETRVE RPL ACB=INPUT,AREA=IN,AREALEN=100, X 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

Page 82: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 82 / 119

B LOOP EOD EQU * . . come here for end of file ERROR . . come here for any error . IN DS CL100 Example Skip Sequential retrieval ksds variable length records

GENCB BLK=ACB,DDNAME=INPUT,MACRF=(KEY,SKP,IN) LTR 15,15 BNZ ERROR LR 2,1 GENCB BLK=RPL,ACB=(2),AREA=RCDADDR, X

AREALEN=4, X ARG=SRCHKEY, X

OPTCD=(KEY,SKP,SYN,NUP,KGE,FKS,LOC) LTR 15,15 BNZ CHECK0

LR 3,1 . LOOP MVC SRCHKEY,source GET RPL=(3) LTR 15,15 BNZ ERROR SHOWCB AREA=RCDLEN,FIELDS=RECLEN,LENGTH=4, X RPL=(3) LTR 15,15 BNZ CHECK0 . B LOOP ERROR …. CHECK0 …. RCDADDR DS F SRCHKEY DS CL8 RCDLEN DS F Example Keyed Direct Retrieval in LOCATE mode(KSDS, RRDS) INPUT ACB MACRF=(KEY,DIR,IN) RETRVE RPL ACB=INPUT,AREA=IN,AREALEN=4,OPTCD=(KEY, X DIR,SYN,NUP,KEQ,GEN,LOC),ARG=KEYAREA, X KEYLEN=5 . . LOOP MVC KEYAREA,source GET RPL=RETRVE LTR 15,15 BNZ ERROR . Address of record is now in IN . B LOOP

Page 83: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 83 / 119

ERROR ….. . IN DS CL4 Where VSAM puts the address of the record in the I/O buffer KEYAREA DS CL5 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 Example Switch from Direct to Sequential retrieval INPUT ACB MACRF=(KEY,DIR,SEQ,IN) RETRVE RPL ACB=INPUT,AREA=IN,AREALEN=100, X OPTCD=(KEY,DIR,SYN,NSP,KEQ,GEN,MVE), X ARG=KEYAREA,KEYLEN=8 . . LOOP MVC KEYAREA,source LOOP1 GET RPL=RETRVE direct get LTR 15,15 BNZ ERROR . SHOWCB RPL=RETRVE,AREA=FDBAREA,FIELDS=FDBK LTR 15,15 CLI ERRCD,8 If 8 means duplicate records BE SEQ B LOOP SEQ MODCB RPL=RETRVE,OPTCD=SEQ * * switched to sequential mode * LTR 15,15 BNZ ERROR SEQGET GET RPL=RETRVE LTR 15,15 BNZ ERROR . SHOWCB RPL=RETRVE,AREA=FDBAREA,FIELDS=FDBK LTR 15,15 BNZ ERROR CLI ERRCD,8 * check to see if still need sequential mode BE SEQGET * if not switch back to direct mode * DIR MODCB RPL=RETRVE,OPTCD=DIR LTR 15,15 BNZ ERROR B LOOP ERROR …..

Page 84: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 84 / 119

IN DS CL100 KEYAREA DS CL8 FDBAREA DS 0F DS 1C TYPECD DS 1C CMPCD DS 1C ERRCD DS 1C Example Position with POINT macro BLOCK ACB DDNAME=IO POSITION RPL ACB=BLOCK,AREA=WORK,AREALEN=50, X 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 Example Keyed Sequential insertion KSDS variable length BLOCK ACB DDNAME=OUTPUT,MACRF=(KEY,SEQ,OUT) LIST RPL ACB=BLOCK,AREA=BUILDRCD,AREALEN=250, X 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 Example Skip Sequential insertion for KSDS variable length record OUTPUT ACB MACRF=(KEY,SKP,OUT) RPL1 RPL ACB=OUTPUT,AREALEN=80, X

OPTCD=(KEY,SKP,SYN,NUP,MVE), X AREA=WORK

* * set up record in WORK *

Page 85: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 85 / 119

LOOP PUT RPL=RPL1 LTR 15,15 BNZ ERROR . set up next record B LOOP ERROR ….. WORK DS 80C Note:In skip sequential insertion you do not need to have a ARG field with key value. However records have to be in sequence. Example Keyed direct insertion OUTPUT ACB MACRF=(KEY,DIR,OUT) RPL1 RPL ACB=OUTPUT,AREALEN=80, X

OPTCD=(KEY,DIR,SYN,NUP,MVE), X 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 keyfield from the record area. Example Keyed Direct Update INPUT ACB NACRF=(KEY,DIR,OUT) UPDTE RPL ACB=INPUT,AREA=IN,AREALEN=120, X OPTCD=(KEY,DIR,SYN,UPD,KEQ,FKS,MVE), X ARG=KEYAREA,KEYLEN=5 * * set up search argument * LOOP GET RPL=UPDTE LTR 15,15 BNZ ERROR SHOWCB RPL=UPDTE,AREA=RLNGTH,FIELDS=RECLEN, X 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

Page 86: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 86 / 119

BNZ ERROR B LOOP ERROR ….. IN DS CL120

KEYAREA DS CL5

RLGTH DS F

FULL EXAMPLE 1 SEQUENTIAL READ. PGMNAM START 0 BEGIN SAVE (14,12) BALR 3,0 USING *,3 ST 13,SAVE+4 LA 13,SAVE OPEN (ACB1) LTR 15,15 set CC based on value in register 15 BNZ OPENERR and test for open error . . LOOP GET RPL=RPL1 LTR 15,15 set CC based on value in register 15 BNZ READERR and test for read error . Process record here . B LOOP CLOSE (ACB1) L 13,SAVE+4 RETURN (14,12) ACB1 ACB AM=VSAM,MACRF=IN RPL1 RPL ACB=ACB1,AREA=REC1,AREALEN=80,RECLEN=80 REC1 DS CL80 SAVE DS 18F END BEGIN FULL EXAMPLE 2 DIRECT RETRIEVAL FOR UPDATE. EXAMPLE START 0 BEGIN SAVE (14,12) BALR 3,0 USING *,3 ST 13,SAVE+4 LA 13,SAVE OPEN (ACB1) LTR 15,15 BNZ DUMP no point continuing if file will not open LOOP MVC ITEMKEY,… Set up record key GET RPL=RPL1 now fetch record LTR 15,15 BNZ ERROR if error check what error . . modify record as desired . PUT RPL=RPL1 LTR 15,15 BNZ DUMP at this stage any error is unexpected .

Page 87: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 87 / 119

. B LOOP CLOSE (ACB1) LTR 15,15 BNZ DUMP error closing files is serious L 13,SAVE+4 RETURN (14,12) ERROR TESTCB RPL=RPL1,FDBK=16 any error other than no BE LOOP record found is serious DUMP ABEND 1000,DUMP REC1 DS CL80 ITEMKEY DS CL6 SAVE DS 18F ACB1 ACB AM=VSAM,MACRF=(DIR,OUT) RPL1 RPL ACB=ACB1,AREA=REC1,AREALEN=80,RECLEN=80, X

ARG=ITEMKEY,OPTCD=(DIR,UPD)

Page 88: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 88 / 119

LINKAGE CONVENTIONS / 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 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 L 15,=A(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 USING PGM,12 GETMAIN RU,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 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 RU,A=(2),LV=72 release this programs save area SR 15,15 Zero R15 L 14,12(0,13) Restore R14 of caller LM 2,12,28(13) Restore R2 to R12 of caller

BR 14 Return END

Primary mode program which uses Linkage stack 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.

Page 89: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 89 / 119

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 R14 instruction.

Passing Parameters

If the calling program is in primary mode, the parameter list should be in primary address space

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 array should have bit 0 set to 1 to indicate it is the last element.

In Primary Mode

Example if control is passed to another program in same mode. L 15,NEXTADDR CNOP 0,4 BAL 1,GOOUT PARMLIST DS 0A DCBADDRS DC A(INDCB) DC A(OUTDCB) ANSWERAD DC A(AREA+X'80000000) NEXTADDR DC V(NEXTPGM) GOOUT BALR 14,15 RETURN . . ARE DC 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 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

GPR1

A(PARM1)

A(PARM2)

A(PARM3)

1 A(PARMN)

2 BYTE LENGTH PARM FIELD -----------

2 BYTE LENGTH PARM FIELD-------------

Page 90: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 90 / 119

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 CSECT MAIN AMODE 31 AMODE can be 24 / 31 / any.Default=24 MAIN RMODE 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

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.

BASSM does all that BSM does and in addition the link register contains the return address.

If we need to transfer control without a change of addressing mode use the following combinations

Transfer Return BAL/BALR BR BAS/BASR BR

If we need to change the AMODE as well use BASSM

Example TEST CSECT TEST AMODE 24 TEST RMODE 24 . . L 15,EPA Obtain transfer address BASSM 14,15 switch AMODE and branch . . EXTRN EP1 EPA DC A(X'80000000+EP1) set high order bit to 1 to switch AMODE . . END

Page 91: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 91 / 119

EP1 CSECT EP1 AMODE 31 EP1 RMODE ANY . . SLR 15,15 set return code to 0 BSM 0,14 return and switch to callers AMODE END

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 A mode bit affect the way some H/W instructions work (BAL,BALR,LA,LRA)

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

LINK, XCTL, ATTACH

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

Calling module

amode 24

rmode 24

Called module

amode 24

rmode 24

Calling module

amode 24

rmode 24

Called module

amode 31

rmode 24

Page 92: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 92 / 119

//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 USER CSECT USER AMODE 24 USER RMODE 24 L 15,ACTLB L 1,LABEL1 BSM 0,1 LABEL1 DC A(LABEL2+X'80000000) LABEL2 DS 0H L 2,4,(,15) LA 1,LABEL3 BSM 0,1 LABEL3 DS 0H . . END

Page 93: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 93 / 119

OK

OK OK

16 MB LINE

OK

16 MB line definitely a problem

possible problem

possible problem

AMODE 31 AMODE 31

AMODE 31 AMODE 31

AMODE 31 AMODE 31

AMODE 24

AMODE 24

AMODE 31

Page 94: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 94 / 119

16MB LINE

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 RTN2AD EXTRN RTN3AD . . L 15,=A(RTN2AD) L 15,0(,15) BASSM 14,15 . . L 15,=A(RTN3AD) L 15,0(,15) BASSM 14,15 . . END RTN2 CSECT RTN2 AMODE 24 ENTRY RTN2AD . BSM 0,14 RTN2AD DC A(RTN2) RTN3 CSECT RTN3 AMODE 31 ENTRY RTN3AD . BSM 0,14

ABOVE CSECT

ABOVE AMODE 31

ABOVE RMODE ANY .

.

.

BSM 0,14

BELOW CSECT

BELOW AMODE 24

BELOW RMODE 24

LOAD EP=ABOVE

ST 0,EPABOVE

L 15,EPABOVE

BASSM 14,15

Page 95: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 95 / 119

RTN3AD DC A(X'80000000+RTN3)

Example of 31 bit program with static storage above 16 MB line. This program does not

work with ADD as ADD operates in 24 bit mode. FIRST CSECT

FIRST AMODE 31

FIRST RMODE ANY

STM 14,12,12(13)

BALR 12,0

USING *,12

ST 13,SAVE+4

LA 13,SAVE

LOAD EP=ADD

LTR 15,15

BNZ LOADERR

LR 15,0

LA 1,PARMS

BASSM 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

LOADERR L 13,SAVE+4

LM 14,12,12(13)

LA 15,16

BR 14

SAVE DS 18F

B DC F'200'

A DC F'100'

RES DS F

PARMS DC A(A)

DC A(B)

DC A(X'80000000'+RES)

MSG DC AL2(16)

DS CL16

DW DS D

END

Example of 31 bit program with dynamically acquired storage below the line. This program

works fine with ADD although ADD operates in 24 bit mode. FIRST CSECT

FIRST AMODE 31

FIRST RMODE ANY

STM 14,12,12(13)

BALR 12,0

USING *,12

LR 2,1

Page 96: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 96 / 119

GETMAIN R,LV=LEN,LOC=BELOW

ST 13,4(0,1)

USING WS,13

LR 13,1

LR 1,2

BAL 2,INIT

LOAD EP=ADD

LTR 15,15

BNZ LOADERR

LR 15,0

LA 1,PARMS

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 L 13,SAVE+4

LM 14,12,12(13)

LA 15,16

BR 14

INIT LA 3,100

ST 3,A

LA 3,200

ST 3,B

LA 3,A

ST 3,PARMS

LA 3,B

ST 3,PARMS+4

LA 3,RES

ST 3,PARMS+8

LA 3,16

STH 3,MSG

BR 2

WS DSECT

SAVE DS 18F

A DS F

B DS F

RES DS F

PARMS DS F

DS F

DS F

MSG DS AL2

DS CL16

DW DS D

Page 97: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 97 / 119

LEN EQU *-WS

END

By default ADD operates in 24 / 24 mode ADD CSECT

STM 14,12,12(13)

USING ADD,15

ST 13,SAVE+4

LA 13,SAVE

LR 12,15

DROP 15

USING ADD,12

LR 2,1

WTO 'IN ADD'

LR 1,2

LM 2,4,0(1)

L 5,0(0,2)

A 5,0(0,3)

ST 5,0(0,4)

WTO 'EXITING ADD'

L 13,SAVE+4

LM 14,12,12(13)

LA 15,0

BSM 0,14

SAVE DS 18F

END

Page 98: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 98 / 119

ASSEMBLER COURSE LAB EXERCISES

The following exercises do not present any complex assembler programming effort. Rather they serve to reinforce basic and fundamental concepts. The instructions you may need to use may not be more than about twenty or so. Before you start you need to have the quick reference card, Assembler services reference and assembler services guide handy. The principles of operation which explain all operation codes in detail is available online (Windows network) in case you need it. Most operation codes you use would have been explained in the class handouts and that should be adequate. You may also need to have access to MVS codes in case your program abends. Good luck and happy programming !.

Setup the work environment Note:The data set space parameters are given on a rough basis only. In case you get into a data set full condition, you may have to create a larger, new data set and copy the members across. 1)Create a PDS for your assembler source as below Lrecl 80 Blksize 800

Recfm FB DSN userid.asmclass.asm Unit SYSDA or allow SMS to default Primary alloc 2 trk Sec alloc 2trk Dir 5 block Unit of allocation trk 2)Create a PDS for your assembler JCL as below Lrecl 80

Blksize 800 Recfm FB DSN userid.asmclass.cntl Unit SYSDA or allow SMS to default Primary alloc 2 trk Sec alloc 1trk Dir 5 block Unit of allocation trk 3)Creat a PDS for your assembler object files as below Lrecl 80 Blksize 800 Recfm FB DSN userid.asmclass.obj Unit SYSDA or allow SMS to default Primary alloc 2 trk Sec alloc 1trk Dir 5 block Unit of allocation trk 4)Creat a PDS for your assembler loadlib as below Lrecl 23200 Blksize 0 Recfm U DSN userid.asmclass.loadlib Unit SYSDA or allow SMS to default Primary alloc 2 trk Sec alloc 2trk

Page 99: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 99 / 119

Dir 10 block Unit of allocatin trk 5)Creat a PDS for your assembler user macros as below Lrecl 80 Blksize 800 Recfm FB DSN userid.asmclass.maclib Unit SYSDA or allow SMS to default Primary alloc 2 trk Sec alloc 1trk Dir 5 block Unit of allocatin trk 6)Browse the member ASMACL in the SYS1.PROCLIB . This is the procedure to assemble and link your

assembler programs.You should be able to understand every line of the prcedure as well as the assembler and linker options. You may have to access IBM manuals for the assembler and linker options. Understand what statements need to be overridden to achieve the following:-

Program source from userid.asmclass.asm Program Loadmodule into userid.asmclass.loadlib Object code for subprograms into userid.asmclass.obj Object code for subprograms from userid.asmclass.obj User macros from userid.asmclass.maclib Change assembler and linker parms (if appropriate) when invoking the Procedure.

Page 100: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 100 / 119

EXERCISES 1)Write a simple assembler program which does nothing other than return to check out the operation of the

JCL and submitting jobs to batch. Make sure that you understand the process including using the SDSF facility.

2)Write a program which can detect and copy the value passed through the PARM field in the exec

statement and output it via SYSOUT

3)Write an assembler program which converts a 26 byte character field from lower case to upper case. Verify the correct operation of the program through a SNAP dump before and after the operation.

4)Write an assembler program to convert a binary value in a full word storage field to a displayable value in another storage field. Verify correct operation through SNAP dump

5)a)Write a user macro (store it in userid.asmclass.maclib) which accepts a binary full word field in a GPR (operand one) and converts it to a displayable value in a memory field (operand two)

b)Use the program logic debugged and working from previous example. You will also have to make JCL modifications to include your maclib

c)Write your own macro to implement saving and restoring registers on entry and exit into your program.

6)Write an assembler program to open and read a QSAM PS file and output it via SYSOUT 7)Create a VSAM KSDS data set and load the data set using an assembler program which reads input from a QSAM PS file and loads it in sequential mode.

8)Run an IDCAMS job stream to ensure that the data set has been loaded (use PRINT option )

9)Insert records in the data set using DIRECT mode and input from another QSAM file where records which

may be in any order

10)Try out other modes of VSAM access like DIRECT get, SEQ get with an EODAD routine defined through EXLST macro. Use SHOWCB macro to test VSAM feedback code after each operation. Use dynamic storage allocation (Getmain / Storage macro) to acquire storage for data buffers in your program.

11)Write a main program which calls a subprogram in the same file with three storage Fullword integers as

parameters. The subprogram must add the two integers and return the sum in the third fullword. Output the result via sysout. Note that you have to convert the binary form to displayable form using the CVD and UNPACK instructions.

12)Write an assembler sub program which can be called using CALL macro. The main program and the

subprogram should share the same DCB for SYSOUT data. Main and sub programs should announce their entry and exit thru messages on SYSOUT. Note that main and sub programs are having separate source files and need separate compilation. Hint:You will need to have modified ASMACL to create the Object code for the subprogram which is to be in userid.asmclass.obj.

13)Write an assembler program to do the same function as in exercise (17) above but using a LOAD macro.

14)Write a main program which creates a subtask with the ATTACH macro. The main program and the

subprogram must share the same DCB for the SYSOUT dataset. The main and subprogram must announce their entry and exit. The main program must wait for the attached task to complete before ending.

Page 101: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 101 / 119

*******************************************************************************

* USE THIS PROGRAM TO CHECK OUT YOUR JCL AND BATCH JOB SUBMISSION*

* BEFORE YOU START THE EXERCISES *

*******************************************************************************

BEGIN CSECT

SAVE (14,12)

BALR 12,0

USING *,12

ST 13,SAVE+4

L 13,SAVE+4

RETURN (14,12),,RC=0

SAVE DS 18F

END BEGIN

Page 102: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 102 / 119

********************************************************************************

* EXAMPLE OF LOADING AND EXECUTING A PROGRAM AT RUN TIME *

********************************************************************************

BEGIN CSECT 00010000

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

*

OPEN (FILE2,OUTPUT) 00081005

LTR 15,15 00082005

BNZ ERROR1 00083015

*

MVC OUTBUFF(L'MSG1),MSG1 00084018

PUT FILE2,OUTBUFF 00090218

*

LOAD EP=SUB1 00090319

LTR 15,15 00090419

BNZ LOADERR 00090519

LR 15,0 00090619

BALR 14,15 00090719

*

MVC OUTBUFF(L'MSG2),MSG2 00090820

PUT FILE2,OUTBUFF 00090918

L 13,SAVE+4 00146009

RETURN (4,12),,RC=0 00147009

ERROR1 L 13,SAVE+4 00148015

RETURN (14,12),,RC=4 00149015

LOADERR L 13,SAVE+4 00150019

RETURN (14,12),,RC=8 00151019

OUTBUFF DC CL80' ' 00160018

MSG1 DC C'INVOKING SUB1' 00161018

MSG2 DC C'EXITING MAIN1' 00162018

SAVE DS 18F 00170000

FILE2 DCB DSORG=PS,RECFM=F,BLKSIZE=132,LRECL=132, X 00200001

MACRF=PM,DDNAME=OUTFILE,DEVD=PR 00210005

END BEGIN 00220001

Page 103: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 103 / 119

*******************************************************************************

* SUB1 *

*******************************************************************************

SUB1 CSECT 00010019

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

OPEN (FILE2,OUTPUT) 00081005

LTR 15,15 00082005

BNZ ERROR1 00083015

L 2,=F'5' 00084015

LOOP PUT FILE2,OUTBUFF 00090215

BCT 2,LOOP 00110015

CLOSE (FILE2) 00120018

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

ERROR1 L 13,SAVE+4 00148015

RETURN (14,12),,RC=4 00149015

OUTBUFF DC C'THIS IS SUB 1 LOOPING' 00160015

DC CL(80-L'OUTBUFF)' ' 00161017

SAVE DS 18F 00170000

FILE2 DCB DSORG=PS,RECFM=F,BLKSIZE=132, X

LRECL=132,MACRF=PM,DDNAME=SUBFILE, X

DEVD=PR 00210018

END 00220019

Page 104: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 104 / 119

*******************************************************************************

* EXAMPLE OF USAGE OF A CALL MACRO *

*******************************************************************************

BEGIN CSECT 00010000

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

OPEN (FILE2,OUTPUT) 00081005

LTR 15,15 00082005

BNZ ERROR1 00083015

MVC OUTBUFF(L'MSG1),MSG1 00084018

PUT FILE2,OUTBUFF 00090218

CALL SUB2,(FILE2) 00090322

MVC OUTBUFF(L'MSG2),MSG2 00090820

PUT FILE2,OUTBUFF 00090918

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

ERROR1 L 13,SAVE+4 00148015

RETURN (14,12),,RC=4 00149015

LOADERR L 13,SAVE+4 00150019

RETURN (14,12),,RC=8 00151019

OUTBUFF DC CL80' ' 00160018

MSG1 DC C'INVOKING SUB1' 00161018

MSG2 DC C'EXITING MAIN1' 00162018

SAVE DS 18F 00170000

FILE2 DCB DSORG=PS,RECFM=F,BLKSIZE=132,LRECL=132, X00200001

MACRF=PM,DDNAME=OUTFILE,DEVD=PR 00210005

END BEGIN 00220001

Page 105: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 105 / 119

*******************************************************************************

* SUB2 *

*******************************************************************************

SUB2 CSECT 00010021

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

L 4,0(1) 00080022

L 2,=F'5' 00084015

LOOP PUT (4),OUTBUFF 00090222

BCT 2,LOOP 00110015

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

OUTBUFF DC C'THIS IS SUB 1 LOOPING' 00160015

DC CL(80-L'OUTBUFF)' ' 00161017

SAVE DS 18F 00170000

END 00220019

Page 106: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 106 / 119

*******************************************************************************

* EXAMPLE OF USAGE OF ATTACH A SUBTASK USING ATTACH MACRO *

*******************************************************************************

BEGIN CSECT 00010000

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

SYSSTATE ASCENV=P 00080026

OPEN (FILE2,OUTPUT) 00081005

LTR 15,15 00082005

BNZ ERROR1 00083015

MVC OUTBUFF(L'MSG1),MSG1 00084018

PUT FILE2,OUTBUFF 00090218

ATTACHX EP=SUB3,ETXR=ETXSUB3,PARAM=FILE2, X

SZERO=YES 00090328

LTR 15,15 00090419

BNZ ATTCHERR 00090521

WAIT 1,ECB=ECBSUB3 00090722

MVC OUTBUFF(L'MSG2),MSG2 00091020

PUT FILE2,OUTBUFF 00092018

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00146125

ETXSUB3 ST 1,TCBADDR 00146232

DETACH TCBADDR 00146332

POST ECBSUB3 00146425

BR 14 00146525

ERROR1 L 13,SAVE+4 00148015

RETURN (14,12),,RC=4 00149015

ATTCHERR L 13,SAVE+4 00150021

RETURN (14,12),,RC=8 00151019

TCBADDR DC A(0) 00151132

ECBSUB3 DC F'0' 00152021

OUTBUFF DC CL80' ' 00160018

MSG1 DC C'INVOKING SUB3' 00161021

MSG2 DC C'EXITING MAIN3' 00162021

SAVE DS 18F 00170000

FILE2 DCB DSORG=PS,RECFM=F,BLKSIZE=132,LRECL=132, X00200001

MACRF=PM,DDNAME=OUTFILE,DEVD=PR 00210005

END BEGIN 00220001

Page 107: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 107 / 119

*********************************************************************

* SUB3 *

*********************************************************************

SUB3 CSECT 00010023

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

L 4,0(1) 00080022

L 2,=F'20' 00084023

LOOP PUT (4),OUTBUFF 00090222

BCT 2,LOOP 00110015

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

OUTBUFF DC C'THIS IS SUB 3 LOOPING' 00160023

DC CL(80-L'OUTBUFF)' ' 00161017

SAVE DS 18F 00170000

END 00220019

Page 108: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 108 / 119

***********************************************************************

* EXAMPLE OF INVOKING ANOTHER PROGRAM AT RUN TIME USING A*

* LINK MACRO *

***********************************************************************

BEGIN CSECT 00010000

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

OPEN (FILE2,OUTPUT) 00081005

LTR 15,15 00082005

BNZ ERROR1 00083015

MVC OUTBUFF(L'MSG1),MSG1 00084018

PUT FILE2,OUTBUFF 00090218

LINK EP=SUB4,PARAM=FILE2 00090335

LTR 15,15 00090419

BNZ LINKERR 00090535

MVC OUTBUFF(L'MSG3),MSG3 00094028

PUT FILE2,OUTBUFF 00095028

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00146125

ERROR1 L 13,SAVE+4 00148015

RETURN (14,12),,RC=4 00149015

LINKERR L 13,SAVE+4 00150035

RETURN (14,12),,RC=8 00151019

OUTBUFF DC CL80' ' 00160018

MSG1 DC C'INVOKING SUB4' 00161029

MSG3 DC C'EXITING MAIN4' 00162034

SAVE DS 18F 00170000

FILE2 DCB DSORG=PS,RECFM=F,BLKSIZE=132,LRECL=132, X00200001

MACRF=PM,DDNAME=OUTFILE,DEVD=PR 00210005

END BEGIN 00220001

Page 109: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 109 / 119

***********************************************************************

* SUB4 *

***********************************************************************

SUB4 CSECT 00010024

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

L 4,0(1) 00080022

L 2,=F'2' 00084025

LOOP PUT (4),OUTBUFF 00090222

BCT 2,LOOP 00110015

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

OUTBUFF DC C'THIS IS SUB 4 LOOPING' 00160026

DC CL(80-L'OUTBUFF)' ' 00161017

SAVE DS 18F 00170000

END 00220019

Page 110: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 110 / 119

************************************************************************

* EXAMPLE OF OBTAINING A SNAP DUMP *

************************************************************************

BEGIN CSECT 00010000

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

TPUT MSG,L'MSG 00071013

OPEN (FILE1,INPUT) 00080005

LTR 15,15 00080105

BNZ ERROR1 00080205

OPEN (FILE2,OUTPUT) 00081005

LTR 15,15 00082005

BNZ ERROR2 00083005

OPEN (SNAPDCB,OUTPUT) 00084014

LTR 15,15 00085014

BNZ ERROR3 00086014

LOOP GET FILE1,INBUFF 00090002

MVC OUTBUFF,INBUFF 00090108

PUT FILE2,OUTBUFF 00090208

B LOOP 00110000

ERROR1 L 13,SAVE+4 00141005

RETURN (14,12),,RC=1 00142005

ERROR2 L 13,SAVE+4 00143005

RETURN (14,12),,RC=2 00144005

ERROR3 L 13,SAVE+4 00144114

RETURN (14,12),,RC=3 00144214

EOFRTN CLOSE (FILE1,,FILE2) 00145009

SNAP DCB=SNAPDCB,ID=1,PDATA=(REGS,SA), X

STORAGE=(BEGIN,LAST) 00145214

CLOSE SNAPDCB 00145314

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

INBUFF DS CL80 00150012

OUTBUFF DS CL80 00160012

DC 52C' ' 00161012

SAVE DS 18F 00170000

MSG DC CL15'ENTERING PGM' 00171013

FILE1 DCB DSORG=PS,RECFM=FB,BLKSIZE=800, X

LRECL=80,MACRF=GM,DDNAME=INFILE, X

EODAD=EOFRTN 00190009

FILE2 DCB DSORG=PS,RECFM=F,BLKSIZE=132, X

LRECL=132,MACRF=PM,DDNAME=OUTFILE, X

DEVD=PR 00210005

SNAPDCB DCB DSORG=PS,RECFM=VBA,BLKSIZE=882, X

LRECL=125,MACRF=W,DDNAME=SNAPDMP 00210214

LAST EQU * 00211014

END BEGIN 00220001

Page 111: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 111 / 119

********************************************************************

* EXAMPLE OF LOADING VSAM KSDS SEQUENTIALLY *

********************************************************************

BEGIN CSECT 00010000

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

OPEN (FILE1,INPUT) 00080005

LTR 15,15 00080105

BNZ ERROR1 00080205

OPEN (VSAMACB) 00081015

LTR 15,15 00082005

BNZ ERROR2 00083005

LOOP GET FILE1,INBUFF 00090002

MVC OUTBUFF,INBUFF 00090108

PUT RPL=VSAMRPL 00090215

B LOOP 00110000

ERROR1 L 13,SAVE+4 00141005

RETURN (14,12),,RC=1 00142005

ERROR2 L 13,SAVE+4 00143005

RETURN (14,12),,RC=2 00144005

EOFRTN CLOSE (FILE1,,VSAMACB) 00145016

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

INBUFF DS CL80 00150012

OUTBUFF DS CL80 00160012

SAVE DS 18F 00170000

FILE1 DCB DSORG=PS,RECFM=FB,BLKSIZE=800, X

LRECL=80, MACRF=GM,DDNAME=INFILE, X

EODAD=EOFRTN 00190009

VSAMACB ACB AM=VSAM,DDNAME=OUTFILE, X

MACRF=(KEY,SEQ,OUT) 00200015

VSAMRPL RPL AM=VSAM,ACB=VSAMACB,AREA=OUTBUFF,X

AREALEN=80,ARG=VSAMKEY,KEYLEN=4, X

OPTCD=(KEY,SEQ),RECLEN=80 00210115

VSAMKEY DS F 00210215

END BEGIN 00220001

Page 112: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 112 / 119

************************************************************************

* EXAMPLE OF DIRECT UPDATE OF A VSAM KSDS USING A QSAM FILE *

* INPUT *

************************************************************************

BEGIN CSECT 00010000

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

OPEN (FILE1,INPUT) 00080005

LTR 15,15 00080105

BNZ ERROR1 00080205

OPEN (VSAMACB) 00081015

LTR 15,15 00082005

BNZ ERROR2 00083005

LOOP GET FILE1,INBUFF 00090002

MVC OUTBUFF,INBUFF 00090108

MVC VSAMKEY,OUTKEY 00090217

PUT RPL=VSAMRPL 00090315

B LOOP 00110000

ERROR1 L 13,SAVE+4 00141005

RETURN (14,12),,RC=1 00142005

ERROR2 L 13,SAVE+4 00143005

RETURN (14,12),,RC=2 00144005

EOFRTN CLOSE (FILE1,,VSAMACB) 00145016

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

INBUFF DS CL80 00150012

OUTBUFF DS 0CL80 00160017

OUTKEY DS CL4 00161017

DS CL76 00162017

SAVE DS 18F 00170000

FILE1 DCB DSORG=PS,RECFM=FB,BLKSIZE=800, X

LRECL=80,MACRF=GM,DDNAME=INFILE, X

EODAD=EOFRTN 00190009

VSAMACB ACB AM=VSAM,DDNAME=OUTFILE, X

MACRF=(KEY,DIR,OUT) 00200017

VSAMRPL RPL AM=VSAM,ACB=VSAMACB, X

AREA=OUTBUFF,AREALEN=80, X

ARG=VSAMKEY,KEYLEN=4, X

OPTCD=(KEY,DIR),RECLEN=80 00210117

VSAMKEY DS F 00210215

END BEGIN 00220001

Page 113: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 113 / 119

********************************************************************

* EXAMPLE OF READING VSAM KSDS SEQUENTIALLY *

********************************************************************

BEGIN CSECT 00010000

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

OPEN (VSAMACB) 00080018

LTR 15,15 00080105

BNZ ERROR1 00080205

OPEN (FILE1,OUTPUT) 00081018

LTR 15,15 00082005

BNZ ERROR2 00083005

LOOP GET RPL=VSAMRPL 00090018

SHOWCB RPL=VSAMRPL,AREA=RETCODE,LENGTH=4, X

FIELDS=FDBK 00090120

L 4,RETCODE 00090220

LTR 4,4 00090320

BNZ ERROR3 00090420

MVC OUTBUFF,INBUFF 00090508

PUT FILE1,OUTBUFF 00090619

B LOOP 00110000

ERROR1 L 13,SAVE+4 00141005

RETURN (14,12),,RC=1 00142005

ERROR2 L 13,SAVE+4 00143005

RETURN (14,12),,RC=2 00144005

ERROR3 L 13,SAVE+4 00144120

RETURN (14,12),,RC=3 00144220

EOFRTN CLOSE (FILE1,,VSAMACB) 00145016

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

LIST EXLST AM=VSAM,EODAD=EOFRTN 00148019

INBUFF DS CL80 00150012

OUTBUFF DS CL80 00160018

DS CL52 00161018

SAVE DS 18F 00170000

RETCODE DS F 00171020

FILE1 DCB DSORG=PS,RECFM=F,BLKSIZE=132, X

LRECL=132,MACRF=PM,DDNAME=OUTFILE, X

DEVD=PR 00190018

VSAMACB ACB AM=VSAM,DDNAME=INFILE, X

MACRF=(KEY,SEQ,IN),EXLST=LIST 00201019

VSAMRPL RPL AM=VSAM,ACB=VSAMACB,AREA=INBUFF, X

AREALEN=80,ARG=VSAMKEY,KEYLEN=4, X

OPTCD=(KEY,SEQ),RECLEN=80 00210118

VSAMKEY DS F 00210215

END BEGIN 00220001

Page 114: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 114 / 119

********************************************************************

* EXAMPLE OF READING VSAM KSDS DIRECTLY BY KEY *

********************************************************************

BEGIN CSECT 00010000

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

OPEN (VSAMACB) 00080018

LTR 15,15 00080105

BNZ ERROR1 00080205

OPEN (FILE1,OUTPUT) 00081018

LTR 15,15 00082005

BNZ ERROR2 00083005

FIRST MVC VSAMKEY,=C'0008' 00084021

GET RPL=VSAMRPL 00090021

SHOWCB RPL=VSAMRPL,AREA=RETCODE,LENGTH=4, X

FIELDS=FDBK 00090120

L 4,RETCODE 00090220

LTR 4,4 00090320

BNZ ERROR3 00090420

MVC OUTBUFF,INBUFF 00090508

PUT FILE1,OUTBUFF 00090619

SECOND MVC VSAMKEY,=C'0010' 00090721

GET RPL=VSAMRPL 00090821

SHOWCB RPL=VSAMRPL,AREA=RETCODE,LENGTH=4, X

FIELDS=FDBK 00090921

L 4,RETCODE 00091021

LTR 4,4 00092021

BNZ ERROR3 00093021

MVC OUTBUFF,INBUFF 00094021

PUT FILE1,OUTBUFF 00095021

THIRD MVC VSAMKEY,=C'0001' 00096021

GET RPL=VSAMRPL 00097021

SHOWCB RPL=VSAMRPL,AREA=RETCODE,LENGTH=4, X

FIELDS=FDBK 00098021

L 4,RETCODE 00099021

LTR 4,4 00100021

BNZ ERROR3 00101021

MVC OUTBUFF,INBUFF 00102021

PUT FILE1,OUTBUFF 00103021

FOURTH MVC VSAMKEY,=C'0050' 00103122

GET RPL=VSAMRPL 00103222

SHOWCB RPL=VSAMRPL,AREA=RETCODE,LENGTH=4, X

FIELDS=FDBK 00103322

L 4,RETCODE 00103422

LTR 4,4 00103522

BNZ ERROR3 00103622

MVC OUTBUFF,INBUFF 00103722

PUT FILE1,OUTBUFF 00103822

B ENDRTN 00104021

ERROR1 L 13,SAVE+4 00141005

RETURN (14,12),,RC=1 00142005

ERROR2 L 13,SAVE+4 00143005

Page 115: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 115 / 119

RETURN (14,12),,RC=2 00144005

ERROR3 CLOSE (FILE1,,VSAMACB) 00144121

L 13,SAVE+4 00144221

RETURN (14,12),,RC=3 00144320

ENDRTN CLOSE (FILE1,,VSAMACB) 00145021

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

INBUFF DS CL80 00150012

OUTBUFF DS CL80 00160018

DS CL52 00161018

SAVE DS 18F 00170000

RETCODE DS F 00171020

FILE1 DCB DSORG=PS,RECFM=F,BLKSIZE=132, X

LRECL=132,MACRF=PM,DDNAME=OUTFILE, X

DEVD=PR 00190018

VSAMACB ACB AM=VSAM,DDNAME=INFILE, X

MACRF=(KEY,DIR,IN) 00200021

VSAMRPL RPL AM=VSAM,ACB=VSAMACB,AREA=INBUFF, X

AREALEN=80,ARG=VSAMKEY,KEYLEN=4, X

OPTCD=(KEY,DIR),RECLEN=80 00210121

VSAMKEY DS F 00210215

END BEGIN 00220001

Page 116: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 116 / 119

************************************************************************

* EXAMPLE OF DYNAMIC ALLOCATION AND USE OF DATA AREAS *

************************************************************************

BEGIN CSECT 00010000

SAVE (14,12) 00030000

BALR 3,0 00040000

USING *,3 00050000

ST 13,SAVE+4 00060000

LA 13,SAVE 00070000

GETMAIN R,LV=NOFBYTES,LOC=BELOW 00071015

LTR 15,15 00072015

BNZ GETMERR 00073015

LR 4,1 00074015

USING BUFFS,4 00075015

OPEN (FILE1,INPUT) 00080005

LTR 15,15 00080105

BNZ ERROR1 00080205

OPEN (FILE2,OUTPUT) 00081005

LTR 15,15 00082005

BNZ ERROR2 00083005

LOOP GET FILE1,INBUFF 00090002

MVC OUTBUFF,INBUFF 00090108

PUT FILE2,OUTBUFF 00090208

B LOOP 00110000

ERROR1 FREEMAIN R,LV=NOFBYTES,A=(4) 00120015

L 13,SAVE+4 00141015

RETURN (14,12),,RC=1 00142005

ERROR2 FREEMAIN R,LV=NOFBYTES,A=(4) 00142115

L 13,SAVE+4 00143015

RETURN (14,12),,RC=2 00144005

GETMERR L 13,SAVE+4 00144315

RETURN (14,12),,RC=4 00144415

EOFRTN CLOSE (FILE1,,FILE2) 00145009

FREEMAIN R,LV=NOFBYTES,A=(4) 00145115

L 13,SAVE+4 00146009

RETURN (14,12),,RC=0 00147009

FILE1 DCB DSORG=PS,RECFM=FB,BLKSIZE=800, X

LRECL=80,MACRF=GM,DDNAME=INFILE, X

EODAD=EOFRTN 00190009

FILE2 DCB DSORG=PS,RECFM=F,BLKSIZE=132, X

LRECL=132,MACRF=PM,DDNAME=OUTFILE, X

DEVD=PR 00210005

SAVE DS 18F 00210315

* 00211115

BUFFS DSECT 00211215

INBUFF DS CL80 00212015

OUTBUFF DS CL80 00213015

DS CL52 00214015

* 00216015

NOFBYTES EQU *-INBUFF 00217015

END BEGIN 00220001

Page 117: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 117 / 119

ASMACL PROCEDURE TO COMPILE AND LINK YOUR ASSEMBLER PROGRAM

//*

//* ASMACL PROCEDURE PROVIDED BY IBM IN SYS1.PROCLIB

//* THIS PROCEDURE RUNS THE HIGH LEVEL ASSEMBLER, LINK-EDITS THE

//* NEWLY ASSEMBLED PROGRAM

//*

//ASMACL PROC

//C EXEC PGM=ASMA90

//SYSLIB DD DSN=SYS1.MACLIB,DISP=SHR

//SYSUT1 DD DSN=&&SYSUT1,SPACE=(4096,(120,120),,,ROUND),UNIT=VIO,

// DCB=BUFNO=1

//SYSPRINT DD SYSOUT=*

//SYSLIN DD DSN=&&OBJ,SPACE=(3040,(40,40),,,ROUND),UNIT=VIO,

// DISP=(MOD,PASS),DCB=(BLKSIZE=3040,LRECL=80,RECFM=FBS,BUFNO=1)

//L EXEC PGM=HEWL,PARM='MAP,LET,LIST,NACL',COND=(8,LT,C)

//SYSLIN DD DSN=&&OBJ,DISP=(OLD,DELETE)

// DD DDNAME=SYSIN

//SYSLMOD DD DISP=(,PASS),UNIT=SYSDA,SPACE=(CYL,(1,1,1)),

// DSN=&&GOSET(GO)

//SYSUT1 DD DSN=&&SYSUT1,SPACE=(1024,(120,120),,,ROUND),UNIT=VIO,

// DCB=BUFNO=1

//SYSPRINT DD SYSOUT=*

INVOCATION OF THE PROCEDURE

//HCLUSR1 JOB MSGCLASS=A,NOTIFY=HCLUSR //*

//* If you want copy the proc into your USERID.ASMCLASS.CNTL and edit it to make many

//* changes

//* if you do this you need to add the JCLLIB statement below

//* JCLLIB ORDER=(HCLUSR.ASMCLASS.CNTL) //* //MYSTEP EXEC PROC=ASMACL //C.SYSIN DD DSN=HCLUSR.ASMCLASS.ASM(memn),DISP=SHR //*

//* use the JCL statement below if you want to compile,link and also place the object code in

your

//* object library

//* C.SYSLIN DD DSN=HCLUSR.ASMCLASS.OBJ(SUB4),DISP=OLD //* //L.SYSLMOD DD DSN=HCLUSR.ASMCLASS.LOADLIB(SAMP9),DISP=OLD //L.SYSLIB DD DSN=HCLUSR.ASMCLASS.OBJ,DISP=SHR //*

//* use the JCL statement below if you want to compile, link and also place the object code in

your

//* object library

//* L.SYSLIN DD DSN=HCLUSR.ASMCLASS.OBJ(SUB4),DISP=SHR //

Page 118: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 118 / 119

SAMPLE RUN JCL - 1 //HCLUSR1 JOB MSGCLASS=A,NOTIFY=HCLUSR //JOBLIB DD DSN=HCLUSR.ASMCLASS.LOADLIB,DISP=SHR //MYSTEP EXEC PGM=SAMP9 //INFILE DD DSN=HCLUSR.ASMCLASS.DATA,DISP=SHR //SNAPDMP DD SYSOUT=* //OUTFILE DD SYSOUT=* //SUBFILE DD SYSOUT=* //

SAMPLE RUN JCL - 2 //HCLUSR1 JOB MSGCLASS=A,NOTIFY=HCLUSR //JOBLIB DD DSN=HCLUSR.ASMCLASS.LOADLIB,DISP=SHR //MYSTEP EXEC PGM=PROG3 //INFILE DD DSN=HCLUSR.ASMCLASS.DATA,DISP=SHR //OUTFILE DD DSN=HCLUSR.ASMCLASS.KSDS.CLUSTER,DISP=SHR //

SAMPLE RUN JCL - 3 //HCLUSR1 JOB MSGCLASS=A,NOTIFY=HCLUSR //JOBLIB DD DSN=HCLUSR.ASMCLASS.LOADLIB,DISP=SHR //MYSTEP EXEC PGM=PROG4 //INFILE DD DSN=HCLUSR.ASMCLASS.DATA1,DISP=SHR //OUTFILE DD DSN=HCLUSR.ASMCLASS.KSDS.CLUSTER,DISP=SHR //

SAMPLE RUN JCL - 4 //HCLUSR1 JOB MSGCLASS=A,NOTIFY=HCLUSR //JOBLIB DD DSN=HCLUSR.ASMCLASS.LOADLIB,DISP=SHR //MYSTEP EXEC PGM=PROG5 //OUTFILE DD SYSOUT=* //INFILE DD DSN=HCLUSR.ASMCLASS.KSDS.CLUSTER,DISP=SHR //

Page 119: Assembler Book

IBM 370 ASSEMBLY LANGUAGE 119 / 119

SAMPLE JCL FOR DEFINING A KSDS VSAM CLUSTER //HCLUSR1 JOB MSGCLASS=A,NOTIFY=HCLUSR //MYSTEP EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD * DEFINE CLUSTER - (NAME(HCLUSR.ASMCLASS.KSDS.CLUSTER) - TRACKS(1 1) - RECORDSIZE(80 80) - KEYS(4 0) - INDEXED - ) - DATA - (NAME(HCLUSR.ASMCLASS.KSDS.DATA) - CISZ(4096) - ) - INDEX - (NAME(HCLUSR.ASMCLASS.KSDS.INDEX)) /* //

SAMPLE JCL TO DEFINE VSAM LINEAR DATA SET //HCLUSR1 JOB MSGCLASS=A,NOTIFY=HCLUSR //MYSTEP EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD * DEFINE CLUSTER - (NAME(HCLUSR.ASMCLASS.LINEAR.DATA) - TRACKS(1 1) - LINEAR - ) /* //

SAMPLE JCL TO PRINT CONTENTS OF VSAM CLUSTER //HCLUSR1 JOB MSGCLASS=A,NOTIFY=HCLUSR //MYSTEP EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD * PRINT INDATASET(HCLUSR.ASMCLASS.KSDS.CLUSTER) CHAR /* //