Thalecress
Thalecress

Reputation: 3451

What's wrong with this alphanumeric to numeric move?

When I move a number in a PIC X to a PIC 9 the numeric field's value is 0.

FOO, a PIC X(400), has '1' in the first byte and spaces in the remaining 399. Moving into the PIC 9(02) BAR like so

DISPLAY FOO
MOVE FOO to BAR
DISPLAY BAR

yields

1
0

Why is BAR 0 instead of 1? [Edit: originally, 'What is happening?']

Postscript: NealB says "Do not write programs that rely on obscure truncation rules and/or data type coercion. Be precise and explicit in what you are doing."

That made me realize I really want COMPUTE BAR AS FUNCTION NUMVAL(FOO) wrapped in a NUMERIC test, not a MOVE.

Upvotes: 3

Views: 24140

Answers (3)

Bill Woodger
Bill Woodger

Reputation: 13076

Firstly, why do you think it might be useful to MOVE a 400-byte field to a two-byte field? You are going to get a "certain amount(!)" of "truncation" with that (and the amount of truncation is certain, at 398 bytes). Do you know which part of your 400 bytes is going to be truncated? I'd guess not.

For an alpha-numeric "sending" item (what you have), the (maximum) number of bytes used is the maximum number of bytes in a numeric field (18/31 depending on compiler/compiler option). Those bytes are taken from the right of the alpha-numeric field.

You have, therefore, MOVEd the rightmost 18/31 digits to the two-digit receiving field. You have already explained that you have "1" and 399 spaces, so you have MOVEd 18/31 spaces to your two-digit numeric field.

Your numeric field is "unsigned" (PIC 9(2) not PIC S9(2) or with a SIGN SEPARATE). For an unsigned field (which is a field with "no operational sign") a COBOL compiler should generate code to ensure that the field contains no sign.

This code will turn the right-most space in your PIC 9(2) into a "0" because and ASCII space is X'20' and an EBCDIC space is X'40'. The "sign" is embedded in the right-most byte of a USAGE DISPLAY numeric field, and and no other data but the sign is changed during the MOVE. The 2 or 4 of X'2n' or X'4n' is, without regard to its value, obliterated to the bit-pattern for an "unsign" (the lack of an "operational sign"). An "unsign" followed by a numeric digit (which is the '0' left over from the space) will, obviously, appear as a zero.

Now, you show a single "1" for your 400-byte field and a single 0 for your two-byte numeric.

What I do is this:

DISPLAY
   ">"
   the-first-field-name
   "<"
   ">"
   the-second-field-name
   "<"
   ...

or

DISPLAY
   ">"
   the-first-field-name
   "<"
DISPLAY
   ">"
   the-second-field-name
   "<"
   ...

If you had done that, you should find 1 followed by 399 spaces for your first field (as you would expect) and space followed by zero for your second field, which you didn't expect.

If you want to specifically see this in operation:

FOO PIC X(400) JUST RIGHT.

MOVE "1" TO FOO
MOVE FOO TO BAR
DISPLAY
   ">"
   FOO
   "<"
DISPLAY
   ">"
   BAR
   "<"

And you should see what you "almost" expect. You probably want the leading zero as well (the level-number 05 is an example, whatever level-number you are using will work).

05  BAR PIC 99.
05  FILLER REDEFINES BAR.
    10  BAR-FIRST-BYTE PIC X.
        88  BAR-FIRST-BYTE-SPACE VALUE SPACE.
    10  FILLER PIC X.
...
IF BAR-FIRST-BYTE-SPACE
    MOVE ZERO TO BAR-FIRST-BYTE
END-IF

Depending on your compiler and how close it is to ANSI Standard (and which ANSI Standard) your results may differ (if so, try to get a better compiler), but:

Don't MOVE alpha-numeric which are longer than the maximum a numeric can be to a numeric;
Note that in the MOVE alpha-numeric to numeric it is the right-most bytes of the alpha-numeric which are actually moved first;
An "unsigned" numeric should/must always remain unsigned;
Always check for compiler diagnostics and correct the code so that no diagnostics are produced (where possible);
When showing examples, it is highly important to show the actual results the computer produced, not the results as interpreted by a human. " 0" is not the same as "0 " is not the same as "0".

EDIT: Looking at TS's other questions, I think Enterprise COBOL is a safe bet. This message would have been issued by the compiler:

IGYPG3112-W Alphanumeric or national sending field "FOO" exceeded 18 digits. The rightmost 18 characters were used as the sender.

Note, the "18 digits" would have been "31 digits" with compiler option ARITH(EXTEND).

Even though it is a lowly "W" which only gives a Return Code of 4, not bothering to read it is not good practice, and if you had read it you'd not have needed to ask the question - although perhaps you'd still not know how you ended up with " 0", but that is another thing.

Upvotes: 4

NealB
NealB

Reputation: 16928

Data MOVEment in COBOL is a complex subject - but here is a simplified answer to your question. Some data movement rules are straight forward and conform to what one might expect. Others are somewhat bizzar and may vary with compiler option, vendor and possibly among editions of the COBOL standard (74, 85, 2002).

With the above in mind, here is an explanation of what happend in your example.

When something 'large' is MOVEd into something 'small' truncation must occur. This is what happened when BAR was MOVEd to FOO. How that truncation occurs is determined by the receving item data type. When the receiving item is character data (PIC X), the rightmost characters will be truncated from the sending field. For numeric data the leftmost digits are truncated from the sending field. This behaviour is pretty much universal for all COBOL compilers.

As a consequense of these rules:

  • When a long 'X' field (BAR) starting with a '1' followed by a bunch of space characters is MOVEd into a shorter 'X' field the leftmost characters are transferred. This is why the '1' would be preserved when moving to another PIC X item.

  • When a long 'X' field (BAR) is moved to a '9' (numeric) datatype the rightmost characters are moved first. This is why '1' was lost, it was never moved, the last two spaces in BAR were.

So far simple enough... The next bit is more complicated. Exactly what happens is vendor, version, compiler option and character set specific. For the remainder of this example I will assume EBCDIC character sets and the IBM Enterprise COBOL compiler are being used. I also assume your program displayed b0 and not 0b.

It is universally legal in COBOL to move PIC X data to PIC 9 fields provided the PIC X field contains only digits. Most COBOL compilers only look at the lower 4 bits of a PIC 9 field when determining its numeric value. An exception is the least significant digit where the sign, or lack of one, is stored. For unsigned numerics the upper 4 bits of the least significant digit are set to 1's (hex F) as a result of the MOVE (coercion follows different rules for signed fields). The lower 4 bits are MOVEd without coercion. So, what happens when a space character is moved into a PIC 9 field? The hex representation of a SPACE is '40' (ebcdic). The upper 4 bits, '4', are flipped to 'F' and the lower 4 bits are moved as they are. This results in the least significant digit (lsd) containing 'F0' hex. This just happens to be the unsigned numeric representation for the digit '0' in a PIC 9 data item. The remaining leading digits are moved as they are (ie. '40' hex). The net result is that FOO displays as b0. However, if you were to do anything other that 'MOVE' or 'DISPLAY' FOO, the upper 4 bits of the remaining 'digits' may be coerced to zeroes as a result. This would flip their display characteristics from spaces to zeros.

The following example COBOL program and its output illustrates these points.

   IDENTIFICATION DIVISION.
   PROGRAM-ID. EXAMPLE.
   DATA DIVISION.
   WORKING-STORAGE SECTION.
   01.
       05 BAR        PIC X(10).
       05 FOO        PIC 9(2).
       05 FOOX       PIC X(2).
   PROCEDURE DIVISION.
       MOVE '1         ' TO BAR
       MOVE BAR TO FOO
       MOVE BAR TO FOOX
       DISPLAY 'FOO : >' FOO '< Leftmost trunctaion + lsd coercion'
       DISPLAY 'FOOX: >' FOOX '< Righmost truncation'
       ADD ZERO TO FOO
       DISPLAY 'FOO : >' FOO '< full numeric coercion'
       GOBACK
       .

Output:

FOO : > 0< Leftmost trunctaion, lsd coercion
FOOX: >1 < Righmost truncation
FOO : >00< full numeric coercion

Final words... Best not to have to know anything about this sort to thing. Do not write programs that rely on obscure truncation rules and/or data type coercion. Be precise and explicit in what you are doing.

Upvotes: 6

Glenn1234
Glenn1234

Reputation: 2582

I gather you expect the 9(2) value to show up as "1" instead of "0" and you are confused as to why it does not?

You are moving values from left to right when you move from an X value (unless the destination value changes things). So the 9 value has a space in it. To simplify it, moving "X(2) value '1 '" to a 9(2) value literally moves those characters. The space makes what is in the 9(2) invalid, so the COBOL compiler does with it what it knows to do, return 0. In other words, defining the 9(2) as it does tells the compiler to interpret the data in a different way.

If you want the 9(2) to show up as "1", you have to present the data in the right way to the 9(2). A 9(2) with a value of 1 has the characters "01". Untested:

03  FOO       PIC X(2) value '1'.
03  TEXT-01   PIC X(2) JUSTIFIED RIGHT.
03  NUMB-01 REDEFINES TEXT-01 PIC 9(2).
03  BAR       PIC 9(2).

DISPLAY FOO.
MOVE FOO TO TEXT-01.
INSPECT TEXT-01 REPLACING LEADING ' ' BY '0'. 
MOVE NUMB-01 TO BAR.
DISPLAY BAR.

Using the NUMERIC test against BAR in your example should fail as well...

Upvotes: 2

Related Questions