churchil assembler

116
ASSEMBLY LANGUAGE - 25/09/2004 1 / 116 ASSEMBLY LANGUAGE

Upload: saravanan-bhojan

Post on 13-Oct-2014

90 views

Category:

Documents


2 download

TRANSCRIPT

Page 1: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 1 / 116

ASSEMBLY LANGUAGE

Page 2: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 2 / 116

CONTENTS1. Introduction 2. Basic Concepts 3. Instructions 4. Symbols, literals, expressions, Constants and data areas, location

counter5. Integer operations 6. Decimal operations 7. Data transfer and Logical operations 8. Bit manipulations 9. Branching 10. Assembler Directives 11. JCL aspects 12. Subroutines, linkage 24 bit mode 13. Macros and conditional assembly 14. MVS system Macros 15. VSAM Macros 16. Linkage Conventions, 24 & 31 bit addressing, mixed mode addressing

issues17. Mixed Mode Programming using COBOL and Assembler .

Page 3: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 3 / 116

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

Advantages over high-level language

⇒ Very efficient and tight code can be developed

Disadvantages

⇒ Applications development time is more⇒ Applications are machine dependent⇒ Relatively more difficult to learn and understand than a high level Language

Advantages over machine language

⇒ Use of mnemonic operation codes helps remembering the instructions⇒ Symbols can be used to represent variables and constants⇒ Macros can be used to generate repeated codes⇒ Conditional assembly enables tailoring the code generated

Page 4: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 4 / 116

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 categories

⇒ Fixed point Arithmetic, ⇒ Decimal Arithmetic,⇒ Floating point Arithmetic,⇒ Logical Operations,⇒ Branching,⇒ Status Switching,⇒ Input Output

• Programmer accessible Hardware Registers are⇒ Program Status Word (PSW) 64 bits wide⇒ General Purpose Registers (GPRs) ⇒ Floating Point Registers (FPRs) ⇒ Control Registers (CRs) 0-15 each 32 bits wide⇒ Access Registers (AR'S) 0-15 each 32 bits wide

• PSW ⇒ 64 bits in length ⇒ Contains the Condition Code (two bits) ⇒ Address of the next instruction to be executed.⇒ PSW Key field

• GPR'S ⇒ numbered 0-15 and 32 bits wide ⇒ Used as accumulators in Fixed point arithmetic⇒ Used as base and index registers in computing the effective address ⇒ Two consecutive registers can be used to hold 64bit operands addressed by even register

• AR'S⇒ Numbered 0-15 each 32 bits wide⇒ Used to point to address / data space

• FPR⇒ Used for floating point operations⇒ Numbered 0,2,4,6 each 64 bits wide⇒ 64 bits in length⇒ Can contain short or long operand⇒ Two adjacent registers can be used as 128 bit register for extended precision

• CR'S⇒ Control registers each of 32 bits are available⇒ Used by the IBM control program⇒ Instructions to access / modify them are privileged and can be issued only by the OS.• INPUT/OUTPUT⇒ Data processing and I/O processing are concurrent⇒ Consists of Channel subsystem, Control Unit and I/O unit

Page 5: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 5 / 116

ASSEMBLY STATEMENT FORMAT

1 10 16 72

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

continue the next line from column 16• Comment lines start with character ('*') on column 1

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

NAME FIELD OPERATION FIELD OPERAND FIELDREMARKS

*SEQUENCE

Page 6: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 6 / 116

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

Page 7: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 7 / 116

INSTRUCTIONS back

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

Example :PRINT NOGENTEST1 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 InstructionPUTMSG 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 InstructionDATA1 DS CL100 Data DefinitionDATA2 DS CL100 Data DefinitionSAVE 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,2immediate operand

Example MVI DATA,X'F1'Storage operand

Example L 3,FIELD1Implied 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

Page 8: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 8 / 116

IMMEDIATE OPERAND• Contained with in the instruction itself• Eight bit value• Self defining term or an absolute symbol can be used• Example : MVI DATA,B'10000000'

STORAGE OPERAND• Resides in memory• Address is not specified explicitly• Base and 12 bit offset with (in some instructions) index register is used• Program can be relocated• If Register 0 is used as a base or index register its contents are ignored• 12 bit displacement • BALR instruction is used to load base register• If symbols are used assembler resolves it to base displacement form• Effective address = (base register) + (Index Register) + 12 bit displacement (note that some instruction formats do not support index register)• base register should be made to contain the base address at run time• Size of storage operand is implied by the instruction for some instructions • For some instructions Length field(s) is/are embedded in the instruction • Storage operands can be specified in implicit form as a re-locatable expression

Example L 3,DATAL 3,DATA+4

• Storage operands can be specified in the Explicit formExample 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,DATAL 3,DATA+4LA 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 9: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 9 / 116

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

BXLE 1,2,D2(B2) (reg 1) <== (reg 1) + (reg 2)If reg1>reg3 then branch

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

S type instructionLPSW D2(B2)

SI type instruction

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 10: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 10 / 116

NI D1(B1),I2SS type instruction

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

Note that (Rn) denotes the contents of GPR n. It is known as Register Notation and is commonly used to supply values for a Macro operand.

Page 11: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 11 / 116

SYMBOLS, LITERALS, DATA AREAS, LOCATION COUNTER back

SYMBOLS• A sequence of one to eight characters as specified below under ORDINARY,VARIABLE,SEQUENCE symbols• Absolute value assigned to a symbol by using 'EQU' assembler instruction with an absolute value operand• A re-locatable value is assigned to a symbol by using it in the name field of a machine instruction• Symbols can be used in operand fields to represent registers, displacements, lengths, immediate data, addresses etc.

Example :LABEL001 MVC S1,S2

B QUITQUIT BR 14S1 DS CL100S2 DC CL100'THE QUICK BROWN FOX'COUNT EQU 10

LABEL001, QUIT, S1, S2 and COUNT are all Symbols. All are re-locatable except COUNT which is absolute.

Ordinary Symbols• Optional• used in the name and operand field of machine/assembler instructions• Up to eight Alphanumeric characters A-Z,$,#,&,0-9• First character must be alphabetic A-Z• Rest can be alphanumeric

Example ABCD0001

Variable Symbols• First character must be an ampersand• second character must be alphabetic• Up to six alphanumeric characters

Example &ABC0001

Sequence Symbols• First Character must be a period• Next Character must be alphabetic• Up to six alphanumeric characters

Example .ABC0001

Advantages of symbols• Easier to remember and use• Meaningful symbol names instead of values• For address the assembler calculates the displacement• Change the value at one place (through an EQU) instead of several instructions• Printed in the cross-reference table by the assembler

Symbol Length attributeTO DS CL80 L'TO = 80FROM DS CL240 L'FROM = 240ADCON DC A(OTHER) L'ADCON = 4CHAR DC C'YUKON' L'CHAR = 5DUPL DC 3F'200' L'DUPL = 4

Page 12: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 12 / 116

Self Defining terms• Can be used to designate registers, masks, and displacements within the operand entry

Decimal self-defining term

• An unsigned decimal integer• maximum number of digits 10• Maximum value 2**31-1

Hexadecimal self-defining• A Hexadecimal integer within apostrophes and preceded by a X• Maximum number of digits 8• Maximum value 2**31-1

Binary Self Defining Term• sequence of 1s and 0s enclosed in single quotation marks and preceded by the letter B; for

example, B'11000101' Character self-defining term

• A character string within apostrophes and preceded by a C• Maximum number of characters 4

EXAMPLES:15 UPTO 2,147,483,647241B'1101' UPTO 32 BITSX'F' UPTO 8 HEX DIGITSX'F1F2'C'ABCD' UPTO 4 CHARACTERSC'&&' TWO AMPERSANDS TO REPRESENT ONEC'''''' TWO APOSTROPHES TO REPRESENT ONE

LiteralsL 1,=F'200'L 2,=A(SUBRTN)MVC MESSAGE(20),=CL20'THIS IS A MESSAGE'L 3,=F'33' BOTH ARE SAMEL 3,FIELD BOTH ARE SAME

FIELD DC F'33'MVC FLAG,=X'00' SAME EFFECTMVI FLAG,X'00' SAME EFFECTMVI FLAG,ZERO SAME EFFECT..

ZERO EQU X'00'FLAG DS C

LA 4,LOCORE SAME EFFECTLA 4,1000 SAME EFFECT.

LOCORE EQU 1000

Absolute expressions An expression is absolute if it's value is unchanged by program relocationFIRST CSECTA DC F'2'B DC F'3'C DC F'4'ABSA EQU 100

Page 13: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 13 / 116

ABSB EQU X'FF'ABSC EQU B-AABSD EQU *-A

All these are absolute expressions:-ABSA15L'AABSA+ABSC-ABSC*15B-AABSA+15-B+C-ABSD/(C-A+ABSA)

Relocatable expressionsA relocatable expression is one whose value changes with program relocation.

FIRST CSECTA DC H'2'B DC H'3'C DC H'4'ABSA EQU 10ABSB EQU *-AABSC EQU 10*(B-A)

The following are relocatable expressions:-AA+ABSA+10B-A+C-10*ABSA

Location Counter• Location counter is incremented after instruction or data definition is assembled to the next available location• Assembler checks boundary alignment and adjusts location counter if required.• While assembling the current line the location counter value does not change

Location counter Source Statements000004 DONE DC CL3'SOB'000007 BEFORE EQU *000008 DURING DC F'200'00000C AFTER EQU *000010 NEXT DS D000018 AFTNEXT EQU *000018 NEXT1 DS D000020 NEXT2 DS D000028 ORG *+8000030 NEXT3 DS D

Example :LOOP EQU *

B *+80...B LOOP

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

Page 14: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 14 / 116

• For a symbol referring to a machine instruction, it is the length of the instruction.• For a 'EQU' symbol, it is the length of the left most term or supplied by the second operand

Example : lengthA DS F 4 DS 20FL4 4 DS XL3 3

AR 1,2 2AA EQU A+4 4S1 EQU 102 1BUF EQU A,256 256

Type attribute• Referred to as 'T' symbol• Gives the one character type code of the symbol

A,Y,V,S For the related Address ConstantsB,C,D,E,F,H,Z,P For the related data constantsI For machine instructionM For a Macro instructionJ For a control section nameT For a EXTRN symbol$ For a WXTRN symbolN For a self defining termO Null string

CONSTANTS AND DATA AREAS• Run Time Constants DC directive

LiteralsSelf 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{NAME} DC {DUP}TYPE{MOD}{V1,V2,...VN} Run time constant

TYPE BYTES ALLOCDC F'100,-10,200' 12DC F'123' 4DC F'-123' 4DC 3F'23' 12DC H'20' 2DC H'123,23,-34' 6

DUPLICATING FACTOR TYPE LENGTH MODIFIER CONSTANT

Page 15: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 15 / 116

DC B'11000001' 1DC X'FFFFFFFF' 4DC X'FF01FF01' 4DC C'ABCDEF' 6DC C'abcdefg''A&&SS@#..' 16 , note double & and 'DC P'-1234' 3DC P'1234' 3DC P'-34' 2DC Z'1234' 4DC E'-3.25E10' 4DC E'+.234E-10' 4DC E'-2.3E15' 4DC A(LOOP1) 4DC V(LOOP1) 4DC S(FIELD2) 2DC 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

DC Y(124) 2

DEFINE STORAGE (DS)• To reserve storage• Storage is not initialised• Location counter is advanced by bytes allocated

DS

SYNTAX{NAME} DS {DUP}TYPE{MOD}

EXAMPLES

DS F Bytes allocated 4DS 10F 40DS H 2DS 2CL3 6

A DS 80C 80 L'A=1DS CL80 80 L'A=80DS 4D 32DS 0F 0 used to force a word BoundaryDS 0D 0 used to force a double word boundaryDS 0CL8 0 length attribute is 8DS 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

DUPLICATING FACTOR TYPE LENGTH MODIFIER

Page 16: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 16 / 116

• A hexadecimal integerX'4A'• A sequence of text characters C'ABCD'• These can be used as immediate operands in any instruction which needs an immediate

operand.

Example CLI 0(8),C'Z'

A literal is a symbolic representation of a constant to which the assembler assigns an address

L 5,FCONL 5,=F'1'

LOAD L 2,=F'-4'MOVE MVC MSG,=C***Error ***'FCON DC F'1'

The first two statements are exactly equivalent to the third.• A convenient means of introducing constants without the use of 'DC' instruction• Storage is allocated for literals at the end of the first CSECT (Literal Pool) where multiple

CSECTS are coded in a single source file.To avoid addressing problems, use a LTORG at end of each CSECT

• Storage allocation can be forced at any point by 'LTORG" assembler instruction• Two literals are the same if their specifications are identical• Assembler translates a literal into a base register and a displacement

A equivalence constant allows a programmer to define a value for a symbol and use it wherever there is a need to employ that value.

R1 EQU 1HERE EQU *OFF EQU X'00'ON EQU X'FF'Y DC F'4'Z EQU 4W EQU Y W is equivalent to Y

CLI STATUS,ONBE POWERONCLI STATUS,OFFBE POWEROFF

Data Alignment• Instructions have to be aligned on half-word boundary• Data can be specified to be aligned to Double word D (Divisible by 8) Full-word F (Divisible by 4) Half-word H (Divisible by 2)• Location counter skipped as per alignment requirement

Example :000100 DC C'ABC'000103 skipped000104 DC F'4'000108 DC C'A'000109 skipped000110 skipped000111 skipped000112 DC F'560'

Instruction Alignment

Page 17: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 17 / 116

Instructions are always aligned on a half word boundary. Some times it may be required to align instructions on a Full word or double word boundary. Use the CNOP instruction to do so. For example to get full word alignment use CNOP 0,4 as below. The BAL instruction will always be aligned on a Full word boundary. Assembler will introduce, if required, a NOP ( X’0700’ ) instruction to ensure this.

CNOP 0,4BAL 1,*+12

PARM DC A(P1)DC A(P2)BALR 14,15

IF ASSEMBLER OPTION ALIGN IS SPECIFIED• Assembler checks storage addresses (labels) to ensure that they are aligned on boundaries required

by the instruction.• Data areas are aligned on boundaries implicit with their type if no length modifier is present

LOC-CTR PROGRAM000010 DATA DC C'ABC'000014 DS F ASSM. AT WORD BDRY

IF NOALIGN IS SPECIFIED• Constants and data areas are not automatically aligned• Assembler does not check storage addresses for boundary alignment.

LOC-CTR PROGRAM000010 DATA DC C'ABC'000013 DS F ASSM. AT NEXT LOC

ExampleThis example illustrates the use of literals and commonly used data definitions.TEST2 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE WTO 'ASM1 REPORTING',ROUTCDE=(11) L 3,=F'200' LA 3,ABSB MVC DATA1(6),=C'ABCDEF' MVC DATA1,=CL20'ABCDEF'

L 13,SAVE+4 LM 14,12,12(13) SR 15,15 BR 14 SAVE DS 18F DC A(SAVE1) A DC H'2' B DC H'3' C DC H'4' ABSA EQU 10 ABSB EQU *-A DC F'100' DC F'-100' DC H'100' DC 3H'100' DC C'ABCEFGH'

Page 18: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 18 / 116

DC CL20'ABCDEFGH' DC 10C'AB' DC P'123' DC P'-123' DC PL5'-123' DC 3PL5'-123' DATA1 DS CL20 END

Page 19: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 19 / 116

INTEGER OPERATIONS back

FIXED POINT ARITHMETICADD AR,A,AH,ALR,ALSUBTRACT SR,S,SH,SLR,SLMULTIPLY MR,M,MHDIVIDE DR,DARITHMETIC COMPARE CR,C,CHLOAD LR,L,LH,LTR,LCR,LPRSTORE ST,STH,STMARITHMETIC SHIFT SLA,SRA,SLDA,SRDACONVERT TO BINARY CVBCONVERT TO DECIMAL CVD

Constants used TypeFixed Point H and FBinary BHexadecimal XCharacter CDecimal PAddress Y,A,S,V,Q

Page 20: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 20 / 116

INTEGER ARITHMETIC

• GPR's are 32 bits with bit 0 as a sign bit• Negative numbers stored as two's complement• Both Full word and Half Word instructions are supported• GPR/GPR and GPR/Memory instructions available• Half words converted to full word by extending sign bit to the left

Two's ComplementDecimal Binary Decimal Binary0 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 00B0After 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 0DEF0123 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 4321After 0000 4321 4321

Before 0000 4321 C321After FFFF C321 C321

STH Copy a half word from GPR to memory RX R1,D2(X2,B2)STH 3,A GPR3 Memory field A

Before 0123 0456 0DEFAfter 0123 0456 0456

Page 21: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 21 / 116

LM Copies 1 to 16 Full words from memory RS R1,R3,D2(B2)to consecutive GPR,sLM 2,4,A GPR'S Memory Address

Before 2:00001234 A+0:0001ABCD3:00003456 A+4:0002BCDE4:00005678 A+8:0003CDEF

After 2:0001ABCD A+0:0001ABCD3:0002BCDE A+4:0002BCDE4:0003CDEF A+8:0003CDEF

STM Copies 1 to 16 Full words to memory RS R1,R3,D2(B2)From consecutive GPR,sSTM 2,4,A GPR'S Memory Address

Before 2:00001234 A+0:0001ABCD3:00003456 A+4:0002BCDE4:00005678 A+8:0003CDEF

After 2:00001234 A+0:000012343:00003456 A+4:000034564:00005678 A+8:00005678

LR Copies one GPR to another RR R1,R2LR 3,4 GPR3 GPR4

Before ABCD EF00 1234 5678After 1234 5678 1234 5678

ADDITIONA 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 000AAfter 0000 004A 0000 000A

S Subtracts a memory field from GPR RX R1,D2(X2,B2)Example 64-10=54S 3,=F'10' GPR3 Memory

Before 0000 0040 0000 000AAfter 0000 0036 0000 000A

AR Adds a GPR to another GPR RR R1,R2Example 4096+(-1)=4095AR 6,5 GPR6 GPR5

Before 0000 1000 FFFF FFFFAfter 0000 0FFF FFFF FFFF

SR Subtracts a GPR from another GPR RR R1,R2Example 4096-(-1)=4097SR 6,5 GPR6 GPR5

Before 0000 1000 FFFF FFFFAfter 0000 1001 FFFF FFFF

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

Page 22: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 22 / 116

Before 0000 0050 0008After 0000 0058 0008

Example 80+(-8)=72AH 10,=H'8' GPR10 Memory

Before 0000 0050 FFF8After 0000 0048 FFF8

SH Subtracts a half word memory field from RX R1,D2(X2,B2) a GPRExample 8-80=-72SH 10,=H'80' GPR10 Memory

Before 0000 0008 0050After 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 = 6L 7,=F'2'M 6,=F'3'

GPR6 GPR7 MemoryBefore any number 0000 0002 0003After 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 GPR4Before 0000 0000 0001 0000 0001 0000After 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 MemoryBefore 0000 0002 0005After 0000 000A 0005

Any number V1

64 bit product V1 X V2

Page 23: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 23 / 116

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)FieldExample 7 / 2 = quotient =3, remainder=1L 9,=F'7'M 8,=F’1'D 8,=F'2'

GPR8 GPR9 MemoryBefore 0000 0000 0000 0007 0002After 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'M 8,=F'1'L 10,=F'-40'DR 8,10

GPR8 GPR9 GPR10Before 0000 0000 0000 0096 FFFF FFD4After 0000 001E FFFF FFFD FFFF FFD4

rem +30 Quot -3 Divisor -40

The condition code is NOT set by the MULTIPLY and DIVIDE instructions.To test the result use the LTR instruction.

ARITHMETIC COMPAREC Compare GPR with memory field RX R1,D2(X2,B2)CR Compare a GPR with another RR R1,R2CH 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,R2Example

LCR 3,3 GPR3Before FFFFFFFAAfter 00000006

LCR 3,4 GPR3 GPR4Before 87654321 80000000After 80000000 80000000

**ovfl set

LPR Load positive register RR R1,R2Example

LPR 5,4 GPR5 GPR4

32 BIT REMAINDER 32 BIT QUOTIENT

64 BIT DIVIDEND V1

Page 24: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 24 / 116

Before 000000AB FFFFFFFAAfter 00000006 FFFFFFFA

LPR 4,5 GPR4 GPR5Before FFFFFFFA 000000ABAfter 0000000AB 000000AB

LPR 8,7 GPR8 GPR7Before 12345678 80000000After 80000000 80000000

***ovflw

LNR Load negative register RR R1,R2Example

LNR 4,5 GPR4 GPR5Before FFFFFFFA 000000ABAfter FFFFFF55 000000AB

LPR 4,5 GPR4 GPR5Before 00000011 FFFFFF55After 000000AB FFFFFF55

Condition code is set( zero, positive , negative, overflow)

SPM Set Program MaskSPM R1 The first operand is used to set the condition code and the program maskof the current PSW. Bits 12-15 of the instruction are ignored. Bits 2 and 3 of general register R1 replace the condition code, and bits 4-7 replace the program mask. Bits 0, 1, and 8-31 of general register R1 are ignored.

SR 4,4L 4,=X’0F000000’SPM 4 turn on all 4 program mask bits

IPM Insert Program MaskIPM R1The condition code and program mask from the current PSW are inserted into bit positions 2-3 and 4-7, respectively, of general register R1. Bits 0 and 1 of the register are set to zeros; bits 8-31 are left unchanged.

Note that unless the Program Mask bits in the PSW are 1 some interrupts are suppressed. See the PSW fields for details.

Page 25: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 25 / 116

DECIMAL OPERATIONS back

ADD APSUBTRACT SPMULTIPLY MPDIVIDE DPDECIMAL COMPARE CPMOVE DECIMAL DATA WITH 4 BIT OFFSET MVOSHIFT DECIMAL DATA SRPSET TO ZERO AND ADD ZAPCONVERT ZONED TO PACKED PACKCONVERT PACKED TO ZONED UNPK

Constants used TypeDecimal PZoned Z

BCD Representation (Packed Decimal)

0011 0010 0101 1100 +325 X’325C’0111 1000 1001 1101 -789 X’789D’

AREA1 DS PL5AREA2 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 SS2Example

ZAP A(3),B(4) A BBefore Dont Care 0023456CAfter 23456C 0023456C

AP Add packed SS2Example

AP A(2),B(3) A BBefore 099C 00001CAfter 100C 00001C

Before 999C 00001CAfter 000C 00001D

(ovfl cond)SP Subtract packed SS2Example

SP A(2),B(3) A BBefore 099D 00001CAfter 100D 00001C

Page 26: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 26 / 116

Before 999C 00001DAfter 000C 00001D

(ovfl cond)

Before 123C 00010CAfter 113C 00010C

MP Multiply packed SS2Length of L2 must be between 1 and 8 and less than L1.L1 must have at least L2 bytes of high order zeroes

ExampleMP A(4),B(2) A B

Before 0000999C 999DAfter 0998001D 999D

MP A(3),B(2) Before 00999C 999DAfter 98001D 999D

**ovflw**

MP A(2),B(2) Before 012C 012CAfter 012C 012C

**error**

DP Divide Packed SS2DP D1(L1,B1),D2(L2,B2) L1 (Dividend) and L2(divisor)L2 < L11<=L2<=8The quotient and remainder is stored in the L1(dividend field) replacing the dividend

Example A BDP A(4),B(2) Before 0000999C 998D

After 001D001C 998D |

DP A(4),B(2) Before 0000999C 3CAfter 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 00003CAfter 999C 00003C **specification exception*****L1-L2=-1(impossible length for quotient)

QUOTIENT REMAINDER

L1-L2 BYTES L2 BYTES

DIVIDEND FIELD

Page 27: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 27 / 116

ERRORS• Decimal overflow occurs when result is too long to fit into first operand and a significant digit would

be lost• Data exception occurs whenever

⇒ Sign fields are invalid⇒ Operands overlap ⇒ The first operand of a MP instruction does not have sufficient zeroes.

COMPARISONSCP Compare packed SS2 D1(L1,B1),D2(L2,B2)

BE V1=V2BH V1>V2BL V1<V2

SRP Shift and Round Packed D1(L1,B1),D2(B2),I3 SS1

The first operand represents an addressThe second operands low order 6 bits is the number of positions to be shifted and direction of shift. Positive represents left shift and vacated positions on the left are filled with zeroes. Negative represents a right shift and zeroes are inserted on the left. The sign is not disturbed in any case. The third operand is the rounding to be applied in case of right shift and is an immediate operand.

L 8,=F’-3’ for shift right 3 positionsSRP A(5),0(8),5 before 031415926C

after 000031416C

CONVERSION BETWEEN EBCDIC, BINARY AND PACKED DECIMAL FORMATCVD converts binary to packed decimal

32 bit binary to a 8 byte packed decimal fieldExample

CVD 5,A REG5 ABefore 7F FF FF FF any numberafter 7F FF FF FF 00 00 02 14 74 83 64 7C

CVD 5,A REG5 ABefore 80 00 00 00 dont care

after 80 00 00 00 00 00 02 14 74 83 64 8D

CVB converts packed decimal to binary8 byte packed decimal field to a 32 bit binary field

ExampleCVB 5,A REG5 A

Before dont care 00 00 00 00 00 00 01 6Cafter 00 00 00 10 00 00 00 00 00 00 01 6C

CVB 5,A REG5 ABefore dont care 00 00 00 00 00 00 01 6Dafter 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 fieldOperand two is the EBCDIC field in zoned decimal format

ExamplePACK A(4),B(4) A B

Before any F1 F2 F3 C4after 00 01 23 4C F1 F2 F3 C4

Page 28: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 28 / 116

UNPK converts packed decimal to EBCDIC D1(L1,B1),D2(L2,B2)Operand two is the packed decimal fieldOperand one will receive the EBCDIC field

ExampleUNPK A(8),B(4) A B

Before any 12 34 56 7DAfter F0 F1 F2 F3 F4 F5 F6 D7 12 34 56 7D

ED Converting a packed decimal numberto EBCDIC with editing D1(L,B1),D2(B2) V1 is pattern, V2 is

packed fldED P(15),Y Before Y 0 0 1 2 3 4 5 6 7 D

Before P 40 20 6B 20 20 20 6B 20 21 20 4B 20 20 60 40 After P 40 40 40 40 F1 F2 6B F3 F4 F5 4B F6 F7 60 40

1st byte of pattern is the fill character, in this case a blankHex 20 is a digit selectorHex 21 is a significance starterHex 6B is a ‘,’Hex 4B is a ‘.’

Every byte of packed decimal needs two bytes of EBCDIC code

00 12 3C ----------------- F0 F0 F1 F2 C3

EDMK Does everything ED does. In addition it sets register 1 to the address of the first significant digit. You can then bump Register 1 down by 1 and move immediate a currency symbol to that storage location represented by the address in 1. Note that you initially set 1 to the first digit position that is forced to print if no significant digits occur to the left.

MVC P,MASKLA 1,MASK+9EDMK P,YBCTR 1,0MVI 0(1),C’$’..

Y DC PL5’-1234567’P DS CL15MASK DC X’40206B2020206B2021204B20206040’

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

Page 29: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 29 / 116

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' B DC PL2'-998' END

Example of displaying a IntegerTEST4 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 30: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 30 / 116

DATA TRANSFER AND LOGICAL OPERATIONS backMOVE MVI,MVC,MVZ,MVCLLOGICAL COMPARE CLR,CL,CLC,CLCL,CLMAND LOGICAL NR,N,NI,NCOR LOGICAL OR,O,OI,OCEXCLUSIVE OR XR,X,XI,XCTESTING BINARY PATTERNS TMINSERTING CHARS INTO GPR IC,ICMSTORE CHARS INTO AREAS STC,STCMLOAD ADDRESS INTO GPR LALOGICAL SHIFT OF GPR SLL,SRL,SLDL,SRDLDATA TRANSLATION TR,TRT

BYTE AND STRING MANIPULATIONSIC 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,mask,D2(B2)

MVI Move Immediate SI Copies 1 byte from immediatefield 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)

CLR Compare Logical Register RR Compares 4 bytes from two GPR’SR1,R2

Page 31: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 31 / 116

CLM Compare Logical under mask RS Compares 1 to 4 bytes (determined by mask) from a GPR to a memory field

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.

BRANCHINGCC 0 CC 1 CC 2 CC3

CL,CLC,CLCL,CLI,CLM,CLR OPR1=OPR2 OPR1<OPR2 OPR1>OPR2 NA.

Opcode MeaningBE OPR1=OPR2BNE OPR1!=OPR2BL OPR1<OPR2BNL OPR1=>OPR2BH OPR1>OPR2BNH OPR1<=OPR2

Notes:Destructive overlap occurs when a to field starts from within a from field

How to modify length field at run timeEX 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.

LH 4,=H’20’ SH 4,=H’1’ EX 4,MOVEV | |MOVEV MVC TO(0),FROM | |FROM DS 10FTO DS 10F

CLCL and MVCL instructions

CLCL R1,R2 MVCL R1,R2

R1 bits 8 to 31 is the TO addressR1+1 bits 8 to 31 is the length of TO fieldR2 bits 8 to 31 is the FROM addressR2+1 bits 8 to 31 is the length of FROM fieldbits 0 to 7 is the padding character to be used to lengthen the shorter string

Page 32: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 32 / 116

LA 4,S L 5,=A(L’S) LA 2,T L 3,=A(L’T) ICM 5,B’1000’,=X’00’ MVCL 2,4 | | |S DS CL1000T 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 CL256ORG FN1+C’+’DC X’FF’ORG

ARG1 DS CL256|TRT ARG1(256),FN1BC 8,NONEBC 4,MOREBC 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.

Example of TRThis sample translates a lower case string to upper case, leaving numeric digits intact. All other characters are converted to NULL.TR CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE TR DATA,TABLE WTO TEXT=MSG L 13,SAVE+4

Page 33: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 33 / 116

LM 14,12,12(13) SR 15,15 BR 14 SAVE DS 18F MSG DC AL2(LEN) DATA DC C'abcdefghijklmnopqrstuvwxyz1234567890' LEN EQU *-DATA TABLE DC 256X'00' ORG TABLE+C'a' DC C'ABCDEFGHI' ORG TABLE+C'j' DC C'JKLMNOPQR' ORG TABLE+C's' DC C'STUVWXYZ' ORG TABLE+C’0’ DC C’0123456789’ ORG END

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

Page 34: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 34 / 116

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

Page 35: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 35 / 116

BIT MANIPULATIONS back

SRA Shift Right Single Arithmetic RSSLA Shift Left Single Arithmetic RSSRDA 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 RSSLL Shift Left Single Logical RSSRDL 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 RXN And RXX Exclusive Or RXOR Or GPR’S RRNR And GPR’S RRXR XOR GPR’S RROI Or Immediate SINI And Immediate SIXI Exclusive Or Immediate SIOC Or Memory fields SSNC And Memory Fields SSXC Exclusive Or Mem Flds SS

TESTING BITSTM 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 36: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 36 / 116

BRANCHING INSTRUCTIONS backBRANCH ON CONDITION CODE BCR,BCBRANCH AND LINK BALR,BALBRANCH ON COUNT BCTR,BCTBRANCH ON INDEX COMPARE BXH,BXLETEMPORARY 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,BNZRBM,BMR,BNM,BNMR,BP,BPR,BNP,BNPRBO,BOR,BNO,BNOR,NOP,NOPR,B,BR All implemented using BC instruction

BRANCHING AND LOOPSBCT Branch on count RX R1,D2(X2,B2)

• Subtract 1 from R1 and test for non zero.• Branch if non zero

BXH Branch on Index High RS R1,R2,D3(B3)• Increments or decrements Index• Counting iterations• Test to determine whether loop should be repeated• BHX is normally used with decrementing• BXLE is used with incrementing• R1 is the Index register• R2 contains the increment / R2+1 contains the limit• S3 is the branch address•

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

Page 37: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 37 / 116

ASSEMBLER DIRECTIVES back

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 CL3FIELD2 DS CL10FIELD3 DS CL10FIELD4 DS CL10FIELD5 DS FCITY 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 addressUSING *,12 Reg 12 is a base registerUSING 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 storageExample:BUFFER DS 100F

ORG BUFFER A DS CL80

Page 38: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 38 / 116

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,0USING *,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, ENTRYThis example illustrates how a data item can be externalised and the address of the data item caught in another program. The second program can then manipulate the data in the data item.

TEST5 CSECT ENTRY 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

Page 39: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 39 / 116

SUB4 CSECT 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. However, in the course of resolving strong external references, if an ENTRY of SAVE1 is found then it is resolved in this module.

ExampleThis example illustrates how you must test whether a WXTRN has been resolved before you use the reference.WXT CSECT

WXTRN WXDATA STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE L 4,AWXDATA LTR 4,4 BZ NOTRESRES . . USE ADDRESS .NOTRES . NOT RESOLVED . L 13,SAVE+4 LM 14,12,12(13) SR 15,15 BR 14 SAVE DS 18FAWXDATA DC A(WXDATA) END

COM

Page 40: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 40 / 116

• Defines a common section. All common sections across CSECTS with the same name map to the same storage. The storage for COMMON sections is allocated at the time the load module is built.

ExampleThis example illustrates how a COM area may be defined and shared across CSECTS.COM CSECT COM AMODE 31 COM RMODE ANY STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE L 15,ASUB BALR 14,15 ICM 4,B'1111',ACOM WTO TEXT=(4) L 13,SAVE+4 LM 14,12,12(13) LA 15,0 BR 14 SAVE DS 18F ASUB DC V(SUB) ACOM DC A(COMMON) COMMON COM MSG DS AL2 DS CL100 END

SUB CSECT SUB AMODE 31 SUB RMODE ANY STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 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

Page 41: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 41 / 116

JCL ASPECTS back

program consists of Machine instructionsAssembler instructionsMacro Instructions.

Development cycle CodingPre AssemblyAssemblyLinkage EditProgram fetch

JCL:- The ASMACL procedure that assembles and links a assembler program can be used. It is usually found in SYS1.PROCLIB.

Look at this JCL on your system and understand the JCL.

If the C step is the compilation step and the L step is the Link edit step, the following DDNAMES refer to the data sets mentioned against each:-

C.SYSIN points to the sourceC.SYSLIB points to the Macro and Copy book librariesC.SYSPRINT is the compilation listing.L.SYSLIB points to an Object code Library which may contain subprograms in Object formL.SYSLMOD points to the target Load library.L.SYSPRINT is the linkage editor listing.The C.SYSUT1 and L.SYSUT1 datasets are work files.

SOURCE

ASSEMBLER

MACLIBSCOPY BOOKS

OBJECT DECKOBJECT LIBRARIES

LINKER

LOAD MODULE

LOAD IN MAIN STORAGE FOR EXECUTION

Page 42: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 42 / 116

Some of the Important linkage editor options are given belowLET allows you to specify severity level of an error to determine whether the load module is to be marked as unusable.

MAP | NOMAP Use map if you want a generated map of the load module

NCAL Do not make an automatic search of the object libraries when linking. Make sure you remove it

RENT Indicates module is re-entrant, NORENT marks it as non re-entrant

AMODE 24|31|ANY . Use this parameter to override the attribute established by the assembler in the assembly process

RMODE 24|ANY overrides this attribute as set by the assembly process

AssemblerOBJECT and LIST are the usual compilation options.

ALIGN instructs assembler to check for alignment where it is requireddefault ALIGN

DECK Assembler generates object deck on SYSPUNCHdefault NODECK

ESD The External symbol dictionary is produced in the listingdefault ESD

OBJECT instructs the assembler to generate an object data set on SYSLINdefault OBJECT

RENT instructs the assembler to check for possible violations of re-entrant default NORENT

RLD the assembler outputs the relocation dictionary in the listing default RLD

SYSPARM SYSPARM ( parmvalue………) max 255 chars

XREF(FULL) Ordinary symbol and literal cross reference listing produced including symbols that are not referred to .

XREF(SHORT) Omits symbols not referred to. Default XREF(SHORT,UNREFS)

Special Considerations when the member name and the CSECT name do not match. Source File-1TEST6 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE WTO 'IN ASM3 BEFORE CALL TO SUB1',ROUTCDE=(11) L 15,ASUB1 BALR 14,15 WTO 'IN ASM3 AFTER CALL TO SUB1',ROUTCDE=(11) L 13,SAVE+4

Page 43: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 43 / 116

LM 14,12,12(13) SR 15,15 BR 14 SAVE DS 18F ASUB1 DC V(SUB1) Does not pose problemsASUB2 DC V(SUB2) Does pose a problem END

Source File-2, compiled and stored as SUB1 in the Object Library. It contains both SUB1 as well as SUB2 CSECT.SUB1 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE WTO 'IN SUB 1',ROUTCDE=(11) DC F'0' L 13,SAVE+4 LM 14,12,12(13) SR 15,15 BR 14 SAVE DS 18F ** NEW CSECT* SUB2 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE1+4 LA 13,SAVE1 WTO 'IN SUB 2',ROUTCDE=(11) L 13,SAVE1+4 LM 14,12,12(13) SR 15,15 BR 14 SAVE1 DS 18F ** note that duplicate labels are not permitted in the same * source file*

END

If you are calling SUB2 , the linkage editor cannot resolve the external reference unless you make the editor explicitly include module with the control statement below:-

//LKED.SYSIN DD *INCLUDE SYSLIB(SUB1)

/*

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

Page 44: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 44 / 116

ALIAS directory-name[(external symbol)]

Example//LKED.SYSIN DD * ALIAS SUB2/*

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

MODE AMODE(31),RMODE(ANY)

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

LIBRARY TESTLIB(DATE,TIME)

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

NAME MYMOD(R)

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

SETSSI 00000001

In addition to AMODE, RMODE and SSI which are stored in the directory entry for the load module the following attributes can be set through the Linkage Editor PARM field:-

REUS The program is serially reusable. The system queues requests to use the module (via LINK, XCTL, ATTACH) if it is in use

RENT The program is re-entrant. It means that more than one task can concurrently use the program.

REFR The program is refreshable (it can be refreshed by a new copy from the PDS anytime , even while it is executing.

If none of these are specified, it means that the program must be fetched afresh from the load library every time it is required.

REFR implies RENT and REUS as well. RENT implies REUS as well.

Note that using the program via BALR instruction can defeat the purpose of these attributes.

Page 45: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 45 / 116

SUBROUTINES AND LINKAGES 24 BIT MODE backSUBROUTINE• 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 subroutineBALR 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 thefirst 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 subroutineBR R1 Branch register

PC <--(R1)Branch unconditionally to the address specified in the operand 1Example: MAIN START 0 . . BAL 14,SUB1 . L 15,SUB2 BALR 14,15* RETURN. . *SUB1 DS OH

BR 14SUB2 DC V(SUBROUT2)

END

Saving and restoring environmentPrograms uses registers as base registers, index registers, and accumulators. If a program calls a subprogram, when the control returns, these register values should not be altered. To achieve this, the calling program provides a SAVEAREA into which the called program saves the registers. Before the control is returned from the subprogram, the registers are restored to their original values. Some subprograms return to the called program a return code (set in GPR15) and a reason code. It is a good programming practice to save and restore the environment. If this is done any subroutine can be used by any program with out the need to identify which registers are modified by the subroutine.

Page 46: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 46 / 116

Convention for saving registers• Every calling routine has a save area of 18 full-words for the use of called routine• The calling routine passes the save area address in register 13• Every called routine saves the registers in this area before establishing addressability • Address of called routine is in register 15• Register 14 has the return address

SAVEAREA (18 Full words) layoutSavearea+0 Reserved for PL/1

Savearea+4 Address of save-area of program which called this sub-programSavearea+8 Address of save-area of another program called by this programSavearea+12 This programs Register 14 contents saved by called program savearea+16 This programs Register 15 contents saved by called programsavearea+20 This programs Register 0 contents saved by called program. .. .. .Savearea+64 This programs Register 11 contents saved by called programSavearea+68 This programs Register 12 contents saved by called program

ExampleMAIN 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 14SAVE 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. An array is created containing the addresses of the parameters in the order they are expected in the called program. Register 1 is loaded with the starting address of this address array. The last address in the array should have bit ' 0' set to ' 1'

• For variable number of parameters, the high order bit of the last parameter is set to one to indicate the end of parameter list

Page 47: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 47 / 116

ExampleThis example illustrates how three parameters P1,P2 and P3 may be passed by reference. . LA 2,P1 ST 2,PARM LA 2,P2 ST 2,PARM+4 LA 3,P3 ST 3,PARM+8 LA 1,PARM L 15,=V(PROC1) BALR 14,15 . . LA 1,=A(P2,P1,P3) L 15,=V(PROC2) BALR 14,15 .P1 DS CL8P2 DC F'20'P3 DC C'ABCDEFGHIJKL'PARM DS 3F

Accessing the parameters• On entry to the subprogram, R1 contains the base address of the array of pointers. Each

element of this array points to one of the parameters.• Access the parameter pointer from the array and using this access the parameter itself. • If a structure is passed as in the case of a COBOL program calling an Assembler program,

the address list contains only the address of the first byte of the structure. You can use this address and map a DSECT over the calling programs data structure. The DSECT defines the same structure as that of the data structure in the calling program.

Example of three parameters being passed to a sub program.LM 4,6,0(1) Fetch address of P1-P3L 4,0(4) R4 has P1L 4,0(5) R4 has P2L 4,0(6) R4 has P3

Functions in Assembly language• To pass back a return value from function set register 0 to that value• The return value in R15 can be used to indicate an error condition• A return code of 0 means successful completion• Return codes are usually a multiple of 4, so that it can be used to index into an address

table

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

Page 48: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 48 / 116

. BR 14I DC F'100'J DC F'120'K DS FSAVE1 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 RESTOREBIG LR 0,4RESTORE EQU * . . exit linkages . BR 14SAVE2 DS 18F END

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

Page 49: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 49 / 116

LR 2,13 LA 13,SAVE ST 13,8(0,2) * LR 12,15 DROP 15 USING TEST13,12 ** * * L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) BR 14 SAVE DS 18F END

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

SUB2 CSECT STM 14,12,12(13) USING SUB,15 ST 13,SAVE+4 LA 13,SAVE LR 12,15

Page 50: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 50 / 116

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

Standard Entry and Exit LinkagesTEMP CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) * * * L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) BR 14 SAVE DS 18F END

Standard Entry and Exit Linkages using GETMAINED storageTEMP1 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 LR 3,1 GETMAIN R,LV=LEN,LOC=BELOW ST 13,4(0,1)

LR 2,13 LR 13,1

ST 13,8(0,2) USING WS,13 LR 1,3 * BUSINESS LOGIC STARTS * * BUSINESS LOGIC ENDS

Page 51: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 51 / 116

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

Page 52: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 52 / 116

MACROS AND CONDITIONAL ASSEMBLY BackMacro• 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 passedMacro body :

• Contains the sequence of statements that are generated in the macro expansion. • Model statements from which assembler language statements are generated.• Processing statements that can alter the content and sequence off the statements

generated or issue error messages.• Comments statements.• Conditional assembly instructions to compute results to be displayed in the message

created by the MNOTE instruction, without causing any assembler language statements to be generated

Model Statement• Assembler language statements are generated at pre-assembly time from model

statement• Variable symbols can be specified to vary the contents of the statements generated• Statements generated must not be conditional assembly instructions

Variable Symbols• Prefixed with '&' character• Can appear in macros and in conditional assembly statements• Can be symbolic parameters, system variables or set symbols• System variables are read only and their value is maintained by the Assembler

Page 53: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 53 / 116

ExampleUSER: &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 symbol2) A special character, except a left parenthesis or a period, is to follow a variable symbol3) 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 onlyExample

MACROMAC1 &P1,&K1=10.MEND

Invocation of above Macro:START 0...MAC1 ONE,K1=12.MAC1 TWO.

Page 54: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 54 / 116

.END

ExampleMACRODIVIDE &R1,&R2,&TYPEM &R1,=F`1'D&TYPE &R1,&R2MEND

InvocationMAIN 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 instructionsMNOTE instruction

<SEQ SYM> MNOTE <opt> <message>• To generate error messages or display intermediate values of variable symbols• Can be used in open code or in a macro• Opt specifies a severity code. If"," is specified then the severity code value is "1"• If opt is omitted or a `*' is specified, then the message is generated as a comment

Example:MNOTE 2, `Error in syntax'MNOTE ,`Error, severity 1'MNOTE *, `A comment'MNOTE `Another comment'

MEXIT instruction<SEQ SYM> MEXIT

• Exit from the current macro definition• Can be used only inside a macro definition

Comments• A "*" in column generates an ordinary comment which will appear in the listing• A ".*" sequence in column 1 generates an internal comment which will not appear in the listing

System Variables

Variables set by the system&SYSDATE, &SYSPARM, and &SYSNDX can be used only within a macro

Page 55: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 55 / 116

Name Description&SYSLIST Provides alternate way of accessing positional parameters&SYSPARM To obtain the compile time parm value passed thru JCL EXEC statement&SYSECT To get the name of CSECT from where macro is invoked&SYSTIME To get time in HH.MM format&SYSDATE To get date in MM/DD/YY format

ExamplePrototype statement : LOOP VNAME V1,V2,,V4,(V5,V6)&SYSLIST(0) = LOOP&SYSLIST(1) = V1&SYSLIST(2) = V2&SYSLIST(3) = NULL STRING&SYSLIST(4) = V4&SYSLIST(5) = (V5,V6)&SYSLIST(5,1) = V5&SYSLIST(5,2) = V6N'&SYSLIST = 5N'&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 charactersExample

MACRO&L VAR &P1,&P2,&KEY=(F0,F,0)

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

DC A&P2.MEND

invocation:MAIN START 0

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

MACROLOOP

LOOP&SYSNDX EQU *BNE LOOP&SYSNDXMEND

InvocationMAIN START 0

LOOP

Page 56: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 56 / 116

+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 symbolsGBLB, for global binary set symbolsGBLC, 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>

ExampleGBLA &TEST,&VALGBLC &NAME,&IDGBLB &TRUE

Local set symbols• Values can be accessed only in the macro in which it is defined• Declared using

LCLA, for local arithmetic set symbolsLCLB, for local binary set symbolsLCLC, 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>

Page 57: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 57 / 116

LCLC <VARLIST>ExampleLCLA &CNT,&VALLCLC &STR1LCLB &TRUE

Conditional Assembly Expressions• Three kinds

⇒ Arithmetic ⇒ Character⇒ Binary

• Can be used as operands of conditional branch instruction• To assign values to set symbols• Arithmetic expressions are formed using arithmetic operators• Character expressions can produce strings of up to 255 chars• Parameter substitution within quoted strings• Duplication factor for quoted strings• Boolean expression by combining arithmetic or character expressions using relational

operators

Assigning Values to Set Symbols• Global set symbols have to be defined before assigning values• Undeclared set symbols are defined as local set symbols• More than one element in an array can be assigned values in a single set statements

Set Arithmetic• <VAR SYMBOL> SETA <arithmetic expression>• To assign an arithmetic value to a SETA symbol• Value represented by SETC symbol variable string can be used as a term in an arithmetic expression provided they contain only numeric digits.• Value represented by SETB symbol variable can also be used in arithmetic expression• Valid unary operators are +,-.Binary operators are +,-,*,/

Examples&A SETA 10 10&B SETA 2 2&C SETA &A + 10/&B 15&D SETA (&A+10)/&B 10&A SETA 11 11&B SETA &A/2 5&A SETA 1 1&B SETA &A/2 0

Set Binary• <VAR SYMBOL> SETB <Boolean expression>

Example&B SETB 1&A SETB 0

• To assign an binary bit value to a SETB symbol

Set Character• <VAR SYMBOL> SETC <expression>• To assign characters value to a SETC symbol• The expression could be

⇒ A type attribute reference⇒ A character expression⇒ A sub string notation

Page 58: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 58 / 116

⇒ A concatenation of sub string notations, or character expressions, or both• A duplication factor can precede any of the first three options

Example:&C SETC 'STRING0'** &C="STRING0"*&D SETC ‘&C(4,2)’** &D = "IN"*&E SETC 'L''SYMBOL'** &E = "L'SYMBOL"*&F SETC 'HALF&&'** &F="HALF&"*&G SETC '&D.NER'** &G="INNER"*&C1 SETC 3('ABC')** &C1 = ‘ABCABCABC’*Example

MACRO&NAME MOVE &TO,&FROM

LCLA &A1LCLB &B1,&B2LCLC &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&A1ST 2,&TO&C1L 2,SAVEAREAMEND

InvocationMAIN START 0HERE 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

Page 59: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 59 / 116

next statement processed. If the expression is false, the next sequential statement is processed by the assembler.

Logical operators are EQ,NE,LE,LT,GE,GT

ExampleAIF (`&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 DescriptionT Type of the symbol

Values returned by assembler areA,V,S,Q For the various address constantsB Binary constantC Character constantD,E,L Floating point constantF,H Integer constantsP Packed decimal constantH Hexadecimal constantZ Zoned decimal constantI Machine instructionM MacroJ Control sectionT EXTRN symbolN Self defining termO undefined (omitted)L Length of symbol number of bytesC Number of characters contained by the variable symbolN Number of element in a sublist associated with the symbolD Defined attribute, indicates whether or not the symbol has been defined prior

ExampleMACRO

Page 60: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 60 / 116

TABLELCLA &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 Function1 Macro Call Trace2 Macro Branch Trace4 Macro AIF Dump8 Macro Exit Dump16 Macro Entry Dump32 Global Suppression64 Macro Hex Dump128 Mhelp Suppression

Page 61: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 61 / 116

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 62: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 62 / 116

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 '').NOREGSAIF (&REGS(1) GE &REGS(2)).RET1AIF (&REGS(2) EQ 15).RET1AIF ('&RC' EQ '').RCT3AIF ('&RC'(1,1) EQ '(').RCT2LA 15,&RC

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

.RCT2 ANOP&VALU SETA &RC(1)

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

.*

.RET1 ANOPAIF ('&RC' EQ '').RCT4

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

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

.RCT1 ANOP&VALU SETA &RC(1)

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

.*

.NOREGS ANOPAIF ('&RC' EQ '').RCT6AIF ('&RC'(1,1) EQ '(').RCT5LA 15,&RC

.RCT6 ANOPBR 14MEXIT

.RCT5 ANOP&WORK SETA &RC(1)

LR 15,&WORKBR 14

Page 63: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 63 / 116

MEXITMEND

Page 64: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 64 / 116

MVS SYSTEM MACROS backQSAM

DCB Macro• Included for every data set accessed by the program• Access method depends upon the parameters passed to the DCB• All parameters are keyword parameters specifying various options for the data set• Generates non executable code (control block) and should therefore be coded in the data area

Name DCB DDNAME =External DD name in JCL,DSORG =PS | PO,MACRF={{(G{M|L})} {(P{M|L})}} {(G{M|L},P{M|L})}}

G specifies that GET macros are used. Specifying G also provides the routines that allow the problem program to issue RELSE macros. G is required if the OPEN option is INPUT or UPDAT. It has no effect if the OPEN option is OUTPUT or EXTEND.

L specifies that the locate transmittal mode is used; the system provides the address of the buffer containing the data.

M specifies that the move transmittal mode is used; the system moves the data from the buffer to the work area in the problem program.

P specifies that PUT or PUTX macros are used. P is required if the OPEN option is OUTPUT or EXTEND. It has no effect if the OPEN option is INPUT. P may be specified if the OPEN option is UPDAT.

LRECL =,BLKSIZE=,RECFM =F | FB | FBA | V |VBA,EODAD=,

Notes:- G Get,P Put,G,P Get and PUTM Move mode I/OL Locate mode I/OF Fixed unblockedFB Fixed blockedFBA Fixed blocked with first character as a ASA control character. Used only for

printer outputV Variable unblockedVB Variable blocked

Notes:-In MOVE mode the data is transferred to or from a data area in your program.In LOCATE mode if you issue a GET the address of the record in the system buffer is returned in register 1. You can load it into a work register and map a DSECT over the system buffer by a USING instruction.

If you issue a PUT in LOCATE mode the system returns you an address in register 1 where you can build the new record. The next PUT will write the previously built record and return you a new buffer address in register 1.

DCBE Macro

Page 65: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 65 / 116

This macro is used (optionally) to extend the DCB functionality. The most common use is when the program is changed from AMODE 24 to AMODE 31. See a sample program that illustrates this usage in the chapter on 24 / 31 bit programming issues.

RDJFCB MacroThis macro is used to change the JFCB (Job file control block) that the system creates, one for each DD statement. This macro copies the JFCB to a user defined 176 byte area where the information from the DD statement may be modified before the file is opened. Be aware that some operations need your program to be in authorised mode. The following program uses the same DD statement to open and read three PS files one at a time.

ExampleThis example illustrates how one single DD statement can be serially used to open and read three different files in the same VOLUME.RDJFCB CSECT SAVE (14,12) BALR 9,0 USING *,9 ST 13,SAVE+4 LA 13,SAVE * OPEN (SYSPRINT,OUTPUT),MODE=31 LTR 15,15 BNZ OPENERR * USING INFMJFCB,10 USING IHADCB,11 USING DSTBLMAP,12 * BAL 6,RDJFCB NEXTFILE BAL 6,MDFYJFCB BAL 6,OPEN BAL 6,PROCESS BAL 6,CLOSE B NEXTFILE CLOSE SYSPRINT VOLEND B RETURN * RDJFCB RDJFCB (FILEDCB,INPUT) LTR 15,15 BNZ NODD BR 6 NODD WTO 'FILE DD NOT SPECIFIED IN JCL' ABEND 901 * MDFYJFCB LA 10,JFCB L 12,DSTBLPTR CLI DSNAME,X'00' BE VOLEND MVC JFCBDSNM,DSNAME LA 14,TBLENLEN(0,12) ST 14,DSTBLPTR * OPEN LA 11,FILEDCB OPEN (FILEDCB,INPUT),TYPE=J LTR 15,15

Page 66: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 66 / 116

BNZ OPENERR BR 6 * CLOSE CLOSE (FILEDCB) BR 6 * OPENERR WTO 'OPENERROR' L 13,SAVE+4 RETURN (14,12),,RC=16 * PROCESS GET FILEDCB,BUFFER MVC OUTREC(80),BUFFER PUT SYSPRINT,OUTCARD B PROCESS EOF BR 6 * RETURN L 13,SAVE+4 RETURN (14,12),,RC=0 * SAVE DS 18F DSTBLPTR DC A(DSNTBL) * DSNTBL DS 0F TBLENTBG EQU * DC A(L'DS01) DS01 DC C'userid.FILE1' DC CL(45-L'DS01)' ' DS 0F TBLENTX EQU * DC A(L'DS02) DS02 DC C'userid.FILE2' DC CL(45-L'DS02)' ' DC A(L'DS02) DS03 DC C'userid.FILE3' DC CL(45-L'DS03)' ' NULL DS A DC X'00' TBLENLEN EQU TBLENTX-TBLENTBG * * QNAME DC CL8'SYSDSN' RNAME DS CL44 * JFCB DS 44F JFCBPTR DC X'87' /* this must be on a fullword boundary */ DC AL3(JFCB) BUFFER DS CL80 * FILEDCB DCB DSORG=PS,MACRF=GM,EXLST=JFCBPTR,EODAD=EOF, X DDNAME=INFILE * OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, X LRECL=137,BLKSIZE=1370,RECFM=VB *

Page 67: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 67 / 116

DCBD DSORG=PS DSECT IEFJFCBN * DSTBLMAP DSECT DSNMLEN DS CL4 DSNAME DS CL44 DS CL1 END

The JCL for the above program//userid1 JOB NOTIFY=&SYSUID,CLASS=A,MSGLEVEL=(1,1) // JCLLIB ORDER=(userid.PROCLIB) //STEP1 EXEC ASMACL,REGION=0M //ASM.SYSIN DD DSN=userid.ASM.SOURCE(RDJFCB),DISP=SHR //LKED.SYSLMOD DD DSN=userid.LOADLIB(RDJFCB),DISP=SHR //LKED.SYSLIB DD DSN=userid.OBJECT,DISP=SHR // DD DSN=CEE.SCEELKED,DISP=SHR //RUN EXEC PGM=RDJFCB //STEPLIB DD DSN=userid.LOADLIB,DISP=SHR // DD DSN=CEE.SCEERUN,DISP=SHR //SYSPRINT DD SYSOUT=* //INFILE DD VOL=SER=(volser),DISP=SHR

OPEN MacroName OPEN (DCB-name,{options...})

• Logically connect a data set• Data set identified in the DCB is prepared for processing• Option MeaningINPUT Input data setOUTPUT Output data setUPDAT Data set to be updated in placeEXTEND Add records to the end of the data set• DISP Disp options (PASS,KEEP,DELETE,CATLG,UNCATLG)

ExampleOPEN (EMPLOYEE,(INPUT),SALES,(OUTPUT))

CLOSE MacroName CLOSE (DCB-NAME {,option),...})

• Logically disconnect a data set• Option MeaningREREAD Position to the beginning of the data setLEAVE Position to the logical end of the data setREWIND Magnetic tape has to be positioned at the beginning

• DISP Disp options like PASS,KEEP,DELETE,CATLG, and UNCATLGExampleCLOSE (EMPLOYEE,SALES)

GET Macro (QSAM)Name GET DCB-NAME, {area name}

• Retrieve the next record• Control is returned after the record is read• In locate mode the address of the record is returned in R1• In move mode the record is moved to the user area

ExampleGET EMPLOYEE, EMPREC

Page 68: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 68 / 116

PUT Macro (QSAM)Name PUT DCB-NAME,{area name}• Write a record.• Control is returned after the record is written• In locate mode the area name parameter is omitted and the system returns the address of the

I/O buffer in R 1. The data has to be moved to this area and it is written in the next PUT call.• In moved mode, the system moves the record to an output buffer before the control is

returned.

ExamplePUT EMPLOYEE,EMPREC

ExampleThis example illustrates how a SYSPRINT (SYSOUT) file may be defined and created.PRINT CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE OPEN (SYSPRINT,OUTPUT) LTR 15,15 BNZ OPENERR LA 5,20 MVC OUTREC+1(132),=CL132'THIS IS LINE ONE.' LOOP PUT SYSPRINT,OUTCARD BCT 5,LOOP CLOSE SYSPRINT L 13,SAVE+4 RETURN (14,12),,RC=0 OPENERR L 13,SAVE+4 RETURN (14,12),,RC=16 OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, X LRECL=137,BLKSIZE=1370,RECFM=VBA SAVE DS 18F END

Required JCL statement//SYSPRINT DD SYSOUT=*

Example of LOCATE mode I/OGETQSAMLOCR CSECT SAVE (14,12) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) * OPEN (SYSPRINT,OUTPUT)

Page 69: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 69 / 116

LTR 15,15 BNZ OPENERR1 * OPEN (INFILE,INPUT) LTR 15,15 BNZ OPENERR2 * USING INREC,2 * LOOP GET INFILE LR 2,1 MVC DATA+1(80),INDATA PUT SYSPRINT,RECORD B LOOP * EOF CLOSE SYSPRINT CLOSE INFILE L 13,SAVE+4 RETURN (14,12),,RC=0 * OPENERR1 L 13,SAVE+4 RETURN (14,12),,RC=16 * OPENERR2 L 13,SAVE+4 RETURN (14,12),,RC=20 * SAVE DS 18F RECORD DC AL2(137),AL2(0) DATA DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,DSORG=PS,MACRF=PM,RECFM=VBA,LRECL=137, X BLKSIZE=1370 INFILE DCB DDNAME=INFILE,DSORG=PS,MACRF=GL,EODAD=EOF * INREC DSECT INDATA DS CL80 END

PUT in locate modeQSAMLOCW CSECT SAVE (14,12) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) * OPEN (SYSPRINT,OUTPUT) LTR 15,15 BNZ OPENERR1 * OPEN (INFILE,INPUT) LTR 15,15 BNZ OPENERR2 * OPEN (OUTFILE,OUTPUT)

Page 70: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 70 / 116

LTR 15,15 BNZ OPENERR3 * USING INREC,2 * LOOP GET INFILE LR 2,1 PUT OUTFILE LR 3,1 MVC DATA+1(80),INDATA MVC 0(80,3),INDATA PUT SYSPRINT,RECORD B LOOP * EOF CLOSE SYSPRINT CLOSE INFILE CLOSE OUTFILE L 13,SAVE+4 RETURN (14,12),,RC=0 * OPENERR1 L 13,SAVE+4 RETURN (14,12),,RC=16 * OPENERR2 L 13,SAVE+4 RETURN (14,12),,RC=20 * OPENERR3 L 13,SAVE+4 RETURN (14,12),,RC=24 * SAVE DS 18F RECORD DC AL2(137),AL2(0) DATA DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,DSORG=PS,MACRF=PM,RECFM=VBA,LRECL=137, X BLKSIZE=1370 INFILE DCB DDNAME=INFILE,DSORG=PS,MACRF=GL,EODAD=EOF OUTFILE DCB DDNAME=OUTFILE,DSORG=PS,MACRF=PL,RECFM=FB,LRECL=80, X BLKSIZE=800 * INREC DSECT INDATA DS CL80 END

UPDATE (GET/PUTX)QSAMLOCU CSECT SAVE (14,12) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) * OPEN (INFILE,UPDAT) LTR 15,15 BNZ OPENERR *

Page 71: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 71 / 116

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

Memory ManagementGETMAIN

• 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

SyntaxName GETMAIN RC,LV=lv,BNDRY=bndry,LOC=LocR Register formLV Length valueBNDRY DBLWD / PAGELOC BELOW / ANY (16MB line)

ExampleGETMAIN RC,LV=4096,BNDRY=PAGE,LOC=ANY

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

Page 72: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 72 / 116

OI MSG+17,X'F0' LA 3,MSG WTO TEXT=(3) LR 2,13 L 13,4(0,2) FREEMAIN R,LV=LEN,A=(2) RETURN (14,12),,RC=0 ** constants can be part of CSECT like this* MSG1 DC CL16'THIS IS MSG 1' MSG2 DC CL16'THIS IS MSG 2' MSG3 DC CL16'THIS IS MSG 3' MSG4 DC CL16'THIS IS MSG 4' MSG5 DC CL16'THIS IS MSG 5' ** This DSECT maps over getmained storage* WS DSECT SAVE DS 18F MSG DS AL2 DS CL16 DW DS D ARRAY DS 1000D LEN EQU *-WS END

Example DXD, CXD and Q Type Address ConstantThis example illustrates the use of DXD, CXD data types and Q type address constants.DXD refers to storage allocated in an external dummy section. A DSECT can also be considered an external dummy section if it is used in a Q type constant. The CXD is initialised by the linkage editor to the sum of the lengths of all external dummy sections in the load module. It is used to getmain storage for the external dummy sections at run time. The Q type address constants are set to the offset of the corresponding dummy sections.

ROUTINE AA 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 2DL8BX DXD 4FL4LEN CXD . DC Q(AX) DC Q(BX) .

Page 73: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 73 / 116

ROUTINE BB 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 CE DSECTITEM DS FNO DS FSUM 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

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

RC Register formlv Length valueA Virtual storage address

ExampleFREEMAIN RC,LV=4096,A=(1)

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

Page 74: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 74 / 116

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

Page 75: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 75 / 116

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 ManagementLOAD

• Brings the load module into virtual storage• Module contains program or table• Placed above or below line• Returns

⇒ Authorisation code⇒ Length of the module⇒ Entry point to the module⇒ AMODE of the module

• Control is not passed to the module• Used in dynamic subroutine call• Modules can be shared

Name LOAD EP=entry nameOn return to caller the registers contain the following0 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

ExampleLOAD EP=MYPROG,ERRET=LERRORLR 15,0 stick to using register 15 for entry pointBSSM 14,15 BSSM takes care of switch of AMODE if reqd.

Page 76: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 76 / 116

.

LERROR WTO ‘LOAD OF MYPROG FAILED’L 13,SAVE+4RETURN (14,12),,RC=16

An important point to note is that if the module has already been loaded into the callers address space because of a earlier request ( Possibly from some asynchronous exit routine) then control is given to the existing copy of the module. Since we branch to the entry point directly, we can have a problem if the module is in use and it is not re-entrant or is only serially reusable. For this reason XCTL or LINK is preferred as the control is passed via system which checks for this possible source of error. DELETE

• Remove a module from virtual storage• Entry name same as used in load macro• Task termination removes the module

Name DELETE EP=entry nameRegister 15 is zero on successful completion.

CALLName CALL entry-name | (n),(parm1,parm2,….),VL

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

Notes:- The reg1,reg2 indicates the registers that are to be restored from save area before the called routine gets control . Usually coded (2,12). MF=(E,User area). User area points to an area where the parameter list can be generated .Since the transfer is through the system, the system takes care of the AMODE switch if required. The system also takes care of re-entrancy of the module transferred to. Control does not return back to caller in any case.

The caller has to dynamically acquire storage for the user area where the system generates the parameter list. Additionally parm1, parm2 etc must be in getmained storage so that the data areas are available even after the calling program transfers control to the target program.

The receiving program gets control with register 1 pointing to the user area where the XCTL macro builds the parameter list.

Example:This example illustrates how an XCTL may be issued. The point to note is that you must set up any parameters that are passed in GETMAINED storage. That is because the invoking programs storage is released on XCTL and cannot be used to set up parameters.XCTL CSECT STM 14,12,12(13)

Page 77: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 77 / 116

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

XCTL1 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE LR 2,1 USING PARMS,2 WTO 'IN XCTL1',ROUTCDE=(11) L 6,ADDR L 5,0(0,6) L 6,ADDR+4 A 5,0(0,6) * CVD 5,DW UNPK MSG+2(8),DW OI MSG+9,X'F0' WTO TEXT=MSG,ROUTCDE=(11) L 13,SAVE+4 LM 14,12,12(13) SR 15,15 BR 14 SAVE DS 18F DW DS D MSG DC AL2(8) DS CL8 PARMS DSECT

Page 78: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 78 / 116

ADDR DS 2A A1 DS F A2 DS F END

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=error routine

Called routine gets control with the following values in the register⇒ 1 address of parameter list⇒ 15 Entry address of called program

If the link was unsuccessful the error routine gets control with the following⇒ 1 Abend Code that would have been issued if the caller had not provided error exit⇒ 2-12 unchanged⇒ 15 Address of the error exit⇒ 14 used as work register by system

Example LINK EP=MYPROG,PARAM=(parm1,parm2),ERRET=ERROR

.

.PARM1 DS FPARM2 DS FERROR …

Process ManagementABENDName ABEND compcode,REASON=,DUMP,STEP

compcode value 0 to 4095.Register notation (2) to (12) permittedREASON This code is passed to subsequent user exits if specified. 32 bit hexadecimal value or

31 bit decimal numberDUMP Requests a dump of virtual storage assigned to task. Needs //SYSABEND,//SYSDUMP or //SYSUDUMP DD statement to be present in the JCL for the job step.STEP Requests all tasks associated with this Job step of which this task is a part to abend

ATTACH• To create a new task• New task is the subtask• Parameter list could be passed• ECB can be provided• Limit priority same as that of the creating task• Dispatching priority same as that of the creating task• Use DETACH macro to remove the sub task• Returns TCB address in register 1Name ATTACH EP=entry name,

Page 79: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 79 / 116

PARAM=(parm1,parm2,…),VL=1,ECB=ecb-addr,EXTR=Address of end of task routine

Registers on entry to subtask are⇒ 0 Used as work area by system⇒ 1 Used by macro to point to parameter list⇒ 2-12 Used as work registers by System⇒ 13 Should point to a 18F save area in callers module⇒ 14 Return address. Bit 0 is 0 if subtask gets control in 24 bit mode else 1 if subtask gets control in 31 bit mode⇒ 15 Entry point address of subtask

Registers on return to caller after issue of ATTACH⇒ 1 address of TCB of subtask⇒ 15 A return code of non zero means subtask could not be attached

Load Libraries searched are⇒ Job pack area ⇒ Requesting tasks task library and all unique task libraries of parent tasks⇒ Step library⇒ Job library⇒ Link Pack area⇒ Link Library

In simplest form usage can be :ATTACH EP=PROG1,ECB=ECB1

ECB1 DS F

Notes:- • This macro creates a separate thread of execution in callers address space• Within the Address space this subtask will compete for processor resources

1) There is a despatching priority for address space2) At a lower level there is a despatching priority for the subtasks

• The attaching task has to wait for subtasks to end before terminating else it will abend when attempting to terminate • The attaching task has to wait on the ECB which is posted by the system when the subtask ends• The attaching task then issues a DETACH macro.• EXTR exit routine gets control with the following register values

⇒ 0 used as a work register by the system⇒ 1 Address of TCB of subtask. Needed for issuing DETACH macro⇒ 2-12 Work registers⇒ 13 18F save area provided by system⇒ 14 return address⇒ 15 entry point of exit routine

DETACH• Removes a subtask• If issued before task completion, terminate the task• Should be issued if ECB or ETXR is used in ATTACH• Removing a task removes all its dependent tasks also• If ECB or ETXR is used, and the parent task does not issue DETACH, then the

parent task will abend

Name DETACH tcb address | (n)

Page 80: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 80 / 116

Operand can be in register notation in which case regs 1 thru 12 may be used.The TCB address should have been previously obtained by EXTR exit routine

ExampleATTACH EP=PROG1,EXTR=ENDOFTSKLTR 15,15BNZ ERRORST 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 WAIT 1,ECB=ECB1

.

.ECB1 DC F’0’

POST• Posts a ECB through a system call

ExampleLA 4,ECB1POST (4)

.

.ECB1 DC F’0’

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

Page 81: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 81 / 116

LA 4,TCB1 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 ExampleThis example illustrates how a main task and sub task can work in a synchronized fashion writing every alternate record to a shared SYSPRINT dataset. The synchronisation is achieved using WAIT and POST macros.

ATTACH3 CSECT STM 14,12,12(13)

Page 82: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 82 / 116

BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE OPEN (SYSPRINT,OUTPUT) ATTACH EP=SUBTASK3,PARAM=(SYSPRINT,ECBM,ECBS), X

ECB=ECB1 ST 1,TCB1 LTR 15,15 BNZ ATTERR LA 4,50 MVC OUTREC+1(132),=CL132'MAIN MESSAGE' SR 5,5 LA 6,ECBS LA 7,ECBM POST (7)LOOP WAIT 1,ECB=ECBM PUT SYSPRINT,OUTCARD ST 5,ECBM POST (6) BCT 4,LOOP WAIT 1,ECB=ECB1 LA 4,TCB1 DETACH (4) CLOSE SYSPRINT L 13,SAVE+4 RETURN (14,12),,RC=0ATTERR L 13,SAVE+4 RETURN (14,12),,RC=10OUTCARD DC AL2(137),AL2(0)OUTREC DC CL133' 'SYSPRINT DCB DDNAME=SYSPRINT,DSORG=PS,MACRF=PM, X LRECL=137,BLKSIZE=1370,RECFM=VBASAVE DS 18FECB1 DC F'0'ECBM DC F'0'ECBS DC F'0'TCB1 DS F END

SUBTASK CODE: Compile and linkedit this first separatelythen, compile, linkedit and run 'attach3'

SUBTASK3 CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE MVC OUTREC+1(132), X =CL132'Message from Subtask' SR 5,5 L 4,0(0,1) SYSPRINT L 6,4(0,1) ECBM L 7,8(0,1) ECBS LA 3,50

Page 83: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 83 / 116

LOOP1 WAIT 1,ECB=(7) PUT (4),OUTCARD ST 5,0(0,7) POST (6) BCT 3,LOOP1 L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) BR 14SAVE DS 18FOUTCARD DC AL2(137),AL2(0)OUTREC DC CL133' ' END

RETURNName RETURN (reg1,reg2),T,RC=retcoderestores reg1 to reg2 from save area pointed by R13T sets a flag in the save area in the called program for dump analysis if requiredMaximum value for return code is 4095 which is set in R15(see example of implementation under MACROS and conditional assembly)

SAVEName SAVE (reg1,reg2)Saves reg1 thru reg2 in save area pointed to by R13(see example of implementation under MACROS and conditional assembly)

SNAPThis macro enables you to take a snap shot of your program when it is running. It is useful for debugging run time errors. You can issue calls for the snap dump as often as you wish and specify the range of addresses, from one byte to your whole program. You can also request for a register dump and save area trace by coding PDATA=(REGS,SA)

Here is a sample program skeleton for issuing a SNAP macro:-

BEGIN CSECT SAVE (14,12) BALR 3,0 USING *,3 ST 13,SAVE+4 LA 13,SAVE . . OPEN (SNAPDCB,OUTPUT) LTR 15,15 BNZ ERROR3 . . SNAP DCB=SNAPDCB,ID=1,PDATA=(REGS,SA), X STORAGE=(BEGIN,LAST) . . SNAP DCB=SNAPDCB,ID=2,PDATA=(REGS,SA), X STORAGE=(BEGIN,LAST) . . .

Page 84: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 84 / 116

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

REENTERABILITYFor load modules which may be shared amongst more than one concurrent task, re-entrancy is important. Most macros (in standard form) generate an inline parameter list of data areas which are used for passing as well as receiving information from the macro call. Obviously inline parameter list makes the load module non re-entrant and at best serially re-entrant.

For this reason to make a load module re-entrant, do not define data areas in the program which will be part of the load module. Instead at run time (using GETMAIN or STORAGE OBTAIN) to dynamically acquire storage. A typical example of this would be to acquire the 18 full word save area dynamically. Where the acquired area needs to be accessed by field you can use a DSECT to format the block of storage.

As for MACROS IBM provides, apart from standard form which develops inline parameter lists, LIST and EXECUTE (MF=L or MF=E) form of the macro exist. The list form does not generate any executable code. Instead it generates only a parameter list. At run time you acquire storage equivalent in size to this list and copy the list to this area. This way each thread of execution will have it's own discrete parameter area. At run time use the execute form of the macro (which can also be used to change some of the parameters generated earlier) with a pointer to the parameter list built up in virtual storage.

The list form of the macro is signalled to the assembler by the parameter MF=LThe execute form is signalled to the assembler by using the parameter MF=E

Example..LA 3,MACNAME load address of the list generatedLA 5,NSIADDR load address of end of listSR 5,3 GPR5 will now have length of listBAL 14,MOVERTN go to rtn to move listDEQ ,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 gpr4BCTR 5,0 subtract 1 from gpr5EX 5,MOVEINSTBR 14

MOVEINST MVC 0(0,4),0(3) change the length field and copy the listMACNAME DEQ (NAME1,NAME2,8,SYSTEM),RET=HAVE,MF=LNSIADDR EQU *NAME1 DC CL8'MAJOR'NAME2 DC CL8'MINOR'

Page 85: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 85 / 116

Example using WTOThe following example GETMAINS storage for the WTO parameter list as well as writable storage for the program (SAVE, MSG and the 16 byte display area. The ultimate test of the re-entrancy of the program is in making it an RSECT and ensuring that the assembler does not detect any violations of re-entrancy.

WTORENT RSECT STM 14,12,12(13) BALR 12,0 USING *,12 LR 2,1 GETMAIN RC,LV=LEN,LOC=BELOW ST 13,4(0,1) LR 3,13 LR 13,1 ST 13,8(0,3) LR 1,2 USING WS,13 * GETMAIN RC,LV=WTOLEN,LOC=BELOW LR 2,1 MVC 0(WTOLEN,2),WTOL * LH 3,=H'40' STH 3,MSG MVC MSG+2(40),=CL40'THIS IS FROM WTORENT' * LA 3,MSG WTO TEXT=(3),MF=(E,(2)) * LR 2,13 L 13,SAVE+4 FREEMAIN RC,LV=LEN,A=(2) RETURN (14,12),,RC=0 * WTOL WTO TEXT=,ROUTCDE=(11),MF=L WTOLEN EQU *-WTOL WS DSECT SAVE DS 18F MSG DS AL2 DS CL40 LEN EQU *-WS END

Page 86: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 86 / 116

VSAM MACROS back

Macros Name ACB AM=VSAM,

BUFND=, BUFNI=,BUFSP=, DDNAME=,

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

NOTES:AM : Always code VSAM for access to VSAM data setsBUFND : Number of data buffers, default=2,override possible through JCLBUFNI : Number of Index buffers, default=1,override possible through JCLBUFSP : Size of area for Index and Data Buffers. Defaults to specification

in catalogueDDNAME : Connects a DD statement in run time JCL with this ACBEXLST : Address of EXLST macroMACRF : ADR Access by RBA

CNV Access by Control IntervalKEY Access by Record KeyDIR Direct Processing SEQ Sequential ProcessingSKP Skip Sequential ProcessingIN Input onlyOUT Input / Output

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

NotesEODAD Is the exit routine for end of fileJRNAD exit routine for journal file updates/deletions/insertionsLERAD Logical error exitSYNAD Physical error exitA Routine is activeN Routine is inactiveL Routine is to be dynamically loaded when required

Name RPL ACB=,AREA=,AREALEN=,RECLEN=,ARG=,KEYLEN=,OPTCD=,NXTRPL=

NOTES:ACB : Address of ACB macro (label)AM : Always code VSAM (used for documentation purposes only)

Page 87: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 87 / 116

AREA : In move mode address of work area for record (label of data area): In locate mode is used by VSAM to set address of record in VSAM buffer

AREALEN : Length of work area. In locate mode will be at least 4.(Full word)RECLEN : For a PUT request is length of record for variable length record: For a GET request is updated by VSAM to indicate length of record

readARG : Label of Argument Field (Key | RBA) field used with GET,PUT,

: POINTKEYLEN : Used to specify key length if Generic key is used (OPTCD=GEN)NXTRPL : address of next RPL in chain if chained RPL'S are used.OPTCD : ( [ADR|CNV|KEY],[DIR|SEQ|SKP],[FWD|BWD],[ARD|LRD],

: [NSP|NUP|UPD],[LOC|MVE],[ASY|SYN],[KEQ|KGE],: [FKS|GEN]):

: ADR Access by RBA: CNV Access by control interval: KEY Access by record key:: DIR Direct processing: SEQ Sequential Processing: SKP Skip sequential processing:: FWD Forward Sequential processing: BWD Backward Sequential processing

: ARD 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): MVE 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• 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

Page 88: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 88 / 116

• The fifth group specifies whether the record is being read with intention to update. If not which record is to be read next.• The last group specifies whether the MOVE or LOCATE mode of I/O is to be used.• This macro generates a control block and should therefore be placed in Data area of your program

OPEN Address of ACB MacroCLOSE Address of ACB MacroGET RPL=Label of RPL macro | (register) retrieve a record PUT RPL=Label of RPL macro | (register) write a recordPOINT RPL=Label of RPL macro | (register) position for subsequent accessERASE 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 fieldsTESTCB This macro is used to test control block fieldsMODCB This macro used to modify control block fields

Name SHOWCB ACB|EXLST|RPL=,AM=VSAM, only for documentation purpose AREA=,LENGTH=,FIELDS=(keyword[,keyword]…)

Notes:ACB | EXLST | RPL : Address (label) of specified MacroAREA : Area into which VSAM will put the contents of field

specifiedLENGTH : 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 bytesFIELDS : 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 belowAVSPAC number of bytes of available spaceBUFNO Number of buffers in use for this fileCINV Size of Control IntervalFS Percent of Free control intervalsKEYLEN Length of key fieldLRECL Maximum record lengthNCIS Number of Control Interval SplitsNDELR Number of deleted records from file NEXT Number of Extents allocated to fileNINSR Number of records inserted in fileNLOGR Number of records in fileNRETR Number of records retrieved from file

Page 89: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 89 / 116

NUPDR Number of records updated in fileRKP 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 macrosERET : Address of error handler to be executed if test cannot be executedkeyword : Any field of the ACB,EXLST,RPL macro;

The length of any ACB,EXLST,RPL macro using the keywords ACBLEN,EXLLEN,RPLLEN

OBJECT : DATA or INDEX

Example

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

RPL1 RPL ….

Notes: Some common VSAM FDBK codes are8 Duplicate key12 Record out of sequence16 No record found68 Access requested does not match access specified92 A put for update without a corresponding get for update104 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 ….

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

Page 90: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 90 / 116

//

Sample JCL to print contents of the cluster //userid1 JOB MSGCLASS=A,NOTIFY=&SYSUID //MYSTEP EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD * PRINT INDATASET(userid.KSDS1) CHAR /* //

The program that loads the file in sequential modeVSAMLS CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE OPEN (VSAMACB) LTR 15,15 BNZ ERR1 OPEN (QSAMDCB,INPUT) LTR 15,15 BNZ ERR2 LOOP GET QSAMDCB,BUFFER PUT RPL=RPL1 LTR 15,15 BZ OK WTO 'PUT ERROR FOR VSAM' OK B LOOP ERR1 WTO 'ERROR OPENING VSAM FILE' L 13,SAVE+4 RETURN (14,12),,RC=16 ERR2 WTO 'ERROR OPENING QSAM FILE' L 13,SAVE+4 RETURN (14,12),,RC=16 EOF WTO 'EOF ON INPUT' CLOSE (QSAMDCB) CLOSE (VSAMACB) L 13,SAVE+4 RETURN (14,12),,RC=0 SAVE DS 18F VSAMACB ACB AM=VSAM,DDNAME=OUTFILE,MACRF=(KEY,SEQ,OUT) RPL1 RPL AM=VSAM,ACB=VSAMACB,AREA=BUFFER,AREALEN=80,RECLEN=80, X ARG=KEYFLD,OPTCD=(KEY,SEQ,FWD,MVE) BUFFER DS CL80 KEYFLD DS CL5 QSAMDCB DCB DDNAME=INFILE,DSORG=PS,EODAD=EOF,MACRF=GM END

Example to read a VSAM KSDS sequentiallyVSAMRS CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4

Page 91: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 91 / 116

LA 13,SAVE OPEN (VSAMACB) LTR 15,15 BNZ ERR1 OPEN (SYSPRINT,OUTPUT) LTR 15,15 BNZ ERR2 LOOP GET RPL=RPL1 MVC OUTREC+1(80),BUFFER PUT SYSPRINT,OUTCARD B LOOP ERR1 WTO 'ERROR OPENING VSAM FILE' L 13,SAVE+4 RETURN (14,12),,RC=16 ERR2 WTO 'ERROR OPENING SYSPRINT FILE' L 13,SAVE+4 RETURN (14,12),,RC=16 EOF WTO 'EOF ON INPUT' CLOSE (SYSPRINT) CLOSE (VSAMACB) L 13,SAVE+4 RETURN (14,12),,RC=0 SAVE DS 18F VSAMACB ACB AM=VSAM,DDNAME=INFILE,MACRF=(KEY,SEQ,IN),EXLST=EXLST1 RPL1 RPL AM=VSAM,ACB=VSAMACB,AREA=BUFFER,AREALEN=80,RECLEN=80, X OPTCD=(KEY,SEQ,FWD,MVE) EXLST1 EXLST AM=VSAM,EODAD=EOF BUFFER DS CL80 OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, X LRECL=137,BLKSIZE=1370,RECFM=VBA END

Example to read a VSAM KSDS in direct modeVSAMRD CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE OPEN (VSAMACB) LTR 15,15 BNZ ERR1 OPEN (SYSPRINT,OUTPUT) LTR 15,15 BNZ ERR2 OPEN (KEYFILE,INPUT) LTR 15,15 BNZ ERR3 LOOP GET KEYFILE,KEYBUFF MVC KEYFLD,KEYBUFF GET RPL=RPL1 LTR 15,15 BZ OK MVC OUTREC,=CL133' '

Page 92: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 92 / 116

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

Example of direct insertionVSAMUD CSECT SAVE (14,12) BALR 3,0 USING *,3 ST 13,SAVE+4 LA 13,SAVE OPEN (FILE1,INPUT) LTR 15,15 BNZ ERROR1 OPEN (VSAMACB)

Page 93: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 93 / 116

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

Page 94: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 94 / 116

FRAMEWORK OF ASSEMBLER PROGRAMS TO ACCESS VSAM FILESKeyed Direct DeletionDELETE ACB MACRF=(KEY,DIR,OUT)LIST RPL ACB=DELETE,AREA=WORK,AREALEN=50, X ARG=KEYFIELD,OPTCD=(KEY,DIR,SYN,UPD,MVE,FKS,KEQ) . .LOOP MVC KEYFIELD,source GET RPL=LIST LTR 15,15 BNZ ERROR

. . B LOOP if you do not want to delete this record ERASE RPL=LIST LTR 15,15 BNZ ERRORERROR .WORK DS CL50KEYFIELD DS CL5

Note that when you GET a record with UPD in the OPTCD option of the RPL vsam maintains position after the get anticipating either an ERASE or PUT (update). Instead if you issue a GET it goes ahead with the GET and position for the previous record is lost.

Keyed sequential retrieval (backward)INPUT ACB DDNAME=INPUT,EXLST=EXLST1RETRVE RPL ACB=INPUT,AREA=IN,AREALEN=100, X OPTCD=(KEY,SEQ,LRD,BWD)EXLST1 EXLST EODAD=EOD POINT RPL=RETRVE LTR 15,15 BNZ ERRORLOOP GET RPL=RETRVE LTR 15,15 BNZ ERROR . . process the record here B LOOPEOD EQU * . . come here for end of fileERROR . . come here for any error .IN DS CL100

Keyed Direct Retrieval in LOCATE mode(KSDS, RRDS)INPUT ACB MACRF=(KEY,DIR,IN)RETRVE RPL ACB=INPUT,AREA=IN,AREALEN=4,OPTCD=(KEY, X DIR,SYN,NUP,KEQ,GEN,LOC),ARG=KEYAREA, X KEYLEN=5 . .LOOP MVC KEYAREA,source GET RPL=RETRVE

Page 95: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 95 / 116

LTR 15,15 BNZ ERROR . Address of record is now in IN . B LOOPERROR .. .IN DS CL4 Where VSAM puts the address of the record in the I/O bufferKEYAREA 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

Position with POINT macroBLOCK ACB DDNAME=IOPOSITION 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 ERRORLOOP1 GET RPL=POSITION LTR 15,15, BNZ ERROR . process record . B LOOP1 continue in sequential modeERROR .SRCHKEY DS CL5WORK DS CL50

Keyed Sequential insertion KSDS variable lengthBLOCK 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 LOOPERROR .BUILDRCD DS CL250

Page 96: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 96 / 116

Keyed direct insertionOUTPUT 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 LOOPERROR ..WORK DS 80C

Note VSAM extracts the key field from the record area.

Keyed Direct UpdateINPUT ACB MACRF=(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,LENGTH=4 LTR 15,15 BNZ ERROR** update the record* does the new record have a different length BE STORE If not go to PUT L 5,length set R5 for new length MODCB RPL=UPDTE,RECLEN=(5) LTR 15,15 BNZ ERRORSTORE PUT RPL=UPDTE LTR 15,15 BNZ ERROR B LOOPERROR ..IN DS CL120KEYAREA DS CL5RLGTH DS F

Page 97: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 97 / 116

LINKAGE CONVENTIONS 24 / 31 BIT ADDRESSING back

LINKAGE CONVENTIONS• Another program can be invoked through BALR, BASR, BASSM or LINK, XCTL and CALL

macros• A primary mode program is one which operates in primary Address Space Control mode or

primary ASC for short. In this mode access of machine instructions is only in the primary address space. All your application programs run in this mode. System programs, like the DB2 subsystem, etc can switch to Address Space modes.

• The called program needs to save the registers when it receives control and restore them when returning. For this the caller provides a 18 Full word save area pointed to by R13.

When a caller provides a 18F save area the area is used as below

Word Usage0 Used by language products1 Address of previous ( caller) save area2 Address of next save area3 GPR144 GPR155-17 GPR0-12

Example of using the caller provided save areaCalling program linkage . LA 1,=A(P1,P2,P3+X’80000000’)

L 15,=V(PGM)BALR 14,15

.

Called program linkagePGM CSECTPGM AMODE 31PGM RMODE ANY STM 14,12,12(13) save callers registers in callers save area LR 12,15 set up base register LR 2,1 USING PGM,12 GETMAIN RC,LV=72 obtain save area ST 13,4(,1) and store callers R13 point in it ST 1,8(,13) store this programs save area in callers save area LR 13,1 set R13 to point to this save programs area LR 1,2 LM 2,4,0(1) set R2 thru R3 to address of P1,P2 and P3 . . . LR 2,13 Set R1 to the address of this programs save area L 13,4(,13) set R13 to point to callers save area FREEMAIN RC,A=(2),LV=72 release this programs save area SR 15,15 Zero R15 L 14,12(0,13) Restore R14 of caller LM 0,12,20(13) Restore R2 to R12 of caller BR 14 Return END

Page 98: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 98 / 116

Calling program must do the following On entry:-

• Save callers registers 14 thru 12 in the save area pointed to by R13 + 12 bytes Offset.• Establish a GPR as a base register.• Establish a base area of 18 Full words of its own.• Save callers R13 into our own save area + 4.• Set GPR 13 to point to its own save area• Set our save area address into callers save area + 8 (optional).

On exit• Place parameter information that may be returned to caller in R1, R0• Load R13 with callers save area address and restore R0-R12,R14• Load R15 with return code• Issue the BR 14 instruction.

Passing Parameters• Use R1 to point to a parameter list which is an array of 32 bit addresses which point to parameters.• The last element of the Address List array should have bit 0 set to 1 to indicate it is the last element.

Example if control is passed to another program in same mode.

L 15,NEXTADDR CNOP 0,4 BAL 1,GOOUTPARMLIST DS 0ADCBADDR DC A(P1) DC A(P2)ANSWERAD DC A(P3+X'80000000’)NEXTADDR DC V(SUBPGM)GOOUT BALR 14,15RETURN . .P1 DC 12F'0'P2 DC .P3 DC .

AddressingAMODE 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

GPR1

A(PARM1)

A(PARM2)

A(PARM3)

B’1’+ A(PARMN)

2 BYTE LENGTH PARM FIELD

2 BYTE LENGTH PARM FIELD

Page 99: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 99 / 116

that the program expects to receive control in 24 bit addressing mode. In this case the high order 8 bits are not reckoned for computing the effective address. The mode of operation affects operation of some machine instructions like

BAL, BALR, LA

In the case of BAL and BALR, in 24 bit mode the link register (first operand) which contains the return address in low order 24 bits, has the high order 8 bits set to the ILC (Instruction length code, CC (Condition code) and Program mask. When in 31 bit addressing mode the link register has bit 0 set to 1 and rest of the 31 bits represent the address. In the case of LA, in 24 bit mode the high order 8 bits are cleared and low order 24 bits are set to represent a 24 bit address. In 31 bit mode, bit 0 is set to 0 and rest of the bits represent a 31 bit address.

RMODE of a program indicate where it can be loaded by the system for execution. A RMODE of any indicates it can be loaded either above or below what is known as the 16MB line or simply the line. A RMODE of 24 indicates that it is to be loaded only below the line.

AMODE and RMODE can be set in the assembler source as below:

MAIN CSECTMAIN AMODE 31 AMODE can be 24 / 31 / any.Default=24MAIN 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. Note that BAL and BALR will set the Link register as below in 24 bit mode:-

┌───┬───┬─────┬──────────────────────┐│ │ │Prog │ ││ILC│CC │Mask │ Instruction Address │└───┴───┴─────┴──────────────────────┘0 2 4 8 31

BAS and BASR set the high order byte to X’00’ in 24 bit mode. This is how BAS and BASR differ from BAL and BALR.

• BSM provides an unconditional branch to the address in operand 2, saves the current AMODE in the high order bit of the Link register (operand 1) and sets the AMODE to agree with the high order bit in the to address.

• 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

Page 100: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 100 / 116

BAL/BALR BRBAS/BASR BR

If we need to change the AMODE as well use BASSM to call and BSM to return.

ExampleThis code snippet switches a AMODE 24 program to 31 bit mode while calling a AMODE 31 program.TEST CSECTTEST AMODE 24TEST RMODE 24 . . L 15,EPA Obtain transfer address BASSM 14,15 switch AMODE and branch . . EXTRN SUB31EPA DC A(X'80000000+SUB31) set high order bit to 1 to switch AMODE . . END

SUB31 CSECTSUB31 AMODE 31SUB31 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 AMODE bit affect the way some H/W instructions work (BAL,BALR,LA)⇒ A program must return control in the same mode in which it gained control⇒ A program expects a 24 bit address from a 24 bit mode program and 31 bit addresses from a 31 bit mode program⇒ A program must validate the high order byte of any address passed by a 24 bit mode program before using it as an address in 31 bit mode.

CALL, BALR

Calling module AMODE 24RMODE 24

Called moduleAMODE 24RMODE 24

Page 101: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 101 / 116

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 CSECTMAIN AMODE 31MAIN RMODE 24

• In the EXEC statement invoking the linkage editor//LKED EXEC PGM=HEWL,PARM='AMODE=31,RMODE=24'

• Linkage editor control statementMODE 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 followsExampleUSER1 CSECTUSER1 AMODE 24USER1 RMODE 24 L 15,. . . L 1,LAB1 BSM 0,1LAB1 DC A(LAB2+X'80000000)LAB2 DS 0H L 2,4,(,15) LA 1,LAB3 BSM 0,1LAB3 DS 0H . . END

Examples

Calling moduleAMODE 24RMODE 24

Called moduleAMODE 31RMODE 24

Page 102: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 102 / 116

TEST11 is coded to be AMODE31 and RMODE Any. It calls a sub program TEST11A which is a AMODE24, RMODE24 program. The examples illustrate how this may be done.

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

Page 103: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 103 / 116

Change LOC= above to demonstrate the need for being able to access the arguments

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

Page 104: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 104 / 116

AMODE 24

AMODE 31

possible problem AMODE 24

possible problem

AMODE 31 AMODE 31

definitely a problem16 MB line

AMODE 31 AMODE 31

AMODE 31 AMODE 31

OK

OK

OK

OK16 MB LINE

Page 105: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 105 / 116

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.

ExampleRTN1 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 CSECTRTN2 AMODE 24 ENTRY RTN2AD . BSM 0,14RTN2AD DC A(RTN2)

A CSECT A AMODE 31 A RMODE ANY

. . BSM 0,14

B CSECT B AMODE 24 B RMODE 24

LOAD EP=A ST 0,EPA

L 15,EPA BASSM 14,15

16MB LINE

Page 106: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 106 / 116

RTN3 CSECTRTN3 AMODE 31 ENTRY RTN3AD . BSM 0,14RTN3AD DC A(X'80000000+RTN3)

Effect of AMODE on QSAM macros.See the two samples below to illustrate what changes are needed to migrate a AMODE 24 application that uses QSAM macros to a AMODE 31 application.

The PRINT samplePRINT31 CSECT PRINT31 AMODE 31 PRINT31 RMODE ANY STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE GETMAIN RC,LV=LEN,LOC=BELOW LR 2,1 MVC 0(LEN,2),SYSPRINT OPEN ((2),OUTPUT),MODE=31 LTR 15,15 BNZ OPENERR LA 5,20 MVC OUTREC+1(132),=CL132'THIS IS A PRINT LINE.' LOOP PUT (2),OUTCARD BCT 5,LOOP CLOSE (2),MODE=31 L 13,SAVE+4 RETURN (14,12),,RC=0 OPENERR L 13,SAVE+4 RETURN (14,12),,RC=16 OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, X LRECL=137,BLKSIZE=1370,RECFM=VBA LEN EQU *-SYSPRINT SAVE DS 18F END

A sample that copies one QSAM PS file to another.QSAM31 CSECT QSAM31 AMODE 31 QSAM31 RMODE ANY STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LA 13,SAVE GETMAIN RC,LV=LENI,LOC=BELOW LR 2,1 MVC 0(LENI,2),INFILE GETMAIN RC,LV=LENO,LOC=BELOW

Page 107: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 107 / 116

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

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

Page 108: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 108 / 116

GETMAIN RC,LV=RDJL,LOC=BELOW LR 5,1 MVC 0(RDJL,5),RDJ * GETMAIN RC,LV=JFCBL,LOC=BELOW LR 10,1 MVC 0(JFCBL,10),JFCB STCM 10,B'0111',177(10) USING INFMJFCB,10 LA 4,176(10) STCM 4,B'0111',DCBEXLSA * USING DSTBLMAP,12 BAL 6,RDJFCB BAL 6,MDFYJFCB BAL 6,OPEN BAL 6,PROCESS BAL 6,CLOSE CLOSE (3),MODE=31 B RETURN * RDJFCB STCM 11,B'0111',1(5) RDJFCB MF=(E,(5)) LTR 15,15 BNZ NODD BR 6 NODD WTO 'FILEDD NOT SPECIFIED IN JCL' ABEND 901 * MDFYJFCB LA 12,DSNTBL MVC JFCBDSNM,DSNAME BR 6 * OPEN OPEN ((11),INPUT),TYPE=J,MF=(E,(5)) LTR 15,15 BNZ OPENERR BR 6 * CLOSE CLOSE (11),MODE=31 BR 6 * OPENERR WTO 'OPENERROR' L 13,SAVE+4 RETURN (14,12),,RC=16 * PROCESS WTO 'IN PROCESS' GET (11),BUFFER MVC OUTREC(80),BUFFER PUT (3),OUTCARD B PROCESS EOF BR 6 * RETURN L 13,SAVE+4 RETURN (14,12),,RC=0 * SAVE DS 18F

Page 109: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 109 / 116

* DSNTBL DC A(L'DS01) DS01 DC C'userid.FILE1' DC CL(45-L'DS01)' ' DS 0F * JFCB DS 44F JFCBPTR DC X'87' DC AL3(JFCB) JFCBL EQU *-JFCB BUFFER DS CL80 * RDJ RDJFCB (FILEDCB,INPUT),MF=L RDJL EQU *-RDJ * FILEDCB DCB DSORG=PS,MACRF=GM,DCBE=DCBED,EXLST=JFCBPTR, X DDNAME=INFILE FILDCBL EQU *-FILEDCB DCBED DCBE EODAD=EOF * OUTCARD DC AL2(137),AL2(0) OUTREC DC CL133' ' SYSPRINT DCB DDNAME=SYSPRINT,MACRF=PM,DSORG=PS, X LRECL=137,BLKSIZE=1370,RECFM=VB SYSPL EQU *-SYSPRINT DCBD DSORG=PS DSECT IEFJFCBN * DSTBLMAP DSECT DSNMLEN DS CL4 DSNAME DS CL44 DS CL1 END

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

Page 110: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 110 / 116

MIXED MODE PROGRAMMING WITH COBOL AND ASSEMBLER back

This first example is an Assembler program calling a COBOL program. There are many ways to prepare a COBOL / Assembler program.

Methods:-1. Prepare the COBOL program first into an object module. Then compile and link edit the Assembler program, making the COBOL object code available to the link edit step via SYSLIB.

2. Prepare the Assembler program as an object module. Then compile and link edit the COBOL program, making the assembler object code available to the link edit step via SYSLIB.

3. Prepare both the COBOL and Assembler programs as Object code. Then have a separate Link edit only job and use Linkage editor control statements to prepare the Load module, name the module and specify an Entry point.

The following illustrates method (1) and illustrates an Assembler program(TEST11) calling a COBOL sub program SUMCOB Use the following JCL to compile the COBOL program. The IGYWC procedure is supplied by IBM and will be available in the system.

Compile the COBOL source//userid1 JOB CLASS=C, // MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID // JCLLIB ORDER=(userid.PROCLIB) //COMPILE EXEC IGYWC //COBOL.SYSIN DD DSN=userid.COBOL.SOURCE(SUMCOB),DISP=SHR //COBOL.SYSLIN DD DSN=userid.COBOL.OBJECT(SUMCOB),DISP=SHR //

See your system for understanding the IGYWC procedure used for compiling a COBOL program. The IGYWCL procedure compiles and link edits a COBOL program.

Here is the assemble and run JCL//userid1 JOB CLASS=C, // MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID,REGION=0M // JCLLIB ORDER=userid.PROCLIB //STEP1 EXEC PROC=ASMACL //C.SYSIN DD DSN=userid.ASM.SOURCE(TEST11),DISP=SHR //L.SYSLMOD DD DSN=userid.LOADLIB(TEST11),DISP=SHR //L.SYSLIB DD DSN=userid.COBOL.OBJECT,DISP=SHR // DD DSN=CEE.SCEELKED,DISP=SHR//L.SYSIN DD * ENTRY asm-csect-name/* //STEP EXEC PGM=TEST12 //STEPLIB DD DSN=userid.LOADLIB,DISP=SHR // DD DSN=CEE.SCEERUN,DISP=SHR //SYSPRINT DD SYSOUT=* //

This COBOL program SUMCOB is called from an assembler module

Page 111: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 111 / 116

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

Here is the assembler version of SUMCOB , doesn’t make a difference from the COBOL version.SUMCOB CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4

Page 112: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 112 / 116

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

The following Illustrates Method (2) with a COBOL program calling an Assembler programFirst Compile the Assembler program//userid1 JOB CLASS=C, // MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID,REGION=0M // JCLLIB ORDER=userid.PROCLIB //STEP1 EXEC PROC=ASMAC //C.SYSIN DD DSN=userid.ASM.SOURCE(SUMASM),DISP=SHR //C.SYSLIN DD DSN=userid.ASM.OBJECT(SUMASM),DISP=SHR //

Then you run this JCL that compiles the COBOL program, link edits it with the Assembler code and runs it.//userid1 JOB CLASS=C, // MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID // JCLLIB ORDER=(userid.PROCLIB) //COMPILE EXEC IGYWCL //COBOL.SYSIN DD DSN=userid.COBOL.SOURCE(TEST11CB),DISP=SHR //LKED.SYSLMOD DD DSN=userid.LOADLIB(TEST11CB),DISP=SHR //LKED.SYSLIB DD // DD DSN=userid.ASM.OBJECT,DISP=SHR //* //RUN EXEC PGM=TEST11CB //STEPLIB DD DSN=userid.LOADLIB,DISP=SHR // DD DSN=CEE.SCEERUN,DISP=SHR//

TEST11CB COBOL PROGRAM (Main) IDENTIFICATION DIVISION. PROGRAM-ID. TEST11CB. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-VARS.

Page 113: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 113 / 116

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

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

Method (3)Here compile the COBOL program SUMCOB into userid.COBOL.OBJECT. Compile the Assembler program TEST11 into userid.ASM.OBJECT. Then run the link edit and run Job shown below.

//userid1 JOB CLASS=C, // MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID //LKED EXEC PGM=HEWL,REGION=1024K //SYSLMOD DD DSN=userid.LOADLIB,DISP=SHR //SYSLIB DD DSNAME=CEE.SCEELKED,DISP=SHR //MYLIB DD DSN=userid.ASM.OBJECT,DISP=SHR // DD DSN=userid.COBOL.OBJECT,DISP=SHR //SYSPRINT DD SYSOUT=* //SYSLIN DD *

Page 114: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 114 / 116

INCLUDE MYLIB(TEST11) include card INCLUDE MYLIB(SUMCOB) include card ENTRY TEST11 entry card NAME TEST11(R) name card /* //GO EXEC PGM=TEST11//STEPLIB DD DSN=userid.LOADLIB,DISP=SHR// DD DSN=CEE.SCEERUN,DISP=SHR

Any Storage that is either statically defined in the assembler program, getmained or is a COM area can be shared with a COBOL program. Here is how a COBOL program can access a COM area defined in an Assembler program.

COBOL and COM Area IDENTIFICATION DIVISION. PROGRAM-ID. TEST12CB. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. LINKAGE SECTION. 01 LS-VAR-ONE. 03 ARG1 USAGE IS POINTER. 01 LS-VAR-TWO. 03 MSG PIC S9(4) COMP. 03 MSG-DATA PIC X(16). PROCEDURE DIVISION USING LS-VAR-ONE. PERFORM MAIN-PARA PERFORM END-PARA. MAIN-PARA. SET ADDRESS OF LS-VAR-TWO TO ARG1. MOVE 16 TO MSG MOVE "TEST12CB" TO MSG-DATA. END-PARA. STOP RUN.

TEST12C CSECT STM 14,12,12(13) BALR 12,0 USING *,12 ST 13,SAVE+4 LR 2,13 LA 13,SAVE ST 13,8(0,2) L 4,ACOM1 USING DCOM1,4 LA 1,=A(ACOM1) L 15,=V(TEST12CB) BALR 14,15 LA 5,MSG WTO TEXT=(5) SR 15,15 L 13,SAVE+4 L 14,12(0,13) LM 0,12,20(13) BR 14 SAVE DS 18F

Page 115: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 115 / 116

ACOM1 DC A(COM1) DCOM1 DSECT MSG DS AL2 DS CL16 COM1 COM DS CL128 COBOL ‘sees’ only 18 bytes END TEST12C

Page 116: Churchil Assembler

ASSEMBLY LANGUAGE - 25/09/2004 116 / 116

Recommended for Reference and further reading1. High level assembler for MVS & VM & VSE, Programmers Guide MVS & VM edition2. High level assembler for MVS & VM & VSE, Language Reference MVS & VM edition3. MVS Programming Assembler Services guide4. MVS Programming Assembler Services reference5. MVS assembly language by Mc.Quillen and Prince6. Assembly language programming for the IBM370 and compatible computers by Michael D. Kudlick.7. Advanced Assembler Language and MVS Interfaces by Carmine A. Cannatello

1 through 4 are IBM Manuals which are available for access at the IBM web site.