C$RCONVERT
The C$RCONVERT library routine sets an item value in a buffer according to the information provided. It is particularly useful to set values that requires a conversion for their binary representation, for example a computational field in a record to be written via I$IO.
Syntax:
 CALL "C$RCONVERT" USING itemValue
                         buffer
                         offset,
                         size,
                         itemType,
                         digitsCount 
                         scale
                         convOpt
                  GIVING returnCode
Parameters:
itemValue
PIC X(n)
Specifies the item value.
buffer
PIC X(n)
The buffer in which the value has to be set.
offset
PIC 9(n)
Specifies the offset of the item in the buffer, starting at 0.
size
PIC 9(n)
Specifies the size in bytes of the item.
itemType
PIC 9(n)
Specifies the item type. Possible values are listed below.
digitsCount
PIC 9(n)
Specifies the number of digits allowed by the item, including decimal digits.
scale
PIC 9(n)
Specifies the number of decimal digits allowed by the item.
convOpt
PIC 9(n)
Specifies the numeric convention. Possible values are listed below.
Supported item types:
Type
Value for the itemType parameter
Numeric Edited
0
Unsigned numeric
1
Signed numeric where the sign is trailing separate
2
Signed numeric where the sign is in the last byte
3
Signed numeric where the sign is leading separate
4
Signed numeric where the sign is in the first byte
5
Signed computational (COMP-2)
6
Unsigned computational (COMP-2)
7
Positive packed-decimal (COMP-3)
8
Signed packed-decimal (COMP-3)
9
Computational-6
10
Signed binary (COMP-4)
11
Unsigned binary (COMP-4)
12
Signed native-order binary (COMP-5)
13
Unsigned native-order binary (COMP-5)
14
Alphanumeric
16
Alphanumeric justified
17
Alphabetic
18
Alphabetic justified
19
Alphanumeric edited
20
Group
22
Float or Double
23
National
24
National justified
25
National edited
26
Wide
27
Wide justified
28
Wide edited
29
Signed var-len native-order binary
30
Unsigned var-len native-order binary
31
Supported numeric convetions:
Convention
Value for the convOpts parameter
DCA
0
DCI
1
DCM
2
DCMI
3
DCII
4
DCD
5
DCDM
6
DCN
7
DCB
8
DCR
9
Return code:
returnCode is a signed numeric data item:
0
Operation successful.
1
Operation failed.
2
Invalid parameters.
Examples:
Example - Set a signed comp-4 field in a buffer under Micro Focus convention (dcm)
working-storage section.
01 my-record.
   03 foo     pic x(10).
   03 my-item pic s9(5)v99 comp-4.
   03 foo     pic x.
01 my-buffer pic x(15redefines my-record.
01 item-val pic x(10).
 
procedure division.
main.
 move "123.45" to item-val.
 
 call "c$rconvert" using item-val, my-buffer
                         104|offset & len
                         11,    |type
                         72,  |digits & scale
                         2.     |convention
                         
*> my-item will be set to 123.45