Sunteți pe pagina 1din 55

Basic HLASM Training

Assembler Programmers Song

Every bit is sacred, every bit is right. If a bit is wasted, I can't sleep at night. Every bit is gorgeous, every bit is free. Admire the shape it forges, in hex and BCD!
(July 2001 Dr Dobbs journal)

Introduction to HLASM
A computer can understand and interpret only machine language. Machine language is in binary form and, thus, very difficult to write. The assembler language is a symbolic programming language that you can use to code instructions instead of coding in machine language. The assembler will translate the symbolic assembler language into machine language before the computer can run your program.

Why We Need HLASM?


The assembler language lies closest to the machine language in form and content.
We need assembler To control the program closely, even down to the bit level. To write some specific routines that are not provided by other symbolic programming languages, such as COBOL, FORTRAN, or PL/I (system level programming). For high processing speed, low memory demands and the capacity to act directly on the systems hardware.

Why HLASM?!

COOL Facts . . .
98% of all instructions executed on the mainframe are written in Assembler! DFSORT, IEBGENER, ISPF, TSO and IMS all are written in Assembler Anything that is high-volume execution is written in Assembler Structured programming is possible! No more code filled with GOTOs Can write clean, readable and understandable code

COBOL & HLASM


CBL Source code
Compile

Advantages over COBOL


Faster execution time or response time. Less CPU usage. Directly converted to object code whereas COBOL needs to be converted to HLASM before converting to object code.

Assembler code HLASM

Machine Language

Advantages over HLASM


Easy to code and maintain.

HLASM Statement format


LABEL00
1 label

L
9 10 mnemonic 15 16

R2
oper1

VAR2
oper2

Load variable contents


comment

*
continuation marker

Position 1- 8 Name

Position 10 -14 Mnemonic Code


Position 15 Blank Position 16 Onwards Operands Multiple operands can be specified separated by commas

Blank after operand indicates comment start


Position 72 Continuation Character X is the most commonly used character Position 73 80 Sequence numbers for identification

* in Position 1 indicates a comment line


7

Sample from Ameriprise


L631010 START 0 PRIME (R11,R12),SAVE,REGEQ EJECT **************************************************************** * MAINLINE ***************************************X************************ USING MASTDSCT,R2 MASTER DSECT STM R1,R3,LINKLIST MVC TABLE1(116),0(1) TABLE L R2,TABLE1 ADDRESS OF MASTER CLI RECORDTY+1,X'20' BL MASTER ***-------------------------------------------------------------------* HISTORY OR SUMMARY RECORD ***------------------------------------X------------------------------OVRSUMRY DS 0H CLC RECORDLN(2),HEX00S L639102 BE CSQRTURN PUTMASTR DS 0H L R3,LINKLIST+8 WILL HAVE ADDR IF TRAN-MASTER LTR R3,R3 BZ NOHEADER NO HEADER TO ADD ON B TRANMSTR NOHEADER DS 0H LH R4,RECORDLN RLI HISTORY OR SUMMARY L R1,LINKLIST+4 ADDR OF DCB

General Purpose Registers


Register is a small amount of storage available on the CPU whose contents can be accessed more quickly than storage available elsewhere. 16 GPRs numbered 0 thru 15. Each GPR is 4 bytes long i.e. 32 bits.

GPRs can hold Data or a Address.


The general purpose registers are used in many of the data movement and arithmetic instructions.

Addressing
Address is used to refer each byte in VIRTUAL Storage. Two types of addressing 24-bit 31-bit

Range of address that can be accessed by 24-bit is 224 i.e. 16MB

(called as LINE).
Range of address that can be accessed by 31-bit is 231 i.e. 2GB

(called as BAR).

10

Addressing
To provide backward compatibility, one bit was reserved

1 indicates 31 bit addressing 0 indicates 24 bit addressing


Establishing a base is also called ADDRESSABILITY
USING INDSECT,R1 USING MAINBASE,R2 USING EXTRBASE,R3 Here R1 is the base register

Assembler requires to establish addressability, if items (copybook

elements or memory) need to be addressed with location names

11

USING directive
USING LABEL/*,REGISTER

Indicates the specified register now points to the given label and henceforth will be used as base for the area
NOTE: Responsibility of the programmer to load register with the correct address of the label A single base register can provide addressability to 4K i.e. 4096 bytes If need to access variables beyond 4K offset, multiple base registers need to be used

12

Data Addressability
Address
1000 1025

Memory area
000001CHRIS ANDREW10000CR 000002MARISA 20000DR 000003PATRICE 15000CR 000004SIMONS 10050CR 000005MARJOLAINE 13000DR 000006BALLENTINE 17000CR . . . 000007CHRISTOPHER 40000CR Rec. no. 1 Rec. no. 2

Layout (Acts as stencil)


INPRECD DSECT RECKEY DS CL06 NAME DS CL11 AMOUNT DS CL05 TYPE DS CL02

nnnn

Rec. no. n

Assume R4 contains 1000. In the above diagram to access the amount & type in 1st record, With addressability:
USING INPRECD, R4 LA R4,1000

Without addressability:
MVC DSPLYAMT(5),17(R4) MVC DSPLYTYP(5),22(R4)

MVC DSPLYAMT(5),AMOUNT MVC DSPLYTYP(2),TYPE

13

Disadvantages of not using Addressability


In the Previous slide, to access the amount & type we

have to manually calculate the displacement (values 17 & 24) from the start address i.e. 1000
In Future if the position of amount field changes then we

have to recode the program. But if addressability is used, only we need to change the copybook.

14

Code Addressability
SAMPGM12 CSECT USING *,R4 CREATE ADDRESSABILITY LR R4,R15 LOAD PGM START ADDR L R6,VAR1 BR R14 DC CL6SAMPLE DC CL6

200

VAR1 VAR2

By specifying VAR1, Assembler will internally convert this into BASE DISPLACEMENT form as follows: L L R6,VAR1 R6, 200(0,R4) Actual Instruction Base displacement form

Here R4 is the base register and 200 is the displacement from the start of the PGM.

15

ORG (Organize)
ISLMASTR DSECT BASE RLI COCODE DS DS DS 0CL196 F XL1 BASE TRAILER RECORD LENGTH COMPANY CODE *BINARY*

. . . . ORG BASE1 DS BASE 0CL156 BL1 XL2 BASE 1 TRAILER BASE 1 RECORD LENGTH LAST TRANSACTION CODE *BINARY*

BASE1RLI DS TRANCODE DS

. . . . ORG BASE2 DS BASE 0CL232 BL1 PL5 BASE 2 TRAILER BASE 2 TRAILER LENGTH *BINARY*

BASE2RLI DS TTDNET DS

TTD NET PURCHASE PAYMENTS-F&V*SIGNED*

. . . .

16

AMODE
AMODE parameter determines whether to recognize an address in 31-bit or in 24-bit AMODE 24, 31, ANY AMODE parameter can be coded as linkage parameter or in the source code itself. Example:
MYPGM78 AMODE 24 MYPGM78 RMODE 24 MYPGM78 CSECT

STM R14,R12,8(R13)

17

RMODE
RMODE parameter determines whether to load the program & data above or below 16MB RMODE 24, 31, ANY RMODE parameter like AMODE can be coded as linkage parameter or in the source code itself. 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

18

Data types
Data types Declaration Example

Hexadecimal Character Binary Halfword Fullword DoubleWord Address Absolute Packed

X (1 Byte) C (1 Byte) B (1 Byte) H (2 Bytes) F (4 Bytes) D (8 bytes) A (4 Bytes) P (1 Byte)

CODEX

DC X0203

TITLE
FLAG

DC CPOLICY NO.
DC B00010000

LENGTH DC 2H20

SAVEAREA DS 18F
FILELEN DS D

RECADDR DC A(FILELEN) AMOUNT DC PL2234

19

Procedure division in HLASM


CSECT is an Assembler Instruction indicating start of an executable control section LABEL CSECT LABEL is equivalent to the PGMID in COBOL CSECT ends at start of another CSECT or END statement

Note:

In most of the Ameriprise system programs, above CSECT is coded within a macro called PRIME (House keeping macro).

20

Program Structure
CSECT

Start Program - CSECT


Entry Housekeeping Instructions Processing Exit Housekeeping Instructions Data Definitions

Entry House keeping

Processing . . .

End program - END

Exit House Keeping


Data Definition END

21

Basic Assembler Program


Registers are common resource and need to be preserved Caller has called us with some register contents, need to save them Where to save ???? Callers SAVEAREA SAVEAREA an area in the CALLED module requiring 18F R13 points to SAVEAREA as per IBMs convention IBMs convention R15 points to called programs address R14 callers return address R1 address of parameter list

22

Save Area Structure


Program X calls Program P and Program P calls Program X Program P's SAVEAREA Contents 0 4 8 12 16 20 24 28 32 36 40 44 48 52 56 60 64 68 Used by PL/I Address of Caller's Savearea Address of Called Program's Savearea Register 14 Register 15 Register 0 Register 1 Register 2 Register 3 Register 4 Register 5 Register 6 Register 7 Register 8 Register 9 Register 10 Register 11 Register 12

Placed by P, after X called P Placed by Q, after P calls Q

Contents of Program P's Registers placed here by program Q after P Calls Q

23

Instruction Format
System/390 has mainly following instruction formats: RR, RS, RX, SI, SS1, and SS2 type instructions. The formats differ in the addressing characteristics whether operands are in registers, in the instruction itself, or in main storage addressed by base and displacement or by base, index, and displacement. Because of the variation in space required, some instructions occupy two bytes of storage, others are four bytes long, and still others are six bytes long.

24

Instruction Format (Contd.)

In all System/390 instructions the first one or two bytes are the operation code, which indicates the length of the instruction and the type of operation to be perform. Although the 390 instruction set is rich, the formats are straightforward and make reasonably efficient use of instruction length. Both register and memory references are used, in various combinations, and two op code lengths are employed.

25

RR Type Instructions (2 Bytes)


RR Type Instructions: Both operands in these instruction are in registers. The instruction is therefore two bytes long.
OPCODE R1 R2

ALR R14, R15

OPCODE

R1, R2

The length of the RR type instruction is 2 bytes Opcode 1 byte R1 4 bits R2 4 bits RR type of instructions has both the source and destination as Registers hence they are called RR.

26

RS Type Instructions: (4 Bytes)


The first operand is a register R1 and the second operand is located in main storage, with address specified by base B2, and a displacement D2. The third operand is a register operand R3.
OPCODE LM R1 R3 B2 D2 ; OPCODE R1,R3,D2(R2)

14,12,12(13)

This above instruction loads the registers from R14,R15,R0,R1.R12 with the values from location R13+12, R13+16, R13+20 . Length of this type of instructions is 4 bytes Opcode 8 bits R1 4 bits R3 4 bits B2 4 bits D2 12 bits Generally LM (load multiple), STM (store multiple) instructions are frequently used from this type. In RS type (Storage to Register) instruction the source is storage and the destination is a register. Storage can be addressed either explicitly or implicitly. These kinds of instructions are generally used in loading the values from storage to registers.
27

RX Type Instructions: (4 Bytes)


The first operand is a register and the second operand is located in main storage. Its address is specified by a base B2, index X2 and a displacement given in bits 20-31 of the instruction.
OPCODE L R1 X2 B2 D2 R1,D2(X2,B2)

R8,4(R4,R5)

; OPCODE

This instruction loads the value in to destination R8 from the address pointed by = contents of R5 + contents of R4 + displacement (4). Length of this type of instruction is 4 bytes Opcode 1 byte R1 4 bits X2 4 bits B2 4 bits D2 12 bits If index register is not required in this type of instruction then X2 component is denoted as 0, then index register is be ignored. The address pointed is calculated with Base and displacement. Effective address in RX type is Effective Address =Base Address + displacement + index Address The index register consists of bits 8 through 31 of the register designated by the X2 field These type of instructions are generally used in Loop conditions where the change in value is given in the indexed register.
28

SI Type Instructions: (4 Bytes)


The first operand is in main storage, with address specified by base B1 and displacement D1. The second operand is the eight-bit immediate operand I2.
OPCODE MVI 4(R5),CA I2 B1 D1 D1(B1), I2

; OPCODE

This instruction loads the byte location pointed to by address = contents of R5 + displacement (4) , with the character A. The value of A in EBCDIC format is 0xC1. The length of this type of instructions is 4 bytes Opcode 1 byte I2 1 byte B1 4 bits D1 12 bits Two operands: Storage, Immediate data SI type (Storage to Immediate) Immediate data is meant to give the value directly to the instruction. These kinds of instructions are used to transfer values into Storage area (in the above example: the character in immediate operand is stored in some location and is moved into the storage area, but we dont know where the character A has been stored).
29

SS1 Type Instructions: (6 Bytes)


Both operands are in main storage, the first operand is S1+D1, the second operand is B2+D2, the value of L plus 1 indicates the operand length.
OPCODE L B1 D1 B2 D2

CLC 5(2,R2),2(R3)

; OPCODE D1(L,B1),D2(B2)

The above logical character compare instruction compares 2 (length) characters at address = contents of R2 + displacement (5) with the address = contents of R3 + displacement (2) Length of this type of instruction is 6 bytes. Opcode 1 byte L 1 byte B1 4 bits D1 12 bits B2 4 bits D2 12 bits Two operands: destination storage with length and source storage. Length is given only in destination field and is 8 bit unsigned integer. Maximum possible length can be 255 (28-1). If the length is not mentioned the assembler takes length as 1. Length given as 1 is taken as 1 SS 1 type of instructions is used in moving the fixed number of bytes from source to destination.
30

SS2 Type Instructions: (6 Bytes)


Both operands are in main storage, the first operand is S1+D1, the second operand is B2+D2. Length can be specified for both Source (L1) and destination(L2)
OPCODE L1 L2 B1 D1 B2 D2

AP 10(5,R2),9(3,R3)

; OPCODE D1(L1,B1),D2(L2,B2)

This above Add Packed instruction adds a Packed Decimal of length 3bytes from address = contents of R3 + displacement (9) ; with another Packed Decimal of length 5 bytes from address = contents of R2 + displacement (10) and the result after addition is stored in this place. The length of this type of instruction is 6 bytes. Opcode 1 byte L1 4 bits L2 4 bits B1 4 bits D1 12 bits B2 4 bits D2 12 bits Two operands: destination storage with length specified and source storage with length specified. L1 and L2 serve the same purpose as L field of an SS-1 type instruction, but L1 for denoting the length of the destination and L2 the source. The maximum possible lengths for source and destination are 16 (24). SS 2 type of instructions is mainly used in editing where the source and destination are of 31 different lengths

House Keeping
Entry Housekeeping
USING STM LR ST LR LA ST TESTDCB,R12 ESTABLISH R12 AS BASE REG R14,R12,12(R13) SAVE CALLER'S REGS R12,R15 LOAD BASE REG, R15=CALLER ADDRESS R13,SVAREA+4 SAVE CALLER SAVEAREA POINTER R2,R13 TEMPORARY LOAD CALLER SAVEAREA R13,SVAREA LOAD ADDRESS OF PROGRAMS SAVEAREA R13,8(R2) SAVE PROGRAM SAVEAREA IN CALLER

Exit Housekeeping
L LM LA BR R13,SVAREA+4 R14,R12,12(R13) R15,F0 R14 RESTORE CALLER SAVEAREA RESTORE CALLER'S REGS INITIALIZE RETURN CODE BRANCH TO RETURN ADDRESS

32

In Ameriprise . . .
PRIME (11,12,6),SAVE,REGEQ *********************************************************************** * S T A N D A R D O S P R O G R A M E N T R Y * *********************************************************************** USING *,11,12,6 * ESTABLISH ADDRESSABILITY B 30(0,15) * BRANCH AROUND IDENTIFIER DC AL1(8+16) * IDENTIFIER LENGTH DC CL8'L631004' * PROGRAM NAME DC CL8'08/04/08' * ASSEMBLY DATE DC CL8'04.39' * ASSEMBLY TIME STM LR LA LA LA CNOP BAS DC ST ST LM 14,12,12(13) 11,15 * 1,4095 * 12,1(1,11) 6,1(1,12) 0,4 * 1,*+72+4 A(72),17A(0) 1,8(,13) * 13,4(,1) * 13,1,8(13) * * * * * SAVE CALLERS REGISTERS LOAD FIRST BASE REGISTER LOAD INDEX REGISTER WITH 4095 LOAD NEXT BASE REGISTER LOAD NEXT BASE REGISTER FULLWORD ALIGNMENT LOAD SAVE AREA ADDRESS 10 Nov 2000 * STATIC SAVE AREA CHAIN TO CALLERS SAVE AREA CHAIN CALLERS SAVE AREA SET SAVE AREA PTR, RESTR 14 - 1

SAVE

33

LOAD (L & LR)


Format for Load (L): Format for Load Register (LR): Mnemonic Operands

Mnemonic

Operands

R1, D2 (X2 , B2)

LR

R 1, R2

The LOAD instruction takes four bytes from storage or from a general register and place them unchanged into a general register.
Example: Instruction : Register R4 01 02 03 04 L R4,VAR1 Storage VAR1 (6 bytes) X010203040506
Only four bytes will be loaded

Instruction : Register R4 01 02 03

LR

R4,R5 Register R5

04

01

02

03

04
34

LOAD Address (LA)


Format: Mnemonic Operands

LA

R1, D2 (X2 , B2)

The effective address of the 2nd-operand field is loaded in the 1st-operand register. The effective address calculated by adding up the values of the index-register (X2 ), the base-register (B2) and the displacement (D2)
Example: Assume initial contents of R4 is 10 00 00 00. Instruction : Register R4 00 00 03 E8
Starting address : X000003E8 35 In R4, initial contents are cleared after execution

LA

R4,VAR1 Storage VAR1 (6 bytes) X010203040506

LOAD Multiple (LM)


Format: Mnemonic Operands

LM

R1, R3, D2 (X2 , B2)

Sequence of full words in storage are loaded into the adjacent target-registers starting with R1 and ending with R3.
Example: Instruction : Register R4 11 22 LM R4,R6,VAR1
If we specify LM R14,R12,VAR1 loading sequence will be 14,15,0,1,2..12

33

44 Storage VAR1 (12 bytes) 88 X112233445566778899AABBCC

Register R5 55 66 77

Register R6 99 AA BB CC
36

STORE (ST)
Format :

Mnemonic

Operands

ST

R1, D2 (X2 , B2)

The store instruction moves four bytes from register to a storage location.
Example: Instruction : Register R4 01 02 03 04 ST R4,VAR1 Storage VAR1 (4 bytes) X01020304

37

Store Multiple (STM)


Format: Mnemonic Operands

STM

R1, R3, D2 (X2 , B2)

Adjacent registers contents starting with R1 and ending with R3 are moved to the storage location specified by the second operand [D2 (X2 , B2)].
Example: Instruction : Register R4 11 22 STM R4,R6,VAR1

33

44 Storage VAR1 (12 bytes) 88 X112233445566778899AABBCC

Register R5 55 66 77

Register R6 99 AA BB CC
38

Add Full Word (A)


Format :

Mnemonic

Operands

R1, D2 (X2 , B2)

A four byte field in storage location containing a binary value is added to the binary value of a register and the resulting sum is placed in the first operand register.
Example:
Instruction : Register R4 00 00 00 05 A R4,VAR1 Storage VAR1 (4 bytes)

X00000004

Condition codes 0 = 0 result is 0 1 < 0 result is -ve 2 > 0 result is +ve 3 overflow

00

00

00

09

Register R4 after execution


39

Subtract Full Word (S)


Format :

Mnemonic

Operands

R1, D2 (X2 , B2)

A four byte field in storage location containing a binary value is subtracted from the binary value of a register and the result is placed in the first operand register.

Example:
Instruction : Register R4 00 00 00 05 S R4,VAR1 Storage VAR1 (4 bytes)
Condition codes 0 = 0 result is 0 1 < 0 result is -ve 2 > 0 result is +ve 3 overflow

X00000004

00

00

00

01

Register R4 after execution


40

Multiply Full Word (M)


Format :

Mnemonic

Operands

R1, D2 (X2 , B2)

A four byte value in (R 1 + 1) register is multiplied with the four byte value

specified in the second operand and the result is placed in the R 1 & R 1 + 1 register pair. The R1 field designates an even-odd pair of general registers and must designate an even-numbered register; otherwise, a specification exception is recognized.
Example: Instruction : R4 00 00 00 00 M R5 00 00 00 05
R4 R5

R4,VAR1

VAR1 (4 bytes) X00000004

Initial contents of R4 register is ignored

00 00 00 00

00 00 00 14

41

Compare (C)
Format :

Mnemonic

Operands

R1, D2 (X2 , B2)

A value in the first operand register is compared with the 4-byte field in storage

specified by the second operand register. Result is indicated in the condition code.
Example:

Instruction :

R4,VAR1

R5 00 00 00 0A

VAR1 (4 bytes) X00000002


Condition codes 0 1=2 1 1<2 2 1 >2 3 not used!
42

Condition code 2 is set

Compare Logical Immediate (CLI)


Format :

Mnemonic

Operands

CLI

D1 (B1), I2

Single byte of data in the first operand is compared with the single byte of

immediate value (value coded in the instruction itself). Result is indicated in the condition code.
Example: Instruction : CLI VAR1 X20000002 VAR1, X20

X20 Condition codes 0 1=2 1 1<2 2 1 >2 3 not used!


43

Condition code 0 is set

Compare Logical Character (CLC)


Format :

Mnemonic

Operands

CLC

D1 (L1,B1), D2 (B2 )

The data of the 1st-operand field is compared with the data of the 2nd-operand

field. The length is defined by the 1st-operand. The result is indicated in the condition code.
Example: Instruction : CLC VAR1 X20500055 VAR1(3), VAR2

X20500066

Condition code 0 is set

Condition codes 0 1=2 1 1<2 2 1 >2 3 not used!

44

Branch on Condition (BC)


Format :

Mnemonic

Operands

BC

M1 , D2 (X2 , B2)

This instruction is used to test the condition code (CC) and based on the CC,

control will go to the next sequential instruction or to the location specified the second operand. Branch occurs only if the current condition code corresponds to a one bit in a mask specified by the instruction.
Example: Instruction : BC 8, LOC1
Extended Mnemonics can also be used instead of BC as follows: BC 8,LOC1 ---- BZ LOC1 BC 4,LOC1 ---- BNZ LOC1 Etc..

1 Condition code 0

0 1

0 2

0 3

Bit corresponding to the condition code 0 is 1. If the CC from the previous instruction is zero, control will go to the LOC1 location. Else, NSI will be executed.
45

Branch and Link (BAL)


Format :

Mnemonic

Operands

BAL

R1 , D2 (X2 , B2)

In 24-bit

The address of the next sequential instruction (NSI) & other linkage information (CC, ILC, Program mask) is placed in the 1st-operand register. Subsequently a branch is made to the location given by a 2nd-operand.
In 31-bit

The address of the next sequential instruction (NSI) is placed in the 1st-operand register. Subsequently a branch is made to the location given by a 2nd-operand. No other linkage information is saved.

46

Branch and Save (BAS)


Format :

Mnemonic

Operands

BAS

R1 , D2 (X2 , B2)

In both 24-bit & 31-bit

The address of the next sequential instruction (NSI) is placed in the 1st-operand register. Subsequently a branch is made to the location given by a 2nd-operand. No other linkage information is saved.
. . . . . . . . . . . . BAS WTO BR LABLEL1 SR BR R5, LABEL1 CLEARED R14 R6,R6 R5 GOTO clear routine Display cleared Return to caller clear R6 Branch back to BAS
47

Branch on Count (BCT)


Format :

Mnemonic

Operands

BCT

R1 , D2 (X2 , B2)

The contents of the 1st-operand register is subtracted by one. The result is checked for zero. If the result is not zero a branch is made to the location given by the 2nd-operand

label; if the result is zero the next sequential instruction (NSI) is processed.
. . . . . . . . . . . . LA LOOPSTRT BCT BR LABLEL1 R6,6 R6,LABEL1 R14 perform label1 6 times Return to caller IF R6 NE 0

WTO ********************* B LOOPSTRT


48

Move character (MVC)


Format :

Mnemonic

Operands

MVC

D1 (L1 , B1), D2 (B2)

It moves data from the source-field (2nd operand) into the target-field (1st

operand). The maximum length which can be moved is 256 bytes of data. The length is defined by the 1st-operand field.
FIELD1 : Target
Initial contents CXXXXXXXXXX FIELD2 : Source CYYYYYYYYYY FIELD1 : After MVC

Example 1

MVC

FIELD1, FIELD2

CYYYYYYYYYY FIELD1 : After MVC

Example 2

MVC

FIELD1(5), FIELD2

CYYYYYXXXXX
49

Move Immediate (MVI)


Format :

Mnemonic

Operands

MVI

D1 (B1), I2

Single byte of second operand immediate value is moved to the memory location

specified by the first operand.


Example: Instruction : MVI
FLAG (3 Bytes) Before MVI X000202 X01

FLAG, X01

FLAG (3 Bytes) After MVI X010202


50

Zero & Add Packed Data (ZAP)


Format :

Mnemonic

Operands

ZAP

D1 (L1, B1), D2 (L2, B2)

1st-operand field is set to packed decimal zero. The contents of the 2nd-operand field is added to the 1st-operand zero value. The initial contents of the 2nd-operand field has to be in correct packed decimal

format, otherwise the instruction results in data exception.


Example: Instruction : ZAP
Before ZAP X000002
PKFIELD1

PKFIELD1, =P1234
Initialized before adding X00000C
PKFIELD1

After ZAP X01234C


PKFIELD1

51

File Operations
Write Operation (PS file)
WRITEPGM CSECT ..... ..... .. OPNFILE OPEN (PRINT,(OUTPUT)) MVC PRNTLINE, =CFIRST RECORD PUT PRINT, PRNTLINE CLOSE (PRINT) .. PRINT DCB DSORG=PS,MACRF=PM,DDNAME=PRINTER END

OPEN Macro opens the PS file in output or input mode based on the parameter passed.
OPEN (PRINT,(OUTPUT))

Macro Name

DCB name

Mode of opening INPUT OUTPUT


52

File Operations
PUT Macro writes the data into the file.
PUT Macro Name PRINT, PRNTLINE

DCB Name

Memory location where the data to be written is stored

DCB macro generates the control block of memory necessary for the OPEN, GET, PUT macros based on the input parameters ( DSORG, MACRF, DDNAME).
PRINT DCB DSORG=PS,MACRF=PM,DDNAME=PRINTER

DCB Name

DDNAME of the file DCB Macro name Dataset organization PS or PDS P Put operation M Move mode (this parameter specifies whether the operation is read (G) or write (P) & second character specifies whether the data to be written is in R1 (L) or in memory area (M).
53

File Operations
Read Operation (PS File)
WRITEPGM CSECT ..... ..... .. OPNFILE OPEN (BILLIN,(INPUT)) GET BILLIN LR R2,R1 .. EOJ BILLIN CLOSE (BILLIN) DCB DSORG=PS,MACRF=GL,DDNAME=BINPUT,EODAD=EOJ END After EOF, go to EOJ label All parameters are same as discussed in WRITE operation

54

Thank you

55

S-ar putea să vă placă și