Assembler To Cobol
Assembler To Cobol
Assembler To Cobol
1. Introduction:
Often, you might have faced many difficulties in converting Assembler code to Cobol code.
Through this document, I have tried to ease out ways of converting the code and find a simple
approach which would be helpful for the same. The major difficulties while converting
assembler to cobol is understanding the use of pointers in cobol. This document helps you to
understand pointers as well as some assembler instructions which could be used in an easy way
to convert to cobol. This document also helps you to learn the advantages of converting your
low-level assembler code to the more flexible, user-friendly COBOL language. We will also
understand some of the differences between the languages and some basics about converting
your programs. This document introduces you to some of the intricacies of the assembler
language and provides general guidance for how to convert assembler code to COBOL.Before
going into the intricacies of conversion, first of all we see what is the need to convert code
available in assembly language.
3
2. Need for Conversion to COBOL:
Coding in assembler language is not like coding in any other language, because assembler lacks
the flexibility and user-friendliness of a high-level language. A low-level language directly
addresses memory-resident areas called registers; in any high-level language, the variables
handle this function.
There are several reasons to convert a low-level assembler program to the higher level COBOL
language. The main reasons are:
• There might be licensing issues with assembler code, and the code might expire.
Licensing is often expensive, and you risk losing rights to use the code.
• Assembler code can be difficult to maintain because of a shortage of experienced
professionals.
• Programming in assembler language is not as flexible or user-friendly as COBOL
language.
3. How to Convert?
Before starting with the code conversion, first of all we need to understand the conversion of
Assembler data types (DSECT) to COBOL data types (Copy Book).
In Assembler the data types are character type (C), binary type (B, X, H, F, D), packed type (P)
and address type (A). While in COBOL, the data types are character type, numeric type and
alpha-numeric type.
Let’s understand with the help of an example how to convert DSECT to Copy Book.
EMPLOYEE DSECT
EMPNUM DS F ------ > Fullword
EMPNAME DS CL30 ------ > Char Type
EMPDEPT DS CL10 ------ > Char Type
4
EMPDESG DS CL3 ------ > Char Type
EMPDOB DS XL10 ------ > Hex Type
EMPDOJ DS XL10 ------ > Hex Type
EMPSAL DS PL5 ------ > Pack Type
Above Dsect is having Binary, Char, Pack types of data. So for binary type data, like F(Fullword
– 4 Byte), H(Halfword – 2 Byte), D(Doubleword – 8 Byte), we will use S9 (9) BINARY, S9 (4)
BINARY and S9 (16) BINARY respectively. We can also use COMP instead of BINARY. For Char
type data here we are using X(Alphanumeric type), because it can store character as well as
alphanumeric types of data. For the packed type data, PL5 (Packed Type – length 5), S9 (9)
COMP-3 would be used.
Hence, in Copy Book, the above code fragment would be written as below:
01 EMPLOYEE.
05 EMPNUM PIC S9 (9) BINARY.
05 EMPNAME PIC X(30).
05 EMPDEPT PIC X(10).
05 EMPDESG PIC X(03).
05 EMPDOB PIC X(10).
05 EMPDOJ PIC X(10).
05 EMPSAL PIC S9 (9) COMP-3.
H1CYMD DS 0CL8
H1CYM DS 0CL6
H1CYY DS 0CL4
H1C DS CL2
H1YY DS CL2
H1MM DS CL2
H1DD DS CL2
ORG H1C + 1
H1CYMD DS CL7
5
In the above code, the purpose of ORG directive is to redefine a location. Hence, to convert
this type of data into COBOL, we would be using REDEFINES keyword. Also, the first three fields
of above Dsect would be used as group level data.
Having done with the data tpes, let’s next move on to code conversion. In code conversion,
we’ll look into the following types of instructions:
a) Conversion Instructions
b) Logical Instructions
c) Character Manipulation & Subroutine
d) Arithmetic Instructions
e) Some more Instructions
In this section, we will discuss how to convert the following Assembler instructions to COBOL:
6
a) Pack
b) Unpack
c) TR
d) TRT
e) ED
f) EDMK
WorkPL8 DS PL8
Zndata DS XL3
In COBOL, we can’t directly convert from character to pack, so we need to take one numeric
variable. We will first convert Character type to numeric type then numeric to pack. In this
example, we are taking numeric variable Wrkfld.
WorkPL8 DS PL8
7
Zndata DS XL3
Suppose initial value of SOURCE is X’0200010301’ then after executing TR instruction, value of
SOURCE would be X’C3C1C2C4C2’
8
MOVE TABLE(WS-2BYTE-N + 1:1)TO SOURCE(WS-I:1)
END-PERFORM
TRT is used to scan a string of characters, searching for the occurrence of any characters which
are specified in a translate table.
TRT also sets the condition code to indicate the results.
To find the first numeric digit or alphabetic character in the field specified by BUFFER variable,
SR R2,R2
TRT BUFFER(80),SCANTAB2
B BRTAB(R2)
BRTAB B NONE
B ALPHA
B DIGIT
In storage:
BUFFER DS CL80
SCANTAB2 DC 256X'00'
ORG SCANTAB2+C'A' If alphabetic, set value in
DC 9X'04' register 2 to 04
ORG SCANTAB2+C'J'
DC 9X'04'
ORG SCANTAB2+C'S'
DC 8X'04'
ORG SCANTAB2+C'0' If numeric, set value in
DC 10X'08' register 2 to 08
ORG
Result:
9
If no alphabetic or numeric character is found, the value in register 2 remains 0 and the branch
to NONE is taken.
If an alphabetic character is found, the rightmost byte of register 2 is set to 04 and the branch
to ALPHA is taken.
If a numeric character is found, the rightmost byte of register 2 is set to 08 and the branch to
DIGIT is taken.
In COBOL, for the above TRT instruction, the following operation would be performed:
10
ED converts the packed decimal number in the second operand, to a displayable form using the
hexadecimal pattern in the first operand, which also receives the result.
In COBOL, we can edit data using edited picture numerical literals. So we define data
The EDMK instruction works in exactly the same way as the Ed instruction with a bonus. If the
significance detector is on, Register 1 will be loaded with the address of the significant digit.
This is useful when wanting to insert a currency symbol ahead of an amount.
Example:
11
MVI 0(R1),C'$'
* PATTERN1 Result => ‘ $12345.67’ => X'40405BF1F2F3F4F54BF6F7'
12
Logical instructions are not easy to handle in COBOL because these instructions work on bit,
and in COBOL bit handling is not an easy task. To solve this problem, there is an approach of
converting the bit information in a single byte to or from an eight-byte field of COBOL
accessible zeroes and ones.
Determining and changing the setting of a bit is possible using COBOL. In COBOL, we need to
write a routine that provides two functions (EXPAND & COMPRESS).
For each bit that is ON (1) in the TEST-BITS field the corresponding byte in the TEST-BYTES
field is set to a value of one. For each bit that is OFF (0) in the TEST-BITS field the
corresponding byte in the TEST-BYTES field is set to a value of zero.
01 TEST-RECORD.
10 TEST-BITS PIC X. - X’55’
10 TEST-BYTES.
15 TEST-BYTE-01 PIC X. - ‘0’
15 TEST-BYTE-02 PIC X. - ‘1’
15 TEST-BYTE-03 PIC X. - ‘0’
15 TEST-BYTE-04 PIC X. - ‘1’
15 TEST-BYTE-05 PIC X. - ‘0’
15 TEST-BYTE-06 PIC X. - ‘1’
15 TEST-BYTE-07 PIC X. - ‘0’
15 TEST-BYTE-08 PIC X. - ‘1’
b) COMPRESS - translate the bytes of an eight-byte field into bits of a one-byte field
For each byte that is a one in the TEST-BYTES field the corresponding bit in the TEST-BITS field
is set to ON (1). For each byte that is zero in the TEST-BYTES field the corresponding bit in the
TEST-BITS field is set to OFF (0).
Input TEST-BYTES, an eight byte field
Output TEST-BITS, a one byte field (8-bits)
13
Example if TEST-BYTES = '01010101' then TEST-BITS will be x’55’
In this section, we are not discussing RR or RX Type instruction. We will discuss only following
instructions:
a) NC
b) NI
c) OC
d) OI
e) XC
f) XI
g) TM
a) NC - AND Character
The NC instruction Ands the character string pointed to by the first operand with the character
sting pointed to by the second operand. The result is stored in the first operands.
LABEL1 DC XL5’D1D2D3D4D5’
LABEL2 DC X'CACBCCCDCECFD6D7D8D9’
NC LABEL1 (4), LABEL2
In COBOL, we will perform expand & compress routine to solve bit wise problem.
14
15 TEST-BYTE1-02 PIC X.
15 TEST-BYTE1-03 PIC X
15 TEST-BYTE1-04 PIC X.
15 TEST-BYTE1-05 PIC X.
15 TEST-BYTE1-06 PIC X.
15 TEST-BYTE1-07 PIC X.
15 TEST-BYTE1-08 PIC X.
01 TEST-RECORD2.
10 TEST-BITS2 PIC X.
10 TEST-BYTES2.
15 TEST-BYTE2-01 PIC X.
15 TEST-BYTE2-02 PIC X.
15 TEST-BYTE2-03 PIC X.
15 TEST-BYTE2-04 PIC X.
15 TEST-BYTE2-05 PIC X.
15 TEST-BYTE2-06 PIC X.
15 TEST-BYTE2-07 PIC X.
15 TEST-BYTE2-08 PIC X.
15
END-IF
IF TEST-BYTE1-04 EQUAL ‘0’
OR TEST-BYTE2-04 EQUAL ‘0’
MOVE ‘0’ TO TEST-BYTE1-014
END-IF
IF TEST-BYTE1-05 EQUAL ‘0’
OR TEST-BYTE2-05 EQUAL ‘0’
MOVE ‘0’ TO TEST-BYTE1-05
END-IF
IF TEST-BYTE1-06 EQUAL ‘0’
OR TEST-BYTE2-06 EQUAL ‘0’
MOVE ‘0’ TO TEST-BYTE1-06
END-IF
IF TEST-BYTE1-07 EQUAL ‘0’
OR TEST-BYTE2-07 EQUAL ‘0’
MOVE ‘0’ TO TEST-BYTE1-07
END-IF
IF TEST-BYTE1-08 EQUAL ‘0’
OR TEST-BYTE2-08 EQUAL ‘0’
MOVE ‘0’ TO TEST-BYTE1-08
END-IF
PERFORM COMPRESS ROUTINE TO COMPRESS TEST-BYTE1 INTO TEST-BITS1
MOVE TEST-BITS1 TO LABEL(WS-I:1)
END-PERFORM
The instructions OC and XC also perform like NC. Similarly, the immediate instructions like NI,
OI, XI would also be performed in the similar way as discussed for NC but on a single byte.
Hence, we will not cover these instructions in detail.
16
.
.
TEST.
HEX1 DS XL4
The initial value of HEX1 is XL4’C1D1C2C3’ and after executing this instruction label TEST will
be executed.
17
3.2.3 Character Manipulation and Subroutines:
a) MVC
b) MVI
c) CLC
d) CLI
e) MVCL
f) CLCL
g) BASR
h) BAS
i) EX
This instruction copies the consecutive bytes starting from the address specified by the second
operands into consecutive addresses specified by the first operand. The number of bytes to be
copied is specified by the first operand.
Example:
H1CYY DS 0CL4
H1C DS CL2
H1YY DS CL2
CMYY DS 0CL6
CYY DS CL1
MYY DS CL3
DYY DS CL3
01 H1CYY.
18
05 H1C PIC X(2).
05 H1YY PIC X(2).
01 CMYY.
05 CYY PIC X(1).
05 MYY PIC X(3).
05 DYY PIC X(3).
This instruction copies the second immediate operands into the storage
location specified by the first operands
19
In COBOL, the above example would be written as follows:
This instruction compares the consecutive byte pointed by the first operand
with the immediate data treating them as character starting and sets the
condition code.
20
The MVCL instruction copies the bytes starting from the address specified with the second
operand, into the address pointed by the first operand. Both operands are even-odd register
pairs. Even register contain address and odd register contain length.
MVCL R2, R4
A DS XL3200
B DS XL3200
Suppose A & B are mapped with R2 and R4 respectively and initial values of R3 and R4 are
3200.
So it copies all 3200 from B to A.
MOVE B TO A
f) CLCL – COMPARE Character Long
The CLCL instruction compares the bytes starting from the address specified with the second
operand, into the address pointed by the first operand. Both operands are even-odd register
pairs. Even register contain address and odd register contain length.
CLCL R2, R4
A DS XL3200
B DS XL3200
Suppose A & B are mapped with R2 and R4 respectively and initial values of R3 and R4 are
3200.
So it compares all 3200 of B with A.
IF A equal B
21
The BASR instruction places the address of the next instruction to be executed into the first
operand. The control is then transferred to the location specified by the second operand. If
second operand is R0, then no branch occurs.
LA R5, INC
BASR R4, R5
.
.
.
INC EQU *
.
.
.
BR R4
PERFORM INC-PARA
.
.
.
INC-PARA.
h) EXECUTE (EX)
The EX instruction executes a single instruction specified by the second operand. Before the
target instruction is executed, the low order byte of the register indicated as the first operand
is ORed with second byte of instruction.
We can use this instruction with MVC, CLC, PACK, TRT etc.
EX R1, MVC1
.
22
.
MVC1 MVC A(0), A + 1
There are four basic Arithmetic instructions – add, subtract, multiply and divide.
a) ADD
In COBOL, we will use ADD command corresponding to Assembler’s AR(Add Register), A(Add),
AH(Add Halfword ) AP(Add Packed).
b) SUBTRACT
c) MULTIPLY
c) DIVIDE
23
This instruction shifts the 32-bit first operand left, the number of bits specified by the second
operand. The second operand does not specify an address.
SLL R1, 2
If the initial value of R1 is X’FFFFFFFF’ then after executing this instruction the value of R1
would be X’FFFFFFFC’
This instruction operates with register so in COBOL a 4 byte variable would be used
corresponding to that register.
So the above code in COBOL can be written as:
01 WS-4Byte.
05 WS-4Byte-N PIC 9(9) Binary. – corresponding to register
Multiply 4 BY WS-4Byte-N.
This instruction shifts the 32-bit first operand right, the number of bits specified by the second
operand. The second operand does not specify an address.
SRL R1, 2
If the initial value of R1 is X’FFFFFFFF’ then after executing this instruction the value of R1
would be X’3FFFFFFF’
This instruction operates with register so in COBOL a 4 byte variable would be used
corresponding to that register.
So the above code in COBOL can be written as:
01 WS-4Byte.
24
05 WS-4Byte-N PIC 9(9) Binary. – corresponding to register
The CVB instruction converts the packed-decimal number in the 8-byte field specified by the
second operand, to an integer in the two’s complement binary number system operand and
stores it in the first operand.
01 WS-4Byte.
05 WS-4Byte-N PIC S9(9) Binary. – Corresponding to register
01 WORKPL8 PIC S9(15) COMP-3.
MOVE WORKPL8 TO WS-4Byte-N.
The CVD instruction converts a 32-bit signed integer specified as the first operand to an 8 byte
packed-decimal number and stored it as the location specified by the second operand location.
25
After executing this instruction the content of WORKPL8 would be 000000123456789C
01 WS-4Byte.
05 WS-4Byte-N PIC S9(9) Binary. – corresponding to register
01 WORKPL8 PIC S9(15) COMP-3.
MOVE WS-4Byte-N TO WORKPL8.
This instruction is used to move only numeric part of a byte from second operand to first
operand; the zoned part of the first operand would not be changed.
FLDA DS XL3’123456’
FLDB DS XL3’777777’
26
05 REM2-C .
10 REM2 PIC 9(4) BINARY.
This instruction is used to move only zoned part of a byte from second operand to first
operand; the numeric part of the first operand would not be changed.
27
This instruction is used to load positive value of second operand to first operand.
Example:
LPR R1, R2
If the value of R2 IS -6 then after executing this instruction the content of R1 will be 6.
In COBOL, we will move signed 4 byte variable to unsigned 4-byte variable.
MOVE B TO A
This instruction is used to load negative value of second operand to first operand.
Example:
LNR R1, R2
If the value of R2 IS -6 then after executing this instruction the content of R1 will be -6.
MOVE B TO A
IF B IS POSITIVE
MULTIPLY -1 INTO A
END-IF
28
LCR R1, R2
If the value of R2 IS -6 then after executing this instruction the content of R1 will be 5.
COMPUTE A = B* (-1) - 1
In Assembler the registers as well as variables both can contain the addresses and further these
addresses are manipulated .These addressing of assembler can be tackled in COBOL by using
the concept of POINTERS, but the major drawback with COBOL is that COBOL is high level
language and hence, does not has registers.
In Assembly language, a structure can be mapped with the addresses stored in registers and
after calculation and processing those addresses are dropped from the register. By USING
directive, we can map the structure and by using DROP directive, we can unmap the structure.
LA R02, HDBTABLE
USING FMTTBENT, R02
DROP R02
Declare a pointer as an elementary data item bearing the USAGE IS POINTER clause, with no
PICTURE. E.g.:
29
WS-POINTER is a four-byte field which can store the address of any data item. The pointer is
then mapped to any variable of Linkage Section.
Suppose there is pointer WS-POINTER which points to some object of some know types. Set up
an instance of such an object in the linkage section. Example:
LINKAGE SECTION.
01 NAME-STRUCTURE.
05 FIRST-NAME PIC X (18).
05 LAST-NAME PIC X (26).
The variable whose address you are setting (NAME-STRUCTURE in this case) must be a 01-level
or 77-level item in the LINKAGE SECTION.
Pointers can further be redefined as a group level and can be used for arithmetic calculations.
For Example:
30
So Ws-pointer-N is the binary variable which can be used as calculation.
Pointers can be further used to pass or receive it as a parameter. Pointers can be assigned
NULL, either with Value clause or with SET verb. Example:
• Dereferencing a NULL pointer: This blunder will cause an ABEND. Always check for
NULL before dereferencing a pointer.
• Failure to initialize a pointer before using it: Until you initialize it, a pointer will be
NULL, or it will contain garbage pointing to a random location in memory.
Dereferencing it will cause an ABEND. Whenever you declare a pointer in WORKING-
STORAGE, always initialize it to NULL with a VALUE clause. Then your code has a way
to defend itself. It can detect NULL, but it cannot detect garbage. Likewise: if you
dynamically allocate something which contains a pointer, set the pointer to NULL or to
some other reasonable value as soon as you allocate it.
• Corrupting a pointer: For example, you might MOVE SPACES to a group item which
contains a pointer variable. The compiler won't protect you -- it will happily trash your
pointer.
• Accessing freed memory: Once you deal locate a chunk of memory, you should treat it
as gone forever. But if you still have a pointer to it lying around, you might
accidentally try to access it through that pointer. The results are unpredictable but
may include the following:
1. You abend. The operating system says you don't own that memory any more.
2. Your program grossly misbehaves because that memory is now being used for
something else. It doesn't even look like what you think it should look like.
31
3. Your program subtly misbehaves because that memory is still accessible, and it
looks just the way it did when you deal located it, but it is no longer valid.
You can minimize this danger if, whenever you deallocate something, you set the
corresponding pointer to NULL. That way (if you follow the advice given earlier) you
won't even try to dereference it.
Even if you follow this policy, you are still vulnerable whenever you have multiple
copies of the same pointer. You might nullify one copy but try to use the other.
As a result, you should avoid keeping multiple copies of pointers. When you can't avoid
it, control the extra copies carefully. Designate only one of the copies to be used for
deallocation.
An Assembler program requires DCB macros (OPEN, GET, PUT, CLOSE), for processing data from
external files.
OPEN (INFILE,,OUTFILE,(OUTPUT))
LOOP GET INFILE, INREC
MVC OUT_PART1, INREC
MVC OUT_PART2, INREC + 50
PUT OUTFILE, OUT_PART1
B LOOP
DONE CLOSE (INFILE, , OUTFILE)
32
INREC DC CL100
OUT_PART1 DS CL50
DC CL20 ‘ ‘
OUT_PART2 DS CL50
INFILE DCB DSORG=PS, MACRF=GM, DDNAME=INDD, EODAD=DONE
OUTFILE DCB DSORG=PS, MACRF=PM, DDNAME=OUTDD, LRECL=120, RECFM=FB,
BLKSIZE=12000
In COBOL, first we need to define file in FILE-CONTROL paragraph. We define each file in the
COBOL program with an external medium, and allow specification of file organization, access
mode and other information in this paragraph.
Each file described in an FD or SD entry in Data Division must be described in one and only one
entry in File-Control Paragraph.
Each data-name must appear in a Data Division entry. The record layout for the files is defined
in the FD section, which is FILE DESCRITPTION entry for the files defined in the SELECT clause.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
ASSIGN INFILE TO CUSTFILE
ORGANIZATION IS SEQUENTIAL.
ASSIGN OUTFILE TO CUSTOUT.
:
DATA DIVISION.
FILE SECTION.
FD INFILE.
01 IN-FILE.
03 INREC PIC X(100).
FD OUTFILE.
01 OUT-REC.
33
05 OUT-PART1 PIC X(50)
05 FILLER PIC X(20) VALUE SPACES.
05 OUT-PART2 PIC X(50)
WORKING-STORAGE SECTION.
01 EOF-FLAG PIC X.
88 END-OF-IN-FILE VALUE 'Y'.
:
PROCEDURE DIVISION.
MAIN-PARAGRAPH.
OPEN INPUT INFILE
OPEN OUTPUT OUTFILE
STOP RUN.
PRINT-DETAILS.
MOVE INREC(1:50) TO OUT-PART1
MOVE INREC(51:50) TO OUT-PART2
WRITE OUT-REC.
34
1) MOVE 9(4) BINARY DATA TO X(5)
Input:
WORKING-STORAGE SECTION.
01 A PIC X(5).
01 B.
05 B-N PIC 9(4) COMP-5.
01 C PIC 9(5).
PROCEDURE DIVISION.
MOVE X'B8DD' TO B. /* X'B8DD' = 47325 */
MOVE B-N TO C.
MOVE C TO A.
DISPLAY '"' A '"'.
DISPLAY '"' B '"'.
DISPLAY '"' C '"'.
STOP RUN.
Output:
"47325" /* A */
" " /* B */
"47325" /* C */
Input:
WORKING-STORAGE SECTION.
01 A PIC X(5).
01 B.
05 B-N PIC 9(9) COMP-5.
01 C PIC 9(5).
PROCEDURE DIVISION.
MOVE X'00023F7D' TO B. /* X'00023F7D'=147325 */
MOVE B-N TO C.
MOVE C TO A.
35
DISPLAY '"' A '"'.
DISPLAY '"' B '"'.
DISPLAY '"' C '"'.
STOP RUN.
Output:
Truncation occur
"47325" /* A */
" " /* B */
"47325" /* C */
Input:
WORKING-STORAGE SECTION.
01 A PIC X(5).
01 B.
05 B-N PIC 9(9)COMP-5.
01 C PIC 9(5).
PROCEDURE DIVISION.
MOVE '47325' TO A.
MOVE A TO C.
MOVE C TO B-N.
DISPLAY '"' A '"'.
DISPLAY '"' B-N '"'.
DISPLAY '"' C '"'.
STOP RUN.
Output:
"47325"
"0000047325"
"47325"
36
Input:
WORKING-STORAGE SECTION.
01 A PIC X.
01 B.
05 B-N PIC 9(4) COMP-5.
01 C PIC 9(5).
01 D PIC X(3).
PROCEDURE DIVISION.
MOVE X'92' TO A.
MOVE LOW-VALUES TO B.
MOVE A TO B(2:1).
MOVE B-N TO C.
MOVE C(3:3) TO D.
DISPLAY '"' A '"'.
DISPLAY '"' B-N '"'.
DISPLAY '"' C '"'.
DISPLAY '"' D '"'.
STOP RUN.
Output:
"k"
"00146"
"00146"
"146"
Input:
WORKING-STORAGE SECTION.
01 A.
05 B PIC 9(2) COMP-5.
PROCEDURE DIVISION.
MOVE HIGH-VALUES TO A.
37
DISPLAY '"' A '"'.
DISPLAY '"' B '"'.
MOVE LOW-VALUES TO A.
DISPLAY '"' A '"'.
DISPLAY '"' B '"'.
STOP RUN.
Output:
" " /* A */
"65535" /* B */
" " /* A */
"00000" /* B */
Input:
WORKING-STORAGE SECTION.
01 L015-DATA.
05 L015-DISPLAY-HEX.
10 L015-DISPLAY-HEX-1 PIC X.
10 L015-DISPLAY-HEX-2 PIC X.
05 L015-LEFT-NYBBLE.
10 L015-LEFT-NYBBLE-N PIC 9(4) COMP-5.
05 L015-RIGHT-NYBBLE.
10 L015-RIGHT-NYBBLE-N PIC 9(4) COMP-5.
05 L015-BINARY-HEX.
10 L015-BINARY-HEX-N PIC 9(4) COMP-5.
*
PROCEDURE DIVISION.
*
*
MOVE 'AB' TO L015-DISPLAY-HEX.
MOVE ZERO TO L015-LEFT-NYBBLE-N.
MOVE ZERO TO L015-RIGHT-NYBBLE-N.
38
MOVE L015-DISPLAY-HEX-1 TO L015-LEFT-NYBBLE(2:1).
MOVE L015-DISPLAY-HEX-2 TO L015-RIGHT-NYBBLE(2:1).
*
IF L015-DISPLAY-HEX-1 LESS THAN '0'
COMPUTE L015-LEFT-NYBBLE-N
= ((L015-LEFT-NYBBLE-N + 57) - 240) * 16
ELSE
COMPUTE L015-LEFT-NYBBLE-N
= ( L015-LEFT-NYBBLE-N - 240) * 16
END-IF
*
IF L015-DISPLAY-HEX-2 LESS THAN '0'
COMPUTE L015-RIGHT-NYBBLE-N = L015-LEFT-NYBBLE-N
+ (L015-RIGHT-NYBBLE-N + 57) - 240
ELSE
COMPUTE L015-RIGHT-NYBBLE-N = L015-LEFT-NYBBLE-N
+ L015-RIGHT-NYBBLE-N - 240
END-IF
*
MOVE L015-RIGHT-NYBBLE(2:1) TO L015-BINARY-HEX (2:1).
*
DISPLAY '"' L015-BINARY-HEX '"'.
DISPLAY '"' L015-BINARY-HEX-N '"'.
OUTPUT:
" "
"00171" /* ‘Hex Value of X’AB’ = 00171 */
Input:
WORKING-STORAGE SECTION.
01 A.
05 B PIC 9(4) COMP-5.
01 C.
05 D PIC X.
39
05 E PIC X.
01 F REDEFINES C PIC XX.
01 QUO PIC 9(2) VALUE 0.
01 REM PIC 9(2) VALUE 0.
PROCEDURE DIVISION.
MOVE LOW-VALUES TO A.
MOVE 'D' TO A(2:1).
DIVIDE B BY 16 GIVING QUO REMAINDER REM.
IF QUO EQUAL 10
MOVE 'A' TO D.
IF QUO EQUAL 11
MOVE 'B' TO D.
IF QUO EQUAL 12
MOVE 'C' TO D.
IF QUO EQUAL 13
MOVE 'D' TO D.
IF QUO EQUAL 14
MOVE 'E' TO D.
IF QUO EQUAL 15
MOVE 'F' TO D.
IF QUO LESS THAN 10
MOVE QUO(2:1) TO D.
*
IF REM EQUAL 10
MOVE 'A' TO E.
IF REM EQUAL 11
MOVE 'B' TO E.
IF REM EQUAL 12
MOVE 'C' TO E.
IF REM EQUAL 13
MOVE 'D' TO E.
IF REM EQUAL 14
MOVE 'E' TO E.
IF REM EQUAL 15
MOVE 'F' TO E.
IF REM LESS THAN 10
MOVE REM(2:1) TO E.
40
DISPLAY '"' F '"'.
STOP RUN.
8) DATE STATEMENT:
Output:
" 99/12/31"
9) TIME STATEMENT:
41
ED HATIME,TIMEVAL+1
Where EDPTIME is the edit-pattern defined for time
EDPTIME DC X'4020217A2020'
HATIME is defined as CL6 format” HH:MM”
TIMEVAL is PL4
TIMEVAL+1 Means we are leaving first byte.
SRP A,64-1,0 means add 0 to A and shift 1 digit to right*/
Output:
" 05:59"
42
BINDATA is defined as FL4.
PACKDATA is PL8
PACKDATA+2 Means we are not moving first 2 byte.
*/
*/
43
COBOL code for unpack data
Input:
WORKING-STORAGE SECTION.
01 BIN-DATA PIC S9(9) COMP-5 VALUE 47325.
01 PACK-DATA PIC S9(15) COMP-3.
01 PACK-DATA-VAL PIC 9(15).
01 UNPK-DATA PIC X(10).
PROCEDURE DIVISION.
MOVE BIN-DATA TO PACK-DATA-VAL.
* MOVE BIN-DATA TO PACK-DATA.
* MOVE PACK-DATA TO PACK-DATA-VAL
MOVE PACK-DATA-VAL(6:10) TO UNPK-DATA
DISPLAY '"' UNPK-DATA '"'.
STOP RUN.
Output:
"0000047325"
44