Assembler/Session 1 Course Title : ASSEMBLER LANGUAGE Duration CTS-PAC : 5 Half - DAYS Version 2.0 1 Assembler/Session 1 Objectives Objectives • Familiarize with IBM 370 Assembly Language CTS-PAC Version 2.0 2 Assembler/Session 1 COURSE SCHEDULE SESSION 1 Day 1 Introduction SESSION 2 Day 1 Addressing SESSION 3 Day 2 CTS-PAC Machine Instructions Version 2.0 3 Assembler/Session 1 COURSE SCHEDULE SESSION 4 Day 3 Program Sectioning SESSION 5 Day 3 Assembler Directives SESSION 6 Day 3 Writing a complete program SESSION 7 Day 4 Assemble and link program CTS-PAC Version 2.0 4 Assembler/Session 1 COURSE SCHEDULE SESSION 8 Day 4 SESSION 9 Day 5 CTS-PAC Macro Language Other Topics Version 2.0 5 Assembler/Session 1 Assembler Language SESSION 1 CTS-PAC Version 2.0 6 Assembler/Session 1 Objectives INTRODUCTION • An assembler language is a symbolic form of machine language • Assembler translates assembler language program to machine language • An assembler program consists of many statements • In general, one assembler language statement corresponds to one machine language instruction CTS-PAC Version 2.0 7 Assembler/Session 1 STATEMENT FORMAT 1 label 10 operation e.g.. INIT1 Objectives LA R5,4 16 operands 30 comments ;INITIALISE REGISTER 5 Rules for choosing labels: • maximum 8 characters • Alphabets, digits, @, #, $ • First character should not be a digit • label should begin in column 1 CTS-PAC Version 2.0 8 Assembler/Session 1 Col1 ….. ….. A B ANS CTS-PAC Objectives Sample program Col10 Col.16 L A ST 2,A 2,B 2,ANS DC DC DS F’15’ F’20’ F Version 2.0 9 Assembler/Session 1 STATEMENT FORMAT Objectives Operation • One of the 200 M/C instruction mnemonics (eg. MVC) Operand • can be a register or memory location Continuing a statement • Place any character in column 72 of the line to be continued • Continue the statement from column 16 of next line • Maximum 2 continuation lines for a statement CTS-PAC Version 2.0 10 Assembler/Session 1 STATEMENT FORMAT Objectives Comment Statement • * in column 1 • Any text in columns 2 - 71 Note : Fields separated by one or more blanks CTS-PAC Version 2.0 11 Assembler/Session 1 TYPES OF INSTRUCTIONS Objectives 1. Machine Instructions 2. Assembler Instructions (Directives) 3. Macro Instructions CTS-PAC Version 2.0 12 Assembler/Session 1 REGISTERS Objectives Registers are storage areas inside the processor Advantages: - No need to retrieve data from main storage (saves time) - Shared resource that allows inter communication between programs CTS-PAC Version 2.0 13 Assembler/Session 1 REGISTERS Objectives General purpose registers: * 16 registers available * Numbered 0 - 15 * Holds 32 bits (4 bytes) of data (1 Full word) Floating point registers: * 4 registers available * Numbered 0,2,4,6 * Holds 64 bits (8 bytes) of data Note : The registers 0, 1, 13, 14 and 15 are reserved for special purpose By IBM convention these registers are used for calling subprograms CTS-PAC Version 2.0 14 Assembler/Session 1 DATA REPRESENTATION Objectives Binary fields - Always fixed in length, either 2 or 4 bytes (Full word or Half word) - Negative numbers stored in 2’s complement form Examples: A DC H’295’ 01 27 B H’-75’ FF 35 DC CTS-PAC Version 2.0 15 Assembler/Session 1 2’s complement form Objectives How to identify a negative number? - Leading bit contains a 1 (In Hex 8 to F) How to convert to a negative number? -First switch the bits (1 to 0 , 0 to 1) -Finally add 1 CTS-PAC Version 2.0 16 Assembler/Session 1 Boundary requirements Objectives Full word – Should begin in a full word boundary (Achieved by aligning with 0F) Half word – Should begin in a half word boundary (Achieved by aligning with 0H) How to find: The starting address of Full word should end with 0, 4, 8 or C and Half words should end with 0, 2, 4, 6, 8, A, C or E CTS-PAC Version 2.0 17 Assembler/Session 1 DATA REPRESENTATION Objectives Characters - One byte (EBCDIC form) - Character representation of decimal digits is called Zoned Decimal (first nibble is zone and next is digit) Zone digit 0-9 +, - , blank CTS-PAC Version 2.0 Zone + Blank Code C, A,E,F D, B F 18 Assembler/Session 1 DATA REPRESENTATION Objectives Floating Point Numbers - Always fixed in length, 4, 8 or 16 bytes (Full word, double word, double double word) - Left most bit represents sign (0 - positive; 1 - negative) - Next 7 bits represent exponent - Remaining bytes represent the fraction CTS-PAC Version 2.0 19 Assembler/Session 1 DATA REPRESENTATION Objectives Decimal numbers ( Packed Decimal representation) - Each byte but the rightmost has 2 decimal digits (0-9) - The right most byte contains a digit in the left half and a sign indicator in the right Sign indicator: C- Positive D - Negative Example: 753 CTS-PAC - 753C Version 2.0 20 Assembler/Session 1 Objectives Addressing Operands • Register addressing • Base, displacement addressing • Base, index and displacement addressing CTS-PAC Version 2.0 21 Assembler/Session 1 INSTRUCTION FORMATS Objectives RR opcode R1 R2 SI opcode I2 B1 D1 SS opcode L B1 D1 B2 D2 SS opcode L1 L2 B1 D1 B2 D2 RX opcode R1 X2 B2 D2 RS opcode R1 R3 B2 D2 CTS-PAC Version 2.0 22 Assembler/Session 1 Addressing RX Operands: Objectives Implicit format: L 3,VAR Explicit format: L 3,100(0,12) Register Displacement Index reg Base reg CTS-PAC Version 2.0 23 Assembler/Session 2 Assembler Language SESSION 2 Addressing CTS-PAC Version 2.0 24 Assembler/Session 2 STORAGE DEFINITIONS Objectives Two ways to define fields : 1. Define a field and initialize the data in it using the DC assembler directive 2. Define a field without initializing using the DS assembler directive CTS-PAC Version 2.0 25 Assembler/Session 2 STORAGE DEFINITIONS Objectives Format: label {DS/DC} dtLn’value’ where : label d t Ln : Label used to name the field (optional) : Duplication factor (optional) : Type of data ( required) : The letter ‘L’ followed by the length of the field in bytes (optional) value : Represents the value enclosed in apostrophes CTS-PAC Version 2.0 26 Assembler/Session 2 STORAGE DEFINITIONS Objectives Examples: ALPHA FLDS H1 F2 F1 F3 DC DS DC DC DC DC C’ABC EF’ 3CL2 H’29’ F’-10’ X’03’ PL4’-72’ Note : for character constants truncation or padding is to the right and for almost all others it is to the left. CTS-PAC Version 2.0 27 Assembler/Session 2 STORAGE DEFINITIONS Objectives DC TYPES Type C X B F H E D L P Implied Length 4 2 4 8 16 - CTS-PAC Alignment Data Representation None None None Full word Half word Full word Double word Double word Character Hex digits Binary digits Binary Binary Floating point Floating point Floating point None Packed decimal Version 2.0 28 Assembler/Session 2 STORAGE DEFINITIONS Objectives Data Representation in other languages: Assembler FORTRAN Language DC Type C Character F, H Integer E Real D X, B P CTS-PAC Double Precision Logical N/A COBOL PASCAL Display COMP COMP-1 String Integer Real COMP-2 Real N/A COMP-3 Version 2.0 Boolean N/A BASIC String Integer Single precision Double Precision Hex N/A 29 Assembler/Session 2 STORAGE DEFINITIONS Objectives Literals • A literal is a constant preceded by an equals sign ‘=‘. • Can be used as a main-storage operand but not as a destination field of an instruction • Causes assembler to define a field that is initialized with the data specified • All constants defined by literals are put by the assembler in a literal pool, usually at the very end of the program (Unless changed by LTORG instruction) L CTS-PAC R4,=F’1’ Version 2.0 30 Assembler/Session 2 Objectives Exercise 1 Q 1 and Q2. 2.What will happen in the following cases DC CL5’123’ DC CL5’123456’ DC X’A1245’ DC XL2’A1245’ DC XL5’A1245’ DC F’19’ DC FL1’513’ CTS-PAC Version 2.0 31 Assembler/Session 2 Objectives EQU (Assembler directive) • The EQU statement is used to associate a fixed value with a symbol R4 EQU 4 DRBACK EQU OUT+25 CTS-PAC Version 2.0 32 Assembler/Session 2 ESTABLISHING ADDRESSABILITY Objectives • By establishing the addressability of a coding section, you can refer to the symbolic addresses defined in it in the operands of machine instruction • Assembler will convert the implicit addresses into explicit addresses (base - displacement form) CTS-PAC Version 2.0 33 Assembler/Session 2 ESTABLISHING ADDRESSABILITY Objectives To establish the address of a coding section : • Specify a base address from which the assembler can compute displacements • Assign a base register to contain this base address • Write the instruction that loads the base register with the base address Note: The base address should remain in the base register throughout the execution of the program CTS-PAC Version 2.0 34 Assembler/Session 2 ESTABLISHING ADDRESSABILITY Objectives Establishing Base Register The USING and DROP assembler instructions enable one to use expressions representing implicit addresses as operands of machine instruction statements, leaving the assignment of base registers and the calculation of displacements to the assembler USING - Use Base Address Register - allows one to specify a base address and assign one or more base registers CTS-PAC Version 2.0 35 Assembler/Session 2 ESTABLISHING ADDRESSABILITY Objectives To use the USING instruction correctly, one should know : • which locations in a coding section are made addressable by the USING statement • where in a source module you can use these established addresses as implicit addresses in instruction operands Format: symbol USING base address,basereg1| basereg2|,.. e.g. USING BASE,9,10,11 USING *,12 CTS-PAC Version 2.0 36 Assembler/Session 2 ESTABLISHING ADDRESSABILITY Objectives Range of a USING instruction: • The range of a USING instruction is the 4096 bytes beginning at the base address specified in the USING instruction Domain of a USING instruction • The domain of a USING instruction begins where the USING instruction appears in a source module to the end of the source module CTS-PAC Version 2.0 37 Assembler/Session 2 ESTABLISHING ADDRESSABILITY Objectives The assembler converts implicit address references into their explicit form: • if the address reference appears in the domain of a USING instruction • if the addresses referred to lie within the range of the same USING instruction Guideline: • Specify all USING instructions at the beginning of the source module • Specify a base address in each USING instruction that lies at the beginning of each control section CTS-PAC Version 2.0 38 Assembler/Session 2 RELATIVE ADDRESSING Objectives • Relative addressing is the technique of addressing instructions and data areas by designating their location in relation to the location counter or to some symbolic location ALPHA BETA LR CR BCR AR 3,4 4,6 1,14 2,3 ALPHA+2 or BETA-4 Note : Always avoid using relative addressing CTS-PAC Version 2.0 39 Assembler/Session 3 & 4 Assembler Language SESSION 3 & 4 Machine Instructions CTS-PAC Version 2.0 40 Assembler/Session 3 & 4 HANDLING CHARACTER DATA Objectives Move Character Instruction (MVC) • Copy data from one place in memory to another Format : MVC operand1,operand2 S1(L), S2 - implicit D1(L,B1),D2(B2) - explicit e.g... MVC CTS-PAC INPUT(5),OUTPUT Version 2.0 41 Assembler/Session 3 & 4 HANDLING CHARACTER DATA Objectives Move Immediate Instruction (MVI) • Can move only one byte of constant data to a field Format : MVI operand1,operand2 S1,I2 - implicit D1(B1),I2 - explicit e.g.. MVI CTS-PAC CTL,C’B’ Version 2.0 42 Assembler/Session 3 & 4 HANDLING CHARACTER DATA Objectives Advanced Techniques 1. Explicit lengths and relative addressing PAD MVC PAD+6(4),=CL4’ ‘ DS CL10 2. Overlapping fields and the MVC instruction MVC FLDB,FLDA FLDA DC C’A’ FLDB DS CL3 Limitation of MVC : Can only move 256 bytes CTS-PAC Version 2.0 43 Assembler/Session 3 & 4 HANDLING CHARACTER DATA Objectives Moving more than 256 characters: MVCL instruction Uses 2 pairs of even-odd pair of registers Format : MVCL R1,R2 (Both are even registers) Reg R1 – Address of destination R1+1 – Length Reg R2 - Source R2+1 – Padding character (1st 8 bits) and Length Eg: LA 2,Q LA 3,2000 LA 4,P LA 5,1500 MVCL 2,4 CTS-PAC Version 2.0 44 Assembler/Session 3 & 4 HANDLING CHARACTER DATA Objectives Comparison Instructions • Compares 2 values - the values are found in fields, in registers or in immediate data CLC - Compare logical character e.g. CLC FLDA,FLDB CLI - Compare logical immediate e.g. CTS-PAC CLI FLDA,C’K’ Version 2.0 45 Assembler/Session 3 & 4 Objectives Exercise 2 Q1 and Q2 2. What will be the effect of the following instructions : MVI OUTAREA,C’ ‘ MVC OUTAREA+1(132),OUTAREA OUTAREA CTS-PAC DS 133C Version 2.0 46 Assembler/Session 3 & 4 BINARY INSTRUCTIONS Objectives Three types of binary instructions •Full word •Half word •Register The Binary Move Instructions L, LH, LR ,ST, STH Type : R,X Register and indexed storage e.g... L 5,FULL LR 5,7 STH 7,HALF CTS-PAC Version 2.0 47 Assembler/Session 3 & 4 BINARY INSTRUCTIONS Objectives Note : Do not mix up the instruction types and field types e.g. RES LH 5,FULL - right half of Reg 5 gets 1st 2 bytes at FULL L 6,HALF - Reg 6 gets 4 bytes starting from HALF ST 3,RES DS H HALF DC H’15’ FULL F’8’ DC CTS-PAC - 4 bytes of reg 3 are stored starting from RES Version 2.0 48 Assembler/Session 3 & 4 BINARY INSTRUCTIONS Objectives Binary Addition (A, AH and AR) • Fixed-point overflow occurs when the sum will not fit in the receiving register • Type R-X e.g. A 5,FULL AH 6,HALF AR 7,3 CTS-PAC Version 2.0 49 Assembler/Session 3 & 4 BINARY INSTRUCTIONS Objectives Binary Subtraction (S, SH and SR) • Type R-X e.g. S 5,FULL SH 6,HALF SR 7,3 CTS-PAC Version 2.0 50 Assembler/Session 3 & 4 BINARY INSTRUCTIONS Objectives Binary comparisons (C, CH and CR) e.g. C 5,FULL CH 6,HALF CR 7,3 Condition code set as HIGH, LOW or EQUAL CTS-PAC Version 2.0 51 Assembler/Session 3 & 4 Objectives Binary Multiplication (M, MR, MH) Format : M op1,op2 op1 : An even numbered register; refers to an even-odd pair of registers (any register in case of half word format) op2 : storage area (full word/half word/register) CTS-PAC Version 2.0 52 Binary Multiplication (M, MR, MH) ... Function : The value in OP2 is multiplied by the value in the odd register of the even-odd pair and the result placed in even-odd registers (For half word format : The half word specified in OP2 is multiplied by the value in OP1 and result stored in OP1.) CTS-PAC Version 2.0 53 Assembler/Session 3 & 4 BINARY INSTRUCTIONS Objectives Binary Division (D, DR) Format: D Type R-X / R-R : op1,op2 Op1 : An even numbered register. It refers to an even-odd pair of registers. The pair holds the double word to be divided. The even register receives the remainder; the odd register receives the quotient. e.g. D CTS-PAC 4,FULL Version 2.0 54 Assembler/Session 3 & 4 BC and BCR Instructions • Objectives instructions that do or do not branch depending on the value of the condition code Format : BC M1,S2 BCR M1,R2 e.g. BC B’1001’,BRPTA will cause a branch to the instruction named BRPTA, if at the time the instruction is executed, the condition code is 0 or 3. CTS-PAC Version 2.0 55 Assembler/Session 3 & 4 BRANCHING Objectives A branch causes execution to continue at some other instruction in the program • Branch conditions : Arithmatic B, BZ,BP,BM, BNZ,BNP,BNM,BO,BNO • Comparison BH, BL, BE, BNH, BNL,BNE e.g : CLI FLDA,C’K’ BNL GOOD CTS-PAC Version 2.0 56 Assembler/Session 3 & 4 CONDITION CODE PROCESSING Objectives • • • condition code occupies 2 bits of PSW condition code is set by each of a number of instructions condition code is an extremely important intermediary between arithmetic instructions and conditional branch instructions • very important in implementing control structures CC Arithmetic Comparison 0 Zero First operand = Second operand 1 < Zero First operand < Second operand 2 >Zero First operand > second operand 3 Overflow Not set CTS-PAC Version 2.0 57 Assembler/Session 3 & 4 LPR, LNR and LCR Instructions Format: Objectives LPR,LNR or LCR R1,R2 LPR - Load positive register (Loads into R1 the absolute value of R2) LNR Load Negative register (Loads into R1 the negative of absolute value of R2) LCR Load complement register (Loads opposite sign of the value in R2) Note: R1 and R2 can be the same CTS-PAC Version 2.0 58 Assembler/Session 3 & 4 BIT MANIPULATIONS Objectives Operation S-I S-S R-R R-X OR OI OC OR O AND NI NC NR N Exclusive OR XI XC XR X e.g... OI FLDA,X’0F’ NR 5,7 X 9,FULL CTS-PAC Version 2.0 59 Assembler/Session 3 & 4 BIT MANIPULATIONS Objectives OR Second 0 First 0 1 1 0 AND 1 1 1 Second 0 1 First 0 0 0 1 0 1 Exclusive OR Second CTS-PAC 0 1 First 0 0 1 1 1 0 Version 2.0 60 Assembler/Session 3 & 4 BIT MANIPULATIONS Objectives Testing individual bits - Test under mask (TM) TM S1,I2 Function : The bits of S1 ( a single byte) are tested under the control of the mask in I2 and condition code is set as ‘all zeroes’, all ones’ or ‘mixed’ e.g. TM EMP,B’00000101’ BNM NEXT CTS-PAC Version 2.0 61 Assembler/Session 3 & 4 BIT MANIPULATIONS Objectives Bit Shifting Instructions SLL, SLDL Left logical SRL, SRDL Right logical (No condition code set) SLA, SLDA Left arithmetic SRA, SRDA Right arithmetic (Sign bit not affected and condition code set) e.g. CTS-PAC SLL 5,1 SRDA 4,5 Version 2.0 62 Assembler/Session 3 & 4 BIT MANIPULATIONS Objectives Bit Shifting Instructions Condition code setting for arithmetic shift instructions 0- Result is zero 1- Result is negative 2- Result is positive 3- Overflow generated Overflow is generated when a bit other than the sign bit is shifted out CTS-PAC Version 2.0 63 Assembler/Session 3 & 4 BIT MANIPULATIONS Translations • Objectives To translate from one bit combination to another Format : TR S1(L),S2 or S1,S2 S1 : The field whose data is to be translated S2 : A 256-byte translation table Function : The value of the original byte is used as a displacement into the translation table. The byte found there replaces the original byte. e.g. TR WORK,XTABLE If the source byte is x’40’ (Space), then the displacement into the table is 64. The value in the table at displacement 64 will be replacing the source. CTS-PAC Version 2.0 64 Assembler/Session 3 & 4 BIT MANIPULATIONS Translations Objectives 1 byte - 256 possible combinations x’00’,x’01’, x’02’, x’03’,…………..x’0F’ x’10’,x’11’,x’12’,…………………..x’1F’ ………………………………………….. x’F1’,x’F2’,x’F3’,…………………x’FF’ The table should start with replacement byte for x’00’ and end with replacement for x’FF’ CTS-PAC Version 2.0 65 Assembler/Session 3 & 4 BIT MANIPULATIONS (TRT) Objectives Translations - TRT (Translate and test register) -Similar to TR but the source is not changed -Table is searched similar to TR taking the displacement into the table -Usually employed for editing purposes -The characters we need to search will have non zeros (x’00’) but other characters will be x’00’. -Source is searched one character at a time from left to right -The first nonzero match in the table halts the instruction -Condition code is set to 1 if match found before last byte, 2 if found at the last and 0 if not found -Loads address of source operand if found in last 24 bits of register 1, value from the table into last bit of register 2. No bits are changed in both the registers CTS-PAC Version 2.0 66 Assembler/Session 3 & 4 BIT MANIPULATIONS (TRT continued) Objectives Translations - TRT (Translate and test register) This example searches for a period X’4B’ The period 4B is decimal 75. So the X’4B’ is placed at the 76th position in the table. (Any non zero character may be placed in the table Table should be declared as follows: TABLE DC 75X’00’ DC X’4B’ DC 180X’00’ CTS-PAC Version 2.0 67 Assembler/Session 3 & 4 Numeric Conversions Objectives 1. Conversion to binary (CVB) Format: CVB operand1,operand2 operand1 : Register operand2 : a double word (containing valid packed decimal number) e.g. CVB 5,DOUBLE Use : Character data -(PACK)->Packed decimal-(CVB)-> binary CTS-PAC Version 2.0 68 Assembler/Session 3 & 4 Numeric Conversions Objectives 2. Conversion from binary (CVD) Format: CVD operand1,operand2 operand1 : Register operand2 : a double word e.g. CVD 5,DOUBLE Use : Binary-(CVD)->Packed decimal-(UNPK)-> Character data CTS-PAC Version 2.0 69 Assembler/Session 3 & 4 Numeric Conversions Objectives 3. Conversion from Zoned decimal to packed (PACK) (SS instruction) Format: PACK operand1,operand2 operand1 : Packed decimal operand2 : Zoned Decimal e.g. CTS-PAC PACK PACKED(3),ZONED(5) Version 2.0 70 Assembler/Session 3 & 4 Numeric Conversions Objectives 4 Packed decimal to Zoned decimal (UNPACK) Format: UNPACK operand1,operand2 operand1 : Zoned decimal operand2 : Packed decimal e.g. CTS-PAC UNPACK ZD(5),PACKED(2) Version 2.0 71 Assembler/Session 3 & 4 Relation between CVD,CVB,PACK and UNPACK Objectives PACK CVB Binary in Register CTS-PAC CVD Packed Decimal Version 2.0 UNPK Input Zoned Decimal Output 72 Assembler/Session 3 & 4 Example code for Different conversions Objectives PACK PNUM(8),START(3) CVB 7,PNUM A 7,=F’1’ CVD 7,PNUM UNPK ANS(3),PNUM(8) … … START DC C’125’ ANS DS CL3 PNUM DS CTS-PAC D Version 2.0 73 Assembler/Session 3 & 4 Packed decimal operations Objectives SS format - OPCODE D1(L1,B1),D2(L2,B2) AP - Add packed SP - Subtract packed ZAP - Zero and add packed MP - Multiply packed DP - Divide packed CP - Compare packed Note: All these operations ignore the decimal places. You have to track the decimal places and edit it with ED and EDMK instructions CTS-PAC Version 2.0 74 Assembler/Session 3 & 4 Packed decimal operations Objectives Advanced instructions: SRP - Shift and Round packed OPCODE D1(L,B1),D2(B2),I3 First operand - Memory location including length Second operand - Direction and number of places to shift Third operand - Whether to round or not ------------------------------------------------------------------------Second operand, <= 32, left shift is done and 33 to 64 right shift is done. Number for right shift = ( 64 - number of digits to be shifted) (No rounding is involved in left shift CTS-PAC Version 2.0 75 Assembler/Session 3 & 4 Packed decimal operations Objectives Advanced instructions: (SRP continued) NUM is a 5 byte packed decimal number and contains 001234567C. What is the value in number after each of these instructions? 1. SRP NUM(5),2,0 2. SRP NUM(5),62,0 3. SRP NUM(5),62,5 4. SRP NUM(5),60,5 CTS-PAC Version 2.0 76 Assembler/Session 3 & 4 Packed decimal operations Objectives Advanced instructions: MVZ - Move Zone (Moves the first half of each byte) MVN - Move numeric (Moves the second half of each byte) MVO - Move with offset EG: Multiply A by 100 where value of A is 123 MVC TEMP(3),A MVN TEMP+2(1),=X’00’ MVZ TEMP+3(1),=X’00’ MVN TEMP+3(1),A+2 A DC PL3’123’ TEMP DS PL4 CTS-PAC Version 2.0 77 Assembler/Session 3 & 4 Editing the output for printing Objectives ED and EDMK instructions ( D1(L,B1), D2(B2)) (Pattern and PD number) … Patterns: … selector x’20’ - Digit x’21’ - Significance selector x’22’ - Field separator x’60’ - Sign indicator Pattern and the packed decimal number processed from left 1 byte at a time X 0 1 2 3 4 5 6 C (Instruction: ED P(12),X) Fill Character P 40 20 20 6B 20 21 20 4B 20 20 60 40 (Before execution) P 40 40 F1 6B F2 F3 F4 4B F5 F6 40 40 (After execution) number is positive) CTS-PAC 1 , 2 3 4 . 5 6 (Last 2 bytes spaces since Version 2.0 78 Assembler/Session 3 & 4 Editing the output for printing Objectives Values being examined Pattern PD digit byte When the Digit 0 significant selector indicator is off 1-9 Significanc 0 e starter 1-9 When the significant indicator is on CTS-PAC Action taken New pattern Fill character digit in EBCIDIC Fill character New state of SI Off On On Field seperator Any other byte Digit selector Significanc e starter None digit in EBCIDIC Fill character None Fill character Off 0-9 digit in EBCIDIC digit in EBCIDIC On Field seperator Any other byte None Fill character Off None Pattern byte not changed On 0-9 Version 2.0 On Off On 79 Assembler/Session 3 & 4 Editing the output for printing Objectives -ED and EDMK can detect the difference between significant and non signi ficant digits ie between leading and non leading zeros - Significance starter forces all subsequent digits to be considered significant -When significance indicator is off and detection of a significant digit turns it on, the address of that significant digit placed in 8-31 of register 1 by EDMK -EDMK allows a floating currency and/or algebraic sign but ED does not allow CTS-PAC Version 2.0 80 Assembler/Session 3 & 4 TABLE PROCESSING Objectives A table is a named storage structure consisting of subunits or entries e.g. RATE DS 6F L 4,RATE+8 Accessing table elements with indexed storage operands: e.g. LH 9,=F8’ L 5,RATE(9) (9 - index register) CTS-PAC Version 2.0 81 Assembler/Session 3 & 4 Multi-purpose branching instructions Objectives Convenient when counted repetition structure (table processing) is needed • Branch on count (BCT and BCTR) Format: BCT op1,op2 (R-X) Function: First the op1 value is decremented by 1. Second the branch is taken to the address specified in op2 only if the value in op1 is not 0. e.g. REPEAT LH 9,=H’12’ EQU * .. BCT CTS-PAC 9,REPEAT Version 2.0 82 Assembler/Session 3 & 4 • Branch on index high and branch on index low or equal (BXH and BXLE) Objectives Format: BXLE op1,op2,op3 BXH op1 : A register known as the index register op2 : A even-odd pair of registers Even register - increment register Odd register - Limit register op3 : A storage operand. This is the branch address. CTS-PAC Version 2.0 83 Assembler/Session 3 & 4 Function : First, the value in the increment Objectives register is added to the indexed register. Second, the branch is taken only when the value in the index register is ‘lower than or equal to’ / ‘higher than’ the value in the limit register Useful when the same register is to be used as the count and index register CTS-PAC Version 2.0 84 Assembler/Session 3 & 4 ‘DO UNTIL’ repetitions BXLE - BXH- ‘DO WHILE’ repetitions e.g... LH 7,=H’0’ index LH 2,=H’2’ increment amount LH 3,=H’18 the limit Objectives --REPEAT ... LH 6,TABLE(7) ... BXLE 7,2,REPEAT CTS-PAC Version 2.0 85 Assembler/Session 3 & 4 Objectives Load instructions with additional features • Load and Test (LTR) e.g... LTR 15,15 BNZ ERROR • Load Address (LA) LA R1,D2(X2,B2) CTS-PAC Version 2.0 86 Assembler/Session 3 & 4 USING EQUATES Objectives • To associate a fixed value with a symbol • Useful for length and relative address calculation e.g. TABLE DS 0H DC C’01 DC C’02’ ... TBLEND EQU * TBLSIZE EQU TBLEND-TABLE CTS-PAC Version 2.0 87 Assembler/Session 3 & 4 USING EQUATES Can be Objectives used for the following purposes: 1. To assign single absolute values to symbols. 2. To assign the values of previously defined symbols or expressions to new symbols, thus allowing you to use different mnemonics for different purposes. 3. To compute expressions whose values are unknown at coding time or difficult to calculate. The value of the expressions is then assigned to a symbol. CTS-PAC Version 2.0 88 Assembler/Session 5 Assembler Language SESSION 5 Program Sectioning CTS-PAC Version 2.0 89 Assembler/Session 5 Beginning and End of Source Modules Objectives • Code a CSECT segment before any statement that affects the location counter • END statement is required as the last statement in the assembly CTS-PAC Version 2.0 90 Assembler/Session 5 CONTROL SECTIONS Objectives •A source module can be divided into one or more control sections •A control section is the smallest subdivision of a program that can be relocated as a unit CTS-PAC Version 2.0 91 CONTROL SECTIONS • At coding time, establish the addressability of each control section within the source module, and provide any symbolic linkages between control sections that lie in different source modules. • Initiated by using the START or CSECT instruction CTS-PAC Version 2.0 92 Assembler/Session 5 CONTROL SECTIONS Objectives • Any instruction that affects the location counter, or uses its current value, establishes the beginning of the first control section. CTS-PAC Version 2.0 93 CONTROL SECTIONS Format of CSECT: Name Operation Any symbol CSECT Operand Not required or blank Note: The end of a control section or portion of a control section is marked by (a) any instruction that defines a new or continued control section, or (b) the END CTS-PAC instruction. Version 2.0 94 Assembler/Session 5 DUMMY SECTIONS Objectives • A dummy control section is a reference control section that allows you to describe the layout of data in a storage area without actually reserving any virtual storage. CTS-PAC Version 2.0 95 DUMMY SECTIONS • Use the DSECT instruction to initiate a dummy control section or to indicate its continuation. Format of DSECT: Name Operation Any symbol DSECT Operand Not required or blank CTS-PAC Version 2.0 96 Assembler/Session 5 DUMMY SECTIONS Objectives To use a dummy section : • Reserve a storage area for the unformatted data • Ensure that this data is loaded into the area at execution time Analogy: Cobol copybook CTS-PAC Version 2.0 97 DUMMY SECTIONS • Ensure that the locations of the symbols in the dummy section actually correspond to the locations of the data being described • Establish the addressability of the dummy section in combination with the storage area You can then refer to the unformatted data symbolically by using the symbols defined in the dummy section. CTS-PAC Version 2.0 98 Assembler/Session 5 ASMBLY2 BEGIN ATYPE CSECT BALR USING ... Objectives 2,0 *,2 Reg 3 points to data area LA USING CLI 3,INPUT INAREA,3 INCODE,C'A' BE ... MVC MVC ATYPE WORKA,INPUTA WORKB,INPUTB .. CTS-PAC Version 2.0 99 WORKA DS CL20 WORKB DS CL18 INPUT DS CL39 ... INAREA DSECT INCODE DS CL1 INPUTA DS CL20 INPUTB DS CL18 ... CTS-PAC END Version 2.0 100 Assembler/Session 5 Assembler Directives Objectives TITLE : To provide headings for each page of the assembly listing of the source modules. EJECT : To stop the printing of the assembler listing on the current page, and continue the printing on the next page. ORG : To reset the location counter CTS-PAC Version 2.0 101 Assembler Directives LTORG : A literal pool is created immediately after a LTORG instruction or, if no LTORG instruction is specified, at the end of the first control section. PRINT : To control the amount of detail to be printed in the listing of programs. PRINT CTS-PAC NOGEN / GEN Version 2.0 102 Assembler/Session 6 Assembler Language SESSION 6 Writing a complete program CTS-PAC Version 2.0 103 Assembler/Session 6 Program Entry and Exit Logic Objectives Program entry - Preserve register contents Program Exit - Restore register contents Register save area Always calling program provides a save area of 18 Full words long used for storage of registers Save area address passed through register 13 by IBM convention CTS-PAC Version 2.0 104 Assembler/Session 6 A register save area (18 consecutive full words) Word Objectives Address Contents 1 SAV 2 SAV+4 Address of calling program’s save area 3 SAV+8 Address of called program’s save area 4 SAV+12 Contents of Register 14 5 SAV+16 Contents of Register 15 6 SAV+20 Contents of Register 0 ... 18 SAV+68 CTS-PAC Contents of Register 12 Version 2.0 105 Assembler/Session 6 Responsibilities of called program Objectives Program entry conventions 1.Save contents of registers 0-12,14 & 15 in calling program’s save area 2.Establish base register 3.Store calling program’s save area in the 2nd word of its own save area CTS-PAC Version 2.0 106 Assembler/Session 6 Program entry conventions (contd..) Objectives 4. Store the address of its register save area in the third word of the calling program’s register save area (The addresses in the 3d word of save area establish a chain of register save areas. This will be useful in reading the dump when program crashes). CTS-PAC Version 2.0 107 Assembler/Session 6 Responsibilities of called program (contd..) Program Entry STM Objectives R14,R12,12(R13) BALR R12,0 USING *,R12 ST R13,SAVOWN+4 store calling programs save area LR R14,R13 LA ... R13,SAVOWN ST R13,8(R14) CTS-PAC Reg 13 contains current prog’s SA Version 2.0 108 Assembler/Session 6 Responsibilities of called program (contd..) Objectives Program Exit conventions 1. Restore registers 0-12 and 14 2. Place the address of the save area provided by the calling program in Reg 13 3. Place a return code in the low order byte of register 15 if one is required. Otherwise restore register 15. CTS-PAC Version 2.0 109 Assembler/Session 6 Responsibilities of called program (contd..) Objectives Program Exit L R13,4(R13) LM R14,R12,12(R13) BR R14 CTS-PAC Version 2.0 110 Assembler/Session 6 Responsibilities of calling program 1. Register 13 mustObjectives contain the address of a register save area. 2. Register 15 should be set to the beginning address of the subroutine L R15,=V(SUBENTRY) where SUBENTRY is the entry address (usually the CSECT name) of the subroutine CTS-PAC Version 2.0 111 Assembler/Session 6 Responsibilities of calling program (contd...) Objectives 3. Register 14 should have the return address 4. Register 1 should have the address of the parameter list A BALR instruction stores the address of the next instruction in the calling program into register 14 and transfers control to the called subroutine BALR R14,R15 CTS-PAC Version 2.0 112 Assembler/Session 6 Passing parameters to a subroutine Objectives • The standard interface requires that addresses of parameters be placed in a block of storage, and the address of the block be loaded into register 1 as the subroutine is called • Both input and output parameters are treated the same way e.g... ADDS CTS-PAC DC A(T) DC A(U) DC A(V) LA R1,ADDS Version 2.0 113 Assembler/Session 6 R1 Main storage Objectives Addr of parmlist Parmlist parm3 Addr of parm1 CTS-PAC Addr of parm2 parm1 Addr of parm3 parm2 Version 2.0 114 Assembler/Session 6 Called subroutine B may get the second parameter Objectives by L R3,4(,R1) L R8,0(,R3) CTS-PAC Version 2.0 115 Assembler/Session 6 Objectives Registers with special use R0 : Contains single word output of a subroutine R1 : contains the address of an area of main storage that contains addresses of parameters CTS-PAC Version 2.0 116 Assembler/Session 6 Objectives Registers with special use (contd...) R14 : Contains the return address, the address in the calling routine to which a subroutine should return control when finished R15 : contains the address of the entry point in the subroutine R13 : contains the address of an area in which register contents can be stored by a subroutine CTS-PAC Version 2.0 117 Assembler/Session 6 The subroutine RANDOM Objectives RANDOM STM R14,R12,12(R13) BALR R12,0 USING *,R12 RN CTS-PAC L R7,RN M R6,=F’65541’ ST R7,RN LR R0,R7 LM R1,R12,24(R13) BR R14 DC F’8193’ Version 2.0 118 Assembler/Session 6 Subroutine RDIGIT RDIGIT STM Objectives R14,R12,12(R13) BALR R12,0 USING *,R12 ST R13,SAV+4 LA R13,SAV ... L R15,RANDAD BALR R14,R15 ... L R13,SAV+4 LM R14,R15,12(R13) LM R1,R12,24(R13) BR R14 SAV DS 18F RANDAD DC A(RANDOM) CTS-PAC Version 2.0 119 Assembler/Session 6 Linkage Conventions Objectives •Program divided into 2 or more source modules •Source module divided into 2 or more control sections •For link-editing, a complete object module or any individual control section of the object module can be specified CTS-PAC Version 2.0 120 Assembler/Session 6 Communicating between program parts Objectives • To communicate between 2 or more source modules, symbolically link them together • To communicate between 2 or more control sections within a source module, establish proper addressability CTS-PAC Version 2.0 121 Assembler/Session 6 Establishing symbolic linkage Objectives • Identify external symbols in the EXTRN or WXTRN instruction or the V-type address constant • provide A-type or V-type address constants to reserve storage for addresses represented by external symbols • In the external source modules, identify these symbols with the ENTRY instruction (name entry of a START or CSECT instruction is automatically identified as an entry symbol) External symbol dictionary CTS-PAC Version 2.0 122 Assembler/Session 6 Establishing symbolic linkage (contd...) e.g. TABADR Objectives program A EXTRN TABLEB WXTRN TABLEB DS V(TABLEB) program B ENTRY TABLEB CTS-PAC DS TABLEB ... Version 2.0 123 Assembler/Session 6 Address Constants (A and V) Objectives • An address constant is a main storage address contained in a constant • A V-type constant is the value of an external symbol - a relocatable symbol that is external to the current control section. Used for branching to locations in other control sections e.g L 5,ADCON ADCON DC A(SOMWHERE) GSUBAD DC V(READATA) CTS-PAC Version 2.0 124 Assembler/Session 7 Assembler Language SESSION 7 Assemble and Link Program CTS-PAC Version 2.0 125 Assembler/Session 7 Processing of Instructions Objectives Assembler ENTRY Time/ M/C Activity instructions. Code source m/c Macro EXTRN Instr. DC,DS instruc. Preassembly Refer to macro instruc. Assembly object code LKED Prog fetch Execution data area form data area in load mod CTS-PAC Version 2.0 126 Assembler/Session 7 JCL ‘ parm’ processing Objectives EXEC PGM=pgmname,PARM= When program gets control : •Register 1 contains the address of a full word on a full word boundary in program’s address space •the high order bit of this full word is set to 1 (this convention is to indicate the last word in a variable length parameter list) CTS-PAC Version 2.0 127 JCL ‘ parm’ processing ... • Bits 1-31 of the full word contain the address of a 2-byte length field on a half word boundary • The length field contains a binary count of the no. of bytes in the PARM field which immediately follows the length field CTS-PAC Version 2.0 128 Assembler/Session 7 COBOL to Assembler Objectives CALL asmpgm USING COMM-AREA PL/I to Assembler DCL ASMSUB ENTRY OPTIONS(ASSEMBLER) CHARSTRING CHAR(25); CALL ASMSUB(CHARSTRING); Ref : PL/I Programming Guide, COBOL programming Guide CTS-PAC Version 2.0 129 Assembler/Session 8 Assembler Language SESSION 8 Macro Language CTS-PAC Version 2.0 130 Assembler/Session 8 Macros Objectives • Short source routines written and stored in libraries •Assembler inserts the source statements in the program where the macro appears CTS-PAC Version 2.0 131 Macro Definition Format : •A header statement •A prototype •Model statements •A trailer statement CTS-PAC Version 2.0 132 Assembler/Session 8 Header statement: Objectives MACRO Prototype: &name MOVE &TO,&FROM,&LENGTH Model statements: A set of machine and assembler instructions Trailer statement: &name CTS-PAC MEND Version 2.0 133 Assembler/Session 8 Macro Instruction: Objectives • A statement containing the name of a macro • when expanded, the symbolic parameters in the model statements are replaced by corresponding parameters from the macro instructions • symbolic parameters may be positional or keyword CTS-PAC Version 2.0 134 Macro Instruction ... MACRO &LABEL HALFSWAP &REG,&SV &LABEL ST &REG,&SV SLL &REG,8 IC &REG,&SV SLL &REG,8 IC &REG,&SV+1 MEND CTS-PAC Version 2.0 135 Assembler/Session 8 SET Symbols (global or local) 3 types : Objectives • arithmetic (SETA) • binary (SETB) • character (SETC) • SET symbols are declared using, LCLA LCLB LCLC GCLA GCLB GCLC CTS-PAC Version 2.0 136 Assembler/Session 8 Format: Label operation operands Objectives symbol-name SETA An expression SETB SETC e.g. LCLA &A1 GCLA &A2 &A1 SETA 1 &A2 SETA &A1+3 CTS-PAC Version 2.0 137 Assembler/Session 8 Attributes Objectives There are 6 attributes of a symbol or symbolic parameter : type, length, scaling, integer, count and number System variable symbols &SYSINDX, &SYSDATE, &SYSTIME, &SYSECT, &SYSPARM, &SYSLOC CTS-PAC Version 2.0 138 Assembler/Session 8 Conditional Assembly Objectives The assembler can be made to branch and loop among assembler language statements using sequence symbols and the assembler instructions AIF and AGO Sequence symbol : Period followed by 1 to 7 alphabets or digits of which the first is a letter e.g. .Z23Ab CTS-PAC Version 2.0 139 Assembler/Session 8 Format: Label Objectives Operation Operand seq symbol AGO or blank -do- AIF seq. symbol A logical expression enclosed in parenthesis, followed by seq symbol CTS-PAC Version 2.0 140 A logical expression is composed of one or more relations or values of SETB symbols connected by logical connects AND, OR, AND NOT, OR NOT A relation consists of 2 arithmetic expressions or 2 character expressions connected by a relational operator EQ, NE, LT, LE, GT, GE CTS-PAC Version 2.0 141 Assembler/Session 8 e.g. MACRO Objectives PSRCH &PARAMS,&STRING GBLB &FOUND LCLA &I &FOUND SETB 0 .LP AIF &I SETA &I+1 &FOUND SETB (‘&PARAMS(&I)’ EQ ‘&STRING’) ((&I GE N’&PARAMS) OR &FOUND) .E AGO .LP .E MEND CTS-PAC Version 2.0 142 Assembler/Session 8 Accessing QSAM files: Keywords in DCB parameter: Objectives DSORG PS RECFM F,FA,FB,FBA,V,VBA BLKSIZE Block length LRECL Record Length DDNAME Dataset name in JCL MACRF Macro Physical sequential GM - Get Move GL - Get Locate PM - Put Move PL - Put locate Move parameter directly puts the record in the storage area specified while Locate mode Loads the address of the record in Register 1 CTS-PAC Version 2.0 143 Assembler/Session 8 Accessing VSAM files: ACB macro AM - Objectives VSAM (For documentation) BUFND - No. of I/O buffers for data control intervals BUFNI - No. of I/O buffers for index control intervals BUFSP - Size of an area for data and Index I/O buffers DDNAME - Filename used in the DD statement. If omitted refers to the ACB macro name EXLST - Address to the EXLST macro. Generates a list of addresses for user routines MACRF - Types of processing the file will do CTS-PAC Version 2.0 144 Assembler/Session 8 Accessing VSAM files: ACB macro (Continued) EXLST options: AM - Objectives VSAM EODAD = (Address, A/N, L) (Load module) EXCPAD = (Address, A/N, L) (Load module) JRNAD = (Address, A/N, L) (Load module) LERAD = (Address, A/N, L) (Load module) SYNAD = (Address, A/N, L) (Load module) Active/No, Stored in load module CTS-PAC Version 2.0 145 Assembler/Session 8 Accessing VSAM files: RPL macro (Request parameter list) ACB - Address of the ACB macro Objectives AREA - Address of the work area to be used AREALEN - Length of the work area (Should be large enough to hold largest record in Move mode and at least 4 bytes in the Locate mode) RECLEN -Length of the records in the file (For VB you have to put the length before writing using MODCB) ARG - Label containing the key for the search (Key for KSDS, RRN for RRDS and RBA for ESDS) OPTCD - 5 sets of groups of parameters CTS-PAC Version 2.0 146 Assembler/Session 8 Accessing VSAM files: RPL macro (Continued) Options for OPTCD: Objectives KEY/CNV/ADR - Access by key,Control interval or Relative byte address SEQ/DIR/SKP - Sequential processing,Direct, Skip sequential FWD/BWD - Forward sequential processing,Backward ARD/LRD -Start seq.processing with ARG specified/ Backward processing from the last record NUP/NSP/UPD - No updating(Next rec not ready),No updating Next rec ready(DA only), Record updating) MVE/LOC - Move mode/ Locate mode CTS-PAC Version 2.0 147 Assembler/Session 8 Accessing VSAM files: OPEN - Open theObjectives file CLOSE - Close the file GET - Read a record PUT - Store a record ERASE - Delete a record POINT - Position for access Advanced macros: SHOWCB, TESTCB, MODCB CTS-PAC Version 2.0 148 Assembler/Session 9 Assembler Language SESSION 9 Other Topics CTS-PAC Version 2.0 149 Assembler/Session 8 Objectives Characteristics of good assembler program • has simple, easy to understand logic • uses mostly simple instructions • has no relative addressing • uses subroutines CTS-PAC Version 2.0 150 Characteristics of good assembler program ... • uses DSECTs • has efficient code (LA R10, 4(0,R10 - A R10,=F’4) • does not abnormally terminate due to user error • requests and check feedback from macro instructions • provides meaningful error messages CTS-PAC Version 2.0 151 Assembler/Session 8 Characteristics of good assembler program Objectives (contd..) • lets the assembler determine lengths • has opcodes, operand and comments aligned • contains meaningful comments • uses meaningful labels CTS-PAC Version 2.0 152 Assembler/Session 8 Structured Programming Objectives • To improve design and understandability of a program • made up of building blocks of subroutines Conventions for general purpose registers • Base registers • Link registers CTS-PAC Version 2.0 153 Assembler/Session 9 The EXecute Instruction Objectives • the EX instruction is a R-X type instruction that directs the execution of an instruction called the subject instruction, which is addressed by the second operand • the subject instruction is in effect a one-instruction subroutine CTS-PAC Version 2.0 154 The EXecute Instruction (contd...) •The subject instruction is modified before execution (though not altered at its main storage location) : bits 8-15 of the instruction ORed with bits 24-31 of register R1 to form the second byte of the instruction actually executed e.g. Let reg 9 have the length of string to be moved EX R9,VARMVC VARMVC MVC A(0),B CTS-PAC Version 2.0 155 Assembler/Session 9 DEBUGGING Objectives Exceptions and Interrupts Interrupts that result directly from attempts at invalid program execution are called program-check interrupts; identified by a code Interruption code 1 : Operation Interruption code 2 : Privileged operation Interruption code 4 : Protection Interruption code 5 :Addressing Interruption code 6 :Specification CTS-PAC Version 2.0 156 Assembler/Session 9 DEBUGGING Objectives Exceptions and Interrupts (contd..) Interruption code 7 : Data Interruption code 8 : Fixed-Point Overflow Interruption code 9 : Fixed-Point Divide Other Interruption codes ( 3, 10, 11, 12, 13, 14, 15) CTS-PAC Version 2.0 157 Assembler/Session 9 DEBUGGING Objectives Reading dumps • whenever a program abends an indicative dump is generated • The completion code is a code furnished by the O/S to designate the reason for the termination of the job step • In case of program check interruption, the first 2 digits of the completion code is 0C CTS-PAC Version 2.0 158 DEBUGGING Reading dumps ... • Locate the entry point of your program CTS-PAC Version 2.0 159 Assembler/Session 9 DEBUGGING Objectives Reading dumps (contd...) • The register contents are the contents at the point of interruption (the instruction that caused the interrupt is usually the one just before the interrupt address given) • use address at interrupt and entry address to locate the instruction that caused the programcheck interruption CTS-PAC Version 2.0 160 Assembler/Session 9 DEBUGGING Objectives Full and Partial dumps • //SYSUDUMP DD SYSOUT=A • SNAP macro CTS-PAC Version 2.0 161 DEBUGGING Reading the dump • SAVE AREA trace • P/P Storage • Examine register contents, PSW and listed entry point to find the portion of program being executed • Look at main storage dump to determine the data being used CTS-PAC Version 2.0 162 Assembler/Session 9 SYSTEM MACROS Objectives Data Management Macros DCB - Construct a data control block OPEN - Logically connect a dataset CLOSE - Logically disconnect a dataset GET - Obtain next logical record (queued access) PUT access) Write next logical record (queued READ - Read a block (basic access) WRITE (basic access) CTS-PAC - Write a block Version 2.0 163 Assembler/Session 9 SYSTEM MACROS Objectives Supervisor Services Macros ABEND - Abnormally terminate a task CALL - Pass control to a control section GETMAIN - Allocate virtual storage FREEMAIN - Free virtual storage LOAD - Bring a load module into virtual storage RETURN - return control to the calling program SAVE - Save register contents CTS-PAC Version 2.0 164 Assembler/Session 9 SYSTEM MACROS Objectives Supervisor Services Macros (contd) SNAP - Dump virtual storage and continue LINK - Pass control to a Program in Another load module WTO - Write to operator CTS-PAC Version 2.0 165 Assembler/Session 9 SYSTEM MACROS e.g. File I/O Objectives OPEN (INFILE,INPUT) GET INFILE,RECAREA PUT OUTFILE,RECAREA CLOSE (INFILE) INFILE DCB DSORG=PS,MACRF=GM,DDNAME=IFILE OUTFILE DCB DSORG=PS,MACRF=PM,DDNAME=OFILE (RECFM=,LRECL=,BLKSIZE=,) CTS-PAC Version 2.0 166 Assembler/Session 9 SYSTEM MACROS Three forms : Objectives Standard form : Results in instructions that store into an inline parameter list and pass control to the required program List form : Provides as out-of-line parameter list Execute form : Provides the executable instructions required to modify the out-of-line parameter list and pass control to the required program CTS-PAC Version 2.0 167 CTS-PAC Version 2.0 168