Assembler Training
Statement Format Position Position Position Position Position
1- 8 – Name 9 – Blank 10 -14 – Mnemonic Code 15 – Blank 16 Onwards – Operands
Multiple operands can be specified separated by commas Blank after operand indicates comment start
Statement Format Position 72 – Continuation Character
Any non-blank character ‘X’ is the most commonly used character
Position 73 – 80 – Sequence numbers for identification ‘*’ in Position 1 indicates a comment line
Statement Format Examples
Addressing Address is used to refer each byte in VIRTUAL Storage Maximum VIRTUAL Storage is 2GB – 231 Hence an Address on OS/390 is represented in a FULLWORD i.e. 4 bytes or 32 bits Where is the 1 bit missing?
Addressing In original MVS versions maximum virtual memory was 16MB – 224 (The LINE) From MVS/XA onwards this was enhanced to 2GB – 231 To provide backward compatibility, one bit was reserved
1 – indicates 31 bit addressing 0 – indicates 24 bit addressing
Addressing This addressing is also called AMODE
AMODE 24 and 31 AMODE goes hand-in-hand with where data is located/residing in virtual storage
This residency is called RMODE
RMODE 24 and ANY RMODE 24 forces data to reside below the line RMODE ANY causes data to reside below the line if storage available, else above the line
Possible AMODE/RMODE combinations
24/24, 31/24, 31/ANY 24/ANY not possible
Addressing Any location is always translated into base and displacement form Abs Addr = Base Addr + Displacement Establishing a base is also called ADDRESSABILITY Assembler requires to establish addressability, if items need to be addressed with location names
s IBM provides many types of S
General Purpose s (GPRs) Floating Point s (FPRs) Control s (CRs) Access s (ARs)
We will restrict to GPRs which are mainly used in application programming 16 GPRs – numbered 0 thru 15 Each GPR is 4 bytes long i.e. 32 bits
s Used as
Base s i.e. point to some base location Index s i.e. contain a value to index into, from base location
Now,
Abs Addr = Base Reg + Index Reg + Displacement
Machine Instructions Based on types of OPERANDS RR – - RX – -Index RS – -Storage SI – Storage-Immediate S – Storage SS1 – Storage-Storage Type 1 SS2 – Storage-Storage Type 2
Machine Instructions First byte of instruction has OPCODE (Operation Code) Following bytes are operands s (Base or Index) take 4 bits i.e. nibble i.e. half word Displacement requires 12 bits i.e. 3 nibbles Immediate operands require 1 byte i.e. 8 bits Length requires 1 byte (with exception od SS2 instruction type where 2 lengths are stored in 1 byte)
Machine Instructions
Data Types Hexadecimal Character Binary Halfword Fullword DoubleWord Address Absolute External Address Packed
X (1 Byte) C (1 Byte) B (1 Byte) H (2 Bytes) F (4 Bytes) D (8 bytes) A (4 Bytes) V (4 Bytes) P (1 Byte)
Data Types Each data type follows its boundary alignment Fullword, Address (External and Absolute) are aligned at FULLWORD boundary i.e. stored at an address divisible by 4 Halfword is aligned at HALFWORD boundary i.e. stored at an address divisible by 2 Character, Hexadecimal, Packed and Binary are aligned at byte boundary i.e. stored at an address divisible by 1 Doubleword is aligned at DOUBLEWORD boundary i.e. stored at an address divisible by 8
Data Definition DS – Define Storage
Label DS
X
DC – Define Constants
Label DC
C’1’
With DC an initial value can be specified Exact format is Label DS/DC Duplicator_Type_Modifier_Initial PGMNAME DC 1CL8’TESTPROG’
Duplicator – 1 Type – C for Character Modifier - L8 indicating length of 8 Initial – ‘TESTPROG’
Data Definition VAR1 DS C Define a character storage VAR2 DS C’A’ Define a character constant initialized with ‘A’ VAR3 DS CL10 Define a character storage of length 10 VAR4 DS 2CL10 Define 2 character storages of length 10 VAR5 DS FL1 Define a fullword storage of length 1
Data Definition Fullword is 4 bytes – Why Length 1 ? VAR1 DS C /*Start address 0000FF00*/ VAR2 DS F /*Start address 0000FF04*/
Assembler will insert 3 bytes to do the boundary alignment To avoid boundary alignment, specify the Modifier VARX DC C’ABC’ /*3 byte constant*/ Same as VARX DC CL3’ABC’
Assembler Program Start CSECT
Is an Assembler Instruction indicating start of an executable control section LABEL CSECT LABEL is equivalent to the PGMID in COBOL CSECT is aligned on a double word boundary Multiple CSECT can be mentioned in the same program CSECT ends at start of another CSECT or END statement
LOAD/STORE/MOVE/BRANC H Instructions LOAD – RX Type The LOAD instruction takes four bytes from storage or from a general and place them unchanged into a general purpose . Abbreviated as “L”. Instruction format: L R1,D2(X2,B2)
Examples of LOAD Instruction
L
R6,4(R5,R12) LOAD R6 FROM R5 ADDRESS + R12 ADDRESS + 4 L R14,FULLWORD LOAD R14 FROM "FULLWORD"
Various LOAD Instructions
LA (LOAD ADDRESS) LM (LOAD MULTIPLE) LH (LOAD HALFWORD) LR (LOAD )
LOAD ADDRESS – RX Type The LOAD ADDRESS instruction loads the address specified by the second operand into the general purpose specified by the first operand. Abbreviated as “LA”. Instruction format: LA R1,D2(X2,B2)
Examples of LA Instruction
LA R6,4(R5,R12) LOAD R6 WITH R5 ADDRESS + R12 ADDRESS + 4 LA R14,1(,R14) ADD 1 TO VALUE IN R14
LOAD MULTIPLE – RS Type The LOAD MULTIPLE instruction loads 1 or more s from consecutive fullword storage locations addressed by the second operand of the instruction. Abbreviated as “LM”. Instruction format: LM R1,R3,D2(B2)
Example for LM Instruction
LM R14,R12,12(R13) LOAD S 14 THROUGH 12 FROM 15 CONSECUTIVE WORDS AT ADDRESS IN R13 PLUS DECIMAL 12
LOAD HALFWORD – RX Type The LOAD HALFWORD instruction places unchanged a halfword from storage into the right half of a . The left half of the is loaded with zeros or ones according to the sign (leftmost bit) of the halfword. Abbreviated as “LH”. Instruction format: LH R1,D2(X2,B2)
Examples of LH Instruction LH R6,0(0,14) 14 contains 00 00 18 03. Locations 1803-1804 contain 00 20. After the instruction is executed, contains 00 00 00 20. If locations 18031804 had contained a negative number, for example, A7 B6, a minus sign would have been propagated to the left, giving FF FF A7 B6 as the final result in 6.
LOAD – RR Type The LOAD instruction copies a value from one general purpose into another. Any general purpose may be used as the R1 or R2 operands. Abbreviated as “LR”. Instruction format: LR R1,R2
Examples of LR Instruction
LR
R6,R5 COPY R5 INTO R6 LR R7,R7 COPY R7 INTO ITSELF
INSERT CHARACTER–RX Type The INSERT CHARACTER instruction inserts the single byte addressed by the second operand into the rightmost byte (bits 55-63) of the first operand . The remaining bytes of the first operand remain unchanged. Abbreviated as “IC” Instruction format: IC R1,D2(X2,B2)
Examples of IC Instruction
IC R11,=C' ‘ INSERT LITERAL CONSISTING OF A SINGLE BLANK INTO RIGHTMOST BYTE OF R11 IC R2,0(R3,R8) INSERT BYTE AT ADDRESS IN R3 + ADDRESS IN R8 INTO RIGHTMOST BYTE OF R2
INSERT CHARACTERS UNDER MASK – RS Type
The INSERT CHARACTERS UNDER MASK (ICM) instruction may be used to replace all or selected bytes in a general with bytes from storage and to set the condition code to indicate the value of the inserted field. Abbreviated as “ICM”. Instruction format: ICM R1,M3,D2(B2)
Examples for ICM Instruction
ICM R5,B'0111',FIELDA FIELDA: FE DC BA 5 (before): 12 34 56 78 5 (after):
12 FE DC BA
Condition code (after): 1 (leftmost bit of inserted field is one)
Example 2 for ICM
ICM 6,B'1001',FIELDB FIELDB: 12 34 6 (before): 00 00 00 00 6 (after):
12 00 00 34
Condition code (after): 2 (inserted field is nonzero with left- most zero bit)
STORE Instruction – RX Type The STORE instruction stores the rightmost four bytes of a general purpose (the R1 value) at a fullword location in main storage. Abbreviated as “ST”. Instruction format ST R1,D2(X2,B2)
Examples for ST Instruction
ST R6,4(R5,R12) STORE RIGHT 4 BYTES IN R6 AT R5 ADDRESS + R12 ADDRESS + 4 ST R14,FULLWORD STORE RIGHT 4 BYTES IN R14 AT "FULLWORD"
Various STORE Instructions
STH (STORE HALFWORD) STM (STORE MULTIPLE) STC (STORE CHARACTER) STCM (STORE CHARACTER UNDER MASK)
STORE HALFWORD – RX Type The STORE HALFWORD instruction stores the rightmost 2 bytes (bits 48-63) of a general purpose (the R1 value) into a 2 byte halfword in main storage. Abbreviated as “STH”. Instruction format: STH R1,D2(X2,B2)
Examples for STH Instruction
STH R2,0(,R4) STORE RIGHT MOST TWO BYTES OF R2 IN R4 STH R14,HALFWORD STORE 2 BYTES IN R14 IN "HALFWORD"
STORE MULTIPLE – RS Type The STORE MULTIPLE instruction stores the rightmost four bytes of one or more general purpose s at consecutive fullword storage locations addressed by the second operand of the instruction. Abbreviated as “STM”. Instruction format: STM R1,R3,D2(B2)
Example for STM Instruction
STM R14,R12,12(R13) STORE RIGHT HALF OF S 14 THROUGH 12 AT 15 CONSECUTIVE WORDS AT ADDRESS IN R13 PLUS DECIMAL 12
STORE CHARACTER– RX Type The STORE CHARACTER instruction stores bits 56-63 (rightmost byte) of the general purpose specified by the first operand at the second operand address. Abbreviated as “STC”. Instruction format: STC R1,D2(X2,B2)
Examples for STC instruction
STC R8,BYTE STORE RIGHTMOST BYTE OF R8 AT LABEL "BYTE" STC R14,4(,R6) STORE RIGHTMOST BYTE OF R14 4 BYTES PAST ADDRESS IN R6
STORE CHARACTER UNDER MASK – RS Type
The STORE CHARACTERS UNDER MASK instruction stores selected bytes from the first operand into Consecutive bytes addressed by the second operand. Abbreviated as “STCM”. Instruction format: STCM R1,M3,D2(B2)
Example for STCM Instruction
STCM
8,B'0111',FIELD3
8: 12 34 56 78 FIELD3 (before): not significant FIELD3 (after) : 34 56 78
MOVE Instructions Various MOVE Instructions are
MVC (MOVE CHARACTER) MVCIN (MOVE INVERSE) MVCL (MOVE LONG) MVI (MOVE IMMEDIATE) MVZ (MOVE ZONES) MVN (MOVE NUMBERIC)
MOVE CHARACTER– SS1 Type The MOVE CHARACTER instruction moves from 1 to 256 bytes from one main storage location to another. The storage locations may overlap each other. If the length operand is not explicitly specified in the first operand, the implicit length of the first operand symbol is used. Abbreviated as “MVC”. Instruction format: MVC D1(L1,B1),D2(B2)
Examples for MVC Instruction
MVC 10(256,R5),0(R5) MOVE 256 BYTES FROM R5 ADDRESS TO R5 PLUS 10 (DECIMAL) ADDRESS MVC TITLE(7),=C'1 ERROR‘ MOVE 7 BYTE LITERAL TO "TITLE" ADDRESS
MOVE INVERSE – SS1 Type The MOVE INVERSE instruction moves the bytes at the second operand location to the first operand location, simultaneously reversing the order of the bytes. After the MOVE INVERSE completes, the rightmost byte of the second operand is the leftmost byte of the first operand. Abbreviated as “MVCIN”. Instruction format: MVCIN D1(L1,B1),D2(B2)
Example for MVCIN Instruction
MVCIN 10(128,R3),0(R5) MOVE 128 BYTES AT ADDRESS IN R5 TO R3 ADDRESS +10 AND REVERSE THEIR ORDER
Note: R5 address should contain the the rightmost byte of the field to be moved.
MOVE CHARACTER LONG – RR Type MOVE CHARACTER LONG instruction moves from 1 to 2,147,483,647 bytes in main storage. Both operands must designate an even-numbered of an even-odd pair. The first operand even numbered contains the address of the receiving field. The first operand odd numbered contains the length of the receiving field.
MVCL The second operand even numbered contains the address of the sending field. The second operand odd numbered contains the length of the sending field in the right 3 bytes and an optional padding character in the leftmost byte. The padding character is used to pad the receiving field if the second operand length is less than the first operand length.
MOVE IMMEDIATE – SI Type The MOVE (MVI) instruction places one byte of information from the instruction stream into storage. The byte may be any type of constant or an expression that resolves to a value in the range 0 to 255. Abbreviated as “MVI”. Instruction format: MVI D1(B1),I2
Examples for MVI Instruction
MVI 10(R4),X'10' MOVE A X'10' TO R4+X'10‘ MVI SWITCH,C' ' MOVE A BLANK TO 'SWITCH‘
MOVE ZONE – SS1 Type The leftmost four bits of each byte(zone portion) in the second operand are placed in the leftmost four bit positions(zone portion) of the corresponding bytes in the first operand. The rightmost four bits of each byte in the first operand remain unchanged. Abbreviated as “MVZ”. Instruction format: MVZ D1(L1,B1),D2(B2)
Example for MVZ Instruction
MVZ 10(128,R3),0(R5) MOVE ZONE PORTION OF 128 BYTES FROM R5 ADDRESS TO R3 ADDRESS + 10
MOVE NUMERIC – SS1 Type The rightmost four bits of each byte(numeric portion) in the second operand are placed in the rightmost 4 bit positions(numeric portion) of the corresponding bytes in the first operand. The leftmost four bits of each byte in the first operand remain unchanged. Abbreviated as “MVN”. Instruction format: D1(L1,B1),D2(B2)
Example for MVN Instruction
MVN 10(128,R3),0(R5) MOVE NUMERICS OF 128 BYTES FROM R5 ADDRESS TO R3 + 10
BRANCH Instructions Various BRANCH Instructions
B (BRANCH) BC (BRANCH ON CONDITION) BCT (BRANCH ON COUNT) BCTR (BRANCH ON COUNT ) BAL (BRANCH AND LINK) BAS (BRANCH AND SAVE) BSM (BRANCH AND SET MODE) BASR (BRANCH AND SAVE ) BAKR (BRANCH AND STACK) BASSM (BRANCH AND SAVE AND SET MODE)
Unconditional BRANCH Instructions BRANCH (B) BRANCH (BR)
Conditional BRANCH Instructions BH or BHR BL or BLR BE or BER BO or BOR BP or BPR BM or BMR BZ
-
Branch on A High Branch on A Low Branch on A Equal B Branch on Overflow Branch on Plus Branch on Minus Branch on Zero
BRANCH Instruction Format
XXX XXXR XXX XXXXL
D2(X2,B2) R2 label label
where XXX is the mnemonic branch instruction
Examples for BRANCH Instruction
B 4(R15) UNCONDITIONAL BRANCH TO ADDRESS IN R15 + 4 BH LOOPA BRANCH TO "LOOPA" LABEL IF FIRST COMPARED OPERAND IS HIGH BR R1 UNCONDITIONAL BRANCH TO ADDRESS IN R1
BRANCH ON COUNT The BRANCH ON COUNT instruction is used to branch to a storage location whose address is specified by the second operand of the instruction, if the value in the first operand is non-zero after one is subtracted from it. Abbreviated as “BCT”. Instruction format: BCT R1,D2(X2,B2)
Examples for BCT Instruction
BCT R4,100(,R11) BRANCH TO ADDRESS IN R11 PLUS 100 BYTES IF R4 VALUE MINUS ONE IS NOT ZERO BCT R5,ENDOFILE BRANCH TO "ENDOFILE" LABEL IF R5 MINUS 1 IS NOT ZERO
BRANCH ON COUNT The BRANCH ON COUNT instruction is used to branch to a storage location whose address is specified by the second operand of the instruction, if the value in the first operand is non-zero after one is subtracted from it. Abbreviated as “BCTR”. Instruction format: BCTR R1,R2
Examples for BCTR Instruction
BCTR R4,R15 BRANCH TO ADDRESS IN R15 IF R4 VALUE MINUS ONE IS NOT ZERO BCTR R5,0 DECREMENT R5 BY 1, BUT DO NOT BRANCH
BRANCH AND LINK – RX Type The BRANCH AND LINK instruction causes program execution to branch to the address provided by the second operand. Linkage information is saved in the first operand after the branch address has been computed. When the R2 value specifies R0, no branch is taken. Linkage Information – Address of next sequential instruction, Instruction length code, Condition code etc. Abbreviated as “BAL”.
Instruction format: BAL R1,D2(X2,B2) Example for BAL Instruction
BAL R14,CALCVAL BRANCH TO "CALCVAL" LABEL- SAVE ADDRESS OF NEXT INSTRUCTION IN R14
BRANCH AND LINK – RR Type The BRANCH AND LINK instruction causes program execution to branch to the address in the second operand . Linkage information is saved in the first operand after the branch address has been computed. Abbreviated as “BALR”. Instruction format: BALR R1,R2
Example for BALR Instruction
BALR R14,R15 SAVE LINK INFO IN R14 AND BRANCH TO ADDRESS IN R15
BRANCH AND SAVE – RX Type Information from the current PSW, including the updated instruction address, is saved as link information at the first-operand location. Subsequently, the instruction address in the PSW is replaced by the branch address. In the RX format(BAS), the secondoperand address is used as the branch address. In the RR format(BASR), the contents of general R2 are used to generate the branch address; however, when the R2 field is zero, the operation is performed without branching.
Example for BAS Instruction
BAS R14,CALCVAL BRANCH TO "CALCVAL" LABEL - SAVE ADDRESS OF NEXT INSTRUCTION IN R14
Example for BASR Instruction
BASR R14,R15 BRANCH TO ADDRESS IN R15 - SAVE ADDRESS OF NEXT INSTRUCTION IN R14
Basic Assembler Program Start Program - CSECT Entry Housekeeping Instructions Processing Exit Housekeeping Instructions Data Definitions End program - END
Basic Assembler Program Entry Housekeeping Instructions USING
Used to establish Addressability USING LABEL/*, Indicates the specified now points to the given label and henceforth will be used as base for the area NOTE: Responsibility of the programmer to load with the correct address of the label If multiple s are pointing to an area i.e. used to establish base, then one with lowest offset is used A single base can provide addressability to 4K i.e. 4096 bytes (NOTE: 12 Bit displacement in Instructions) If need to access variables beyond 4K offset, multiple base s need to be used USING LABEL,Rx,Ry USING LABEL+4096,Ry
Basic Assembler Program
s are common resource and need to be preserved Caller has called us with some contents, need to save them IBM’s convention R15 – Points to Called Programs Address R14 – Caller’s Return Address R1 – Address of parameter list
Addressability needs to be established so that locations can be referenced Where to save ???? CALLER’s SAVEAREA SAVEAREA – An area in the CALLED Module
requiring 18F R13 points to SAVEAREA as per IBM’s convention
Basic Assembler Program
Basic Assembler Program Entry HouseKeeping
USING STM LR ST LR LA ST CALLER
TESTDCB,R12 R14,R12,12(R13) R12,R15 R13,SVAREA+4 R2,R13 R13,SVAREA R13,8(R2)
ESTABLISH R12 AS BASE REG SAVE CALLER'S REGS LOAD BASE REG, R15=CALLER ADDRESS SAVE CALLER SAVEAREA POINTER TEMPORARY LOAD CALLER SAVEAREA LOAD ADDRESS OF PROGRAM’S SAVEAREA SAVE PROGRAM SAVEAREA IN
Exit HouseKeeping
L LM L BR
R13,SVAREA+4 RESTORE CALLER SAVEAREA R14,R12,12(R13) RESTORE CALLER'S REGS R15,=F’0’ INITIALIZE RETURN CODE R14 BRANCH TO RETURN ADDRESS
Basic Assembler Program
TESTPROG CSECT USING TESTDCB,R12 ESTABLISH R12 AS BASE REG STM R14,R12,12(R13) SAVE CALLER'S REGS LR R12,R15 LOAD BASE REG, R15=CALLER ADDRESS ST R13,SVAREA+4 SAVE CALLER SAVEAREA POINTER LR R2,R13 TEMPORARY LOAD CALLER SAVEAREA LA R13,SVAREA LOAD ADDRESS OF PROGRAM’S SAVEAREA ST R13,8(R2) SAVE PROGRAM SAVEAREA IN CALLER --------------------------------------------------------L R13,SVAREA+4 RESTORE CALLER SAVEAREA LM R14,R12,12(R13) RESTORE CALLER'S REGS L R15,=F’0’ INITIALIZE RETURN CODE BR R14 BRANCH SVAREA DS 18F END TESTPROG
Basic Assembler Program Processing – I/O to PS
OPEN Macro Used to open a file OPEN (INFILE,INPUT,OUTFILE,OUTPUT) GET macro used to read one record GET INFILE,TEMPAREA PUT macro used to write one record PUT OUTFILE,OUTAREA CLOSE macro used to write one record CLOSE (INFILE,,OUTFILE) DCB macro used to define a file INFILE DCB DDNAME=INPFILE0, MACRF=(GM), DSORG=PS,LRECL=25,BLKSIZE=2500, RECFM=FB,EODAD=MAIN$015,SYNAD=ERRFILE MACRF – GM for GET and PM for Put EODAD – Indicates End Of File Routine name SYNAD – Indicates Error Analysis Routine Address
Basic Assembler Program MAIN$000
DS OPEN LTR BNZ GET PUT CLOSE
--------------MAIN$015
ERRFILE ERRCLOSE INFILE
DS STH STH PUT CLOSE LTR BNZ B ABEND ABEND DCB
OUTFILE
DCB
0H (INFILE,INPUT,OUTFILE,OUTPUT) OPEN THE INPUT & OPTPUT FILES R15,R15 Q. OPEN SUCCESSFUL? ERROPEN A. NO, PROCESS OPEN ERROR INFILE,TEMPAREA READ THE INPUT FILE OUTFILE,TEMPAREA WRITE THE OUTPUT FILE (INFILE,,OUTFILE) CLOSE THE INPUT AND OUTPUT FILES
0H R6,OUTAREA+64 STORE THE NUMBER OF TRAILERS R9,OUTAREA STORE THE TOTAL REC LEN IN RDW OUTFILE,OUTAREA WRITE THE OUTPUT FILE (INFILE,,OUTFILE) CLOSE THE INPUT AND OUTPUT FILES R15,R15 Q. CLOSE SUCCESSFUL? ERRCLOSE A. NO, PROCESS CLOSE ERROR RETURN A. YES, EXIT THE PROGRAM 500,DUMP 500,DUMP DDNAME=INPFILE0,MACRF=(GM),DSORG=PS,LRECL=25, BLKSIZE=2500,RECFM=FB,EODAD=MAIN$015,SYNAD=ERRFILE DDNAME=OUTFILE0,MACRF=(PM),DSORG=PS,LRECL=300, BLKSIZE=2500,RECFM=FB,EODAD=MAIN$015,SYNAD=ERRFILE
X
X X
BIT Manipulation Instructions AND (N) AND IMMEDIATE (NI) OR (O) OR IMMEDIATE (OI) EXCLUSIVE OR (X) EXCLUSIVE OR IMMEDIATE (XI)
AND The AND instruction ANDs the contents of the four bytes addressed by the second operand with the contents of the first operand . The logical AND function is applied bit by bit; a bit in the first operand is set to one if both corresponding bits in the first and second operands are one. Abbreviated as “N”. Instruction format: N R1,D2(X2,B2)
AND function table 2nd Operand Bit Values 0 1 +--------+--------+ | | | 0| 0 | 0 | 1st | | | Operand +--------+--------+ Bit | | | Values 1| 0| 1 | | | | +--------+--------+
Examples for AND Instruction
N R3,1000(R2,R6) AND VALUE IN R3 WITH 4 BYTES AT R2 ADDRESS + R6 ADDRESS + 1000 decimal N R7,=F'32767' AND VALUE IN R7 WITH LITERAL 32,767
AND IMMEDIATE The AND instruction logically ‘ANDS' the contents of the one byte addressed by the second operand with the byte of data specified in the instruction. Abbreviated as “NI”. Instruction format: NI D1(B1),I2
Examples for NI Instruction
NI BYTE1,X'0F‘ AND VALUE AT BYTE1 WITH IMMEDIATE BYTE OF X'0F' NI 0(R10),255 AND VALUE AT R10 ADDRESS PLUS 0 WITH IMMEDIATE BYTE OF 255 DECIMAL
OR The O instruction performs a connective logical Boolean "OR" function between the 4 bytes in the specified by the first operand, and the 4 bytes in storage addressed by the second operand. Abbreviated as “O”. Instruction format: O R1,D1(X2,B2)
OR function table 2nd Operand Bit Values 0 1 +--------+--------+ | | | 0| 0 | 1 | 1st | | | Operand +--------+--------+ Bit | | | Values 1| 1| 1 | | | | +--------+--------+
Examples for OR Instruction
O R3,0(,R6) "OR" R3 WITH 4 BYTES AT ADDRESS IN R6 O R12,=X'00FF00FF' "OR" R12 WITH 4 BYTE HEXADECIMAL CONSTANT
OR IMMEDIATE The OI instruction performs a logical connective Boolean “OR" function between the byte addressed by the first operand, and the byte of immediate data specified by the second operand. Abbreviated as “OI”. Instruction format: OI D1(B1),I2
Examples for OI Instruction
OI 0(R4),X'40' "OR" BYTE ADDRESSED BY R4 WITH HEX LITERAL OI FLAGBYTE,X'80' "OR" "FLAGBYTE" WITH A X'80' (DECIMAL 128)
EXCLUSIVE OR The EXCLUSIVE OR instruction performs a logical Boolean exclusive "OR" function between the 4 bytes in the right half of the specified by the first operand, and the 4 bytes in storage addressed by the second operand. Abbreviated as “X”. Instruction format: X R1,D1(X2,B2)
EXCLUSIVE OR function table 2nd Operand Bit Values 0 1 +--------+--------+ | | | 0| 0 | 1 | 1st | | | Operand +--------+--------+ Bit | | | Values 1| 1| 0 | | | | +--------+--------+
Examples for EXCLUSIVE OR Instruction
X R3,0(,R6) EXCLUSIVE "OR" R3 WITH 4 BYTES AT ADDRESS IN R6
X R12,=X'00FF00FF' EXCLUSIVE "OR" R12 WITH 4 BYTE HEXADECIMAL CONSTANT
EXCLUSIVE OR IMMEDIATE The EXCLUSIVE OR IMMEDIATE instruction performs a logical Boolean exclusive "OR" function between the byte addressed by the first operand, and the byte of immediate data specified by the second operand. Abbreviated as “XI”. Instruction format: XI D1(B1),I2
Examples for XI Instruction
XI 0(R4),X'40' EXCLUSIVE "OR" BYTE ADDRESSED BY R4 WITH HEX ITERAL
XI FLAGBYTE,X'80' EXCLUSIVE "OR" "FLAGBYTE" WITH A X'80' (DEC. 128)
SHIFT LEFT ALGEBRIC – RS Type The SHIFT LEFT ALGEBRAIC instruction left shifts the 31-bit numeric portion of the 32-bit signed value in the rightmost bits of the specified by the first operand. The number of bits to shift left are specified by the right six bits of the address specified by the second operand. The maximum shift amount is 63 decimal. Bits 0-31 of general R1 remain unchanged.
Condition code for SLA Condition code 0 is set if the resultant value after shifting is 0. Condition code 1 is set if the resultant value after shifting is less than 0. Condition code 2 is set if the resultant value after shifting is greater than 0. Condition code 3 is set if arithmetic overflow occurs.
The sign of the first operand remains unchanged. All 31 numeric bits of the operand participate in the left shift. Abbreviated as “SLA”. Instruction format:
SLA R1,D2(B2)
Examples for SLA Instruction If the contents of 2 are: 00 7F 0A 72 = 00000000 01111111 00001010 01110010 SLA R2,8(R0) Results in 2 being shifted left eight bit positions. Hence the new content is 7F 0A 72 00 = 01111111 00001010 01110010 00000000
SLA R10,12 SHIFT 31 BITS IN R10 LEFT 12 BIT POSITIONS
SHIFT LEFT LOGICAL – RS Type The SHIFT LEFT LOGICAL instruction left shifts the 32-bit value in the rightmost bits of the specified by the first operand. The number of bits to shift left are specified by the right six bits of the address specified by the second operand. Bits 0-31 of general R1 remain unchanged. Abbreviated as “SLL”.
For SLL, the first operand is in bit positions 32-63 of general R1. All 32 bits of the operand participate in the left shift. The condition code is not set by this instruction. Instruction format: SLL R1,D2(B2)
Example for SLL Instruction
SLL R12,22 SHIFT 32 BITS IN R12 LEFT 22 BIT POSITIONS
SHIFT RIGHT ARITHMETIC – RS Type The SHIFT RIGHT ALGEBRAIC instruction right shifts the 31-bit numeric portion of the 32-bit signed value in the rightmost bits of the specified by the first operand. The number of bits to shift right are specified by the right six bits of the address specified by the second operand. The maximum shift amount is 63 decimal.
The sign of the first operand remains unchanged. All 31 numeric bits of the operand participate in the right shift. Abbreviated as “SRA”. Instruction format: SRA
R1,D2(B2)
Condition code for SRA Condition code 0 is set if the resultant value after shifting is 0. Condition code 1 is set if the resultant value after shifting is less than 0. Condition code 2 is set if the resultant value after shifting is greater than 0.
Example for SRA instruction
SRA R10,12 SHIFT 31 BITS IN R10 RIGHT 12 BIT POSITIONS
SHIFT RIGHT LOGICAL – RS Type The SHIFT RIGHT LOGICAL instruction right shifts the 32-bit value in the rightmost bits of the specified by the first operand. The number of bits to shift right are specified by the right six bits of the address specified by the second operand. The maximum shift amount is 63 decimal. All 32 bits of the operand participate in the right shift.
Abbreviated as “SRL”. Instruction format SRL R1,D2(B2)
Example for SRL Instruction
SRL R10,12 SHIFT 32 BITS IN R10 RIGHT 12 BIT POSITIONS
Arithmetic Instructions ADD (A) SUBTRACT (S) MULTIPLY (M) DIVIDE (D)
ADD – RX Type The ADD instruction algebraically adds the value addressed by the second operand to the contents of the first operand . Abbreviated as “A”. Instruction format A R1,D2(X2,B2)
Examples for ADD Instruction
A R3,24(R5,R12) ADD CONTENTS AT R5 ADDRESS + R12 ADDRESS + 24 TO R3
A R14,FULLWORD ADD "FULLWORD" TO R14 A R0,=F'1' ADD 1 TO R0
Condition Code after ADD Condition code 0 is set if the result of the add is 0. Condition code 1 is set if the result of the add is less than 0. Condition code 2 is set if the result of the add is greater than 0. Condition code 3 is set if overflow occurs.
ADD – RR Type The ADD instruction algebraically adds the value in the second operand to the contents of the first operand . Abbreviated as “A”. Instruction format AR R1,R2
Examples for AR Instruction
AR R3,R2 ADD QUANTITY IN R3 TO R2
AR R8,R8 ADD VALUE IN R8 TO ITSELF
SUBTRACT – RX Type The SUBTRACT instruction subtracts the value addressed by the second operand from the contents of the first operand . Abbreviated as “S”. Instruction format: S R1,D2(X2,B2)
Examples for SUBTRACT Instruction
S
R3,24(R5,R12) SUBTRACT CONTENTS AT R5 ADDRESS + R12 ADDRESS + 24 FROM R3
S
R14,FULLWORD SUBTRACT "FULLWORD" FROM R14
S
R0,=F'1' SUBTRACT 1 FROM R0
SUBTRACT – RR Type The SUBTRACT instruction subtracts the value in the second operand from the contents of the first operand . Abbreviated as “SR”. Instruction format: SR R1,R2
Examples for SR Instruction
SR R3,R2 SUBTRACT CONTENT IN R2 FROM R3
SR R8,R8 SUBTRACT VALUE IN R8 FROM ITSELF (RESULT IS 0)
MULTIPLY – RX Type The MULTIPLY instruction multiplies the value in the odd-numbered of the first operand pair by the value in the word at the second operand address. The first operand must designate an even-odd pair. The initial contents of the even-numbered are ignored; the result of the multiplication occupies the first operand even-odd pair.
Abbreviated as “M”. Instruction format: M R1,D2(X2,B2) Examples for MULTIPLY Instruction
M R2,0(R5,R6) MULTIPLY VALUE IN R2 BY VALUE IN WORD AT ADDRESS IN R5 + ADDRESS IN R6 M R8,=F'100' MULTIPLY VALUE IN R9 BY LITERAL 100 (DECIMAL)
MULTIPLE – RR Type The MULTIPLY instruction multiplies the value in the oddnumbered of the first operand pair by the value in the second operand . The first operand must designate an even-odd pair. The second operand may designate any general purpose . Abbreviated as “MR”.
Instruction format: MR R1,R2 Examples for MR Instruction
MR
R2,R5
MULTIPLY VALUE IN R3 BY VALUE IN R5
MR
R8,R9
MULTIPLY VALUE IN R9 BY ITSELF (SQUARING VALUE)
DIVIDE – RX Type The DIVIDE instruction divides the fullword value addressed by the second operand (the divisor) into the 64-bit signed value designated by the first operand (the dividend). The first operand must specify the evennumbered of an even-odd pair. Abbreviated as “M”. Instruction format: D
R1,D2(X2,B2)
The leftmost 32 bits of the dividend are in bit positions 32-63 of the even-numbered general specified by the first operand, and the rightmost 32 bits of dividend are in bit positions 32-63 of the odd-numbered general associated with the first operand. After the division, the remainder (if any) and quotient are contained in the right halves of the even and odd numbered s, respectively. The left halves of the s remain unchanged.
Abbreviated as “D”. Instruction format: D
R1,D2(X2,B2)
Example for DIVIDE Instruction
D R6,=F'300' DIVIDE VALUE IN R6-R7 BY A FULLWORD DECIMAL 300
DIVIDE – RR Type The DIVIDE instruction divides the fullword value in the second operand into the 64-bit signed value which the even-odd pair designated by the first operand contains. After the division, the remainder (if any) and quotient are contained in the even and odd numbered s, respectively. Abbreviated as “DR”.
Instruction format:
DR
R1,R2
Examples for DR Instruction
DR R6,R9 DIVIDE 64-BIT VALUE IN RIGHT HALVES OF S R6 & R7 BY FULLWORD VALUE IN R9
ZAP – SS2 Type The ZERO AND ADD PACKED instruction copies the packed field at the second operand address on top of the packed field at the first operand address. The second operand field must be in the packed format; the first operand field can be in any format. Zeros are used to fill in the first operand if it is longer than the second operand. Zero, -ve, +ve or decimal overflow condition code will be set.
Instruction Format: ZAP D1(L1,B1),D2(L2,B2)
ZAP – SS2 Type Example for ZAP Instruction: P1 DC P’-38460’ P2 DS PL4 : : ZAP P2,P1 Result : P2 : 00 38 46 0D Condition code 1 (-ve) is set.
MVN – SS1 Type The MOVE NUMERICS instruction moves the numeric portion (right half) of each byte at the second operand address to corresponding positions of the byes at the first operand address. Each operand is processed left to right. The storage locations may overlap each other. Instruction Format: MVN D1(L1,B1),D2(B2)
MVN – SS1 Type Example for MVN Instruction: P1 : F0 F1 F2 F3 F4 F5 P2 : C6 C7 C8 C9 : : MVN P1(4), P2 Result : P1 : F6 F7 F8 F9 F4 F5
MVZ – SS1 Type The MOVE ZONES instruction moves the zone portion (right half) of each byte at the second operand address to corresponding positions of the byes at the first operand address. Each operand is processed left to right. The storage locations may overlap each other. Instruction Format: MVZ D1(L1,B1),D2(B2)
MVZ – SS1 Type Example for MVZ Instruction: P1 :
F6 F7 F8 F9 F4 C5
MVZ P1+5(1),=C’0’ Result : P1 : F6 F7 F8 F9 F4 F5
MVO – SS2 Type The MOVE WITH OFFSET instruction moves the second operand to the left of and adjacent to the rightmost four bits of the first operand. The result is obtained as if the operands were processed right to left. When necessary, the second operand is considered to be extended on the left with zeros. If the first operand is too short to contain all of the second operand, the remaining leftmost portion of the second operand is ignored. Instruction Format: MVO D1(L1,B1),D2(L2,B2)
MVO – SS2 Type Example for MVO Instruction: P1 :
77 88 99 0C
MVO P1,=X’123456’ Result : P1 :
01 23 45 6C
SP – SS2 Type The SUBTRACT PACKED subtracts the packed field pointed to by the second operand address from the packed field pointed to by the first operand address. Both the first and second operand fields being manipulated can be up to 16 bytes long. Zero, -ve, +ve or decimal overflow condition code will be set.
Instruction Format: SP D1(L1,B1),D2(L2,B2)
SP – SS2 Type Example for SP Instruction: P1 DC P’-45’ : : SP P1,=P’1’ Result : P1 : 04 6D Condition code 1 (-ve) is set.
DP – SS2 Type The first operand (dividend) is divided by the second operand (the divisor). The resulting quotient and remainder are placed at the first-operand location. The operands and results are in the packed format. The length in bytes of the divisor (2nd operand packed field) must be less than 8 bytes, must also be less than the length in bytes of the dividend
Instruction Format: DP D1(L1,B1),D2(L2,B2)
DP – SS2 Type The result of the division replaces the first operand packed field. The quotient is placed leftmost in the first operand packed field, with the remainder placed rightmost. The length of the quotient is equal to the length of the dividend(L1) minus the length of the divisor(L2). The length of the remainder is equal to the length of the divisor (L2). The sign of the quotient is determined by the rules of algebra from the dividend and divisor signs. The sign of the remainder has the same value as the dividend sign. These rules hold even when the quotient or remainder is zero.
DP – SS2 Type Example for DP Instruction: FIELD1 : 01 23 45 67 8C FIELD2 : 32 1D DP FIELD1,FIELD2 Result : FIELD 1 (after): 38 46 0D 01 8C
MP – SS2 Type The product of the first operand (multiplicand) and the second operand (multiplier) is placed at the first-operand location. The operands and result are in the packed format. The length in bytes of the multiplier must be less than 8 bytes, and must also be less than the length in bytes of the multiplicand
Instruction Format: MP D1(L1,B1),D2(L2,B2)
MP – SS2 Type The multiplicand must have at least as many bytes of leftmost zeros as the number of bytes in the multiplier; otherwise, a data exception is recognized. This restriction ensures that no product overflow occurs. The product can't be bigger than 31 decimal digits, plus the sign. The leftmost decimal digit of the product will always be a zero. The multiplication is done using the laws of algebra, with the signs of both multiplicand and multiplier determining the sign of the product.
MP – SS2 Type Example for MP Instruction: P1 DC P’-38460’ P2 DC P’-321’ P3 DS PL5 : ZAP P3,P1 digits) MP P3,P2
(Multiplicand) (Multiplier)
(Extending the multiplicand
Result : P3 (after): 01 23 45 66 0C
SRP – SS2 Type
The first operand is shifted in the direction and for the number of decimal-digit positions specified by the second-operand address, and, when shifting to the right is specified, the absolute value of the first operand is rounded by the rounding digit, I3. Only the digit portion is shifted; the sign position does not participate in the shifting. Instruction Format: SRP D1(L1,B1),D2(B2),I3
D2 field specifies no. of positions to shift :
+ve shift values specify shifting to the left.
SRP – SS2 Type Example for SRP Instruction: FIELD 3 (before): 12 39 60 0D SRP FIELD3(4),64-3,5 Result : FIELD 3 (after): 00 01 24 0D
The rounding digit is added to the last digit shifted out (which is a 6), and the carry is propagated to the left. The sign is ignored during the addition.
CVD – RX Type The CONVERT TO DECIMAL instruction converts the 4-byte signed binary integer value in the rightmost half of the first operand to an equivalent 8-byte packed decimal value at the second operand address. The second operand must designate a doubleword on a doubleword boundary. If the integer is +ve, the rightmost four bits of the packed decimal result is encoded as B'1100'; if –ve, as B'1101'.
Instruction Format: CVD R1,D2(X2,B2)
CVD – RX Type Example for CVD Instruction: DWORD DC D’0’ R10 contains 00 00 0F 0F CVD R10,DWORD Result : DWORD: 00 00 00 00 00 03 85 5C
(+3855)
CVB – RX Type The CONVERT TO BINARY instruction converts the 8-byte packed decimal value at the second operand address to an equivalent signed binary integer in the first operand . The second operand must designate a doubleword on a doubleword boundary.
Instruction Format: CVB R1,D2(X2,B2)
CVD – RX Type Example for CVB Instruction: DWORD DS 0D DC PL8’25,594’ DWORD contains : 00 00 00 00 00 25 59 4C CVD R10,DWORD Result : R10 :
00 00 63 FA
PACK – SS2 Type The PACK instruction converts the second operand field from zoned to packed decimal format by "packing" it into the field at the first operand address. Up to 16 bytes can be packed at once. Numeric part of each byte of second operand field is copied to the first operand field, except for the last byte, where both halves are copied, but swapped.
Instruction Format: PACK
D1(L1,B1),D2(L2,B2)
PACK – SS2 Type Example for PACK Instruction: P1 DS PL3 : : PACK P1,=X’F1F2F3C4’ Result : P1 :
01 23 4C
UNPK – SS2 Type The UNPACK instruction converts the second operand field from packed to zoned decimal format by "unpacking" it into the field at the first operand address. Up to 16 bytes can be unpacked at once. Swapping of last byte nibbles occurs.
Instruction Format: UNPK D1(L1,B1),D2(L2,B2)
UNPK – SS2 Type Example for UNPACK Instruction: Z1 DS D : : UNPK Z1,=P’1234’ Result : Z1 :
00 00 00 F1 F2 F3 F4 C4
EDIT – SS1 Type The EDIT instruction "unpacks“ converts to zoned format) the packed field pointed to by the second operand address, using a "pattern" that resides at the first operand address. (corr. to Picture Clause in Cobol) Instruction Format: ED D1(L1,B1),D2(B2) Pattern consists of bytes that contain the following hex values: X'20' - digit selector X'21' - significance starter X'22' - field separator Fill - fill character (any printable character)
EDIT – SS1 Type
(contd.)
The first byte is called the Fill character The field separator identifies individual fields in a multiple-file editing operation. If either a digit selector or the significant starter is encountered it is replaced by The fill byte if the significance indicator is OFF The unpacked source digit if the significance indicator is ON If any other byte is encountered, it is Replaced by fill byte if significance indicator is OFF Remains unchanged if significance indicator
EDIT – SS1 Type
(contd.)
The significance indicator is set to OFF At the start of the editing operation OR After a field separator is encountered OR After a source byte is examined that has a plus code in the rightmost four bit positions. The significance indicator is turned on when A significant digit is encountered in the source OR The significant starter is encountered in the pattern
EDIT – SS1 Type
(contd.)
Example for ED Instruction PWORK DC X'4020206B212020' WORK DC P'6,456' WORK in packed format : 06456C ED PWORK,WORK WORK 0 6 PWORK (before)
4 5 6 20 20 6B 21 20 20
PWORK (after)
40 F6 6B F4 F5 F6
Result :
6 , 4 5 6
EDMK – SS1 Type
(contd.)
The Edit and Mark instruction is identical in function to ED, except that the address of the leftmost 'significant' digit of the result is inserted in 1 when EDMK completes execution, if a significant digit was found in the result. one is unchanged if no significant digit was found. Used to implement “floating” currency symbol Instruction Format: EDMK D1(L1,B1),D2(B2)
EDMK – SS1 Type
(contd.)
Always ensure that R1 points to (Significant Starter + 1) location. Example for EDMK Instruction: To insert $ before the leftmost significant digit: LA R1,PWORK+5 EDMK PWORK,WORK BCTR R1,0 MVI 0(R1),C'$' Result :
$6 , 4 5 6
MACROS What is a macro? And what are its uses?
Macro language is an extension of assembler language. It provides a convenient way to generate a sequence of assembler language statements many times in one or more programs. A macro definition is written only once with sequence of assembler statements and can be invoked any where in the program.
Macro Uses Uses
Simplifies the coding of programs Reduces the chance of programming errors Ensures that standard sequences of statements are used to accomplish the functions we want.