Addition on a PIC 9 zone with space characters

I expected the ADD instruction in the following COBOL program to trigger an ABEND S0C7. However the program terminated normally and the ouput was quite surprising.

The SYSIN in the JCL

//SYSIN   DD *
5
//* There is only the character 5 in the SYSIN (well, followed by a newline character of course)

The COBOL program

WORKING-STORAGE SECTION.
77 X                     PIC 9(10).

PROCEDURE DIVISION.
    ACCEPT X
    ADD 1                TO X
    DISPLAY 'X = ' X
    STOP RUN
    .

The output

X = 5000000001

I then ran the program in a debugger

The ACCEPT statement moved a ‘5’ in the leftmost character of X and spaces in the others on the right. So to be more specific, X looked like this after the ACCEPT:

'9         '   <-- These are the 10 characters of X
 0987654321    <-- These are the bytes numbered for clarity

I thought maybe the display of X of my debugger had a bug and showed me space characters instead of zeros but no. I checked the memory at X and it really contained nine bytes with the value 0x40 which are indeed ’ ’ characters in EBCDIC.

I then checked the assembly generated by the compiler

Well, I forgot to copy the exact output from my machine at work but here is the assembly code in pseudo language.

*                 ADD 1                TO X
    PACK  XP, X         * Pack X to XP
    AP    XP, ONEP      * XP += 1
    UNPK  XP, X         * Unpack XP to X
  • ONEP is the address where 1 is stored in a packed format.

I then learned about the PACK instruction

From what I understood, PACK starts by swapping the two nibbles of the right source byte and put them in the right byte of the destination. So the 0x40 of X becomes 0x04 in the right byte of XP which is an invalid byte for a packed decimal.

So, what am I missing here?

Thanks for your help.

Basically, SOC7 happens when target field is not initiated properly. Code like this will do what you want.
01 WS-FIELDS.
05 Z PIC X(3) VALUE ‘ZZZ’.
05 Z9 REDEFINES Z PIC 9(3).

ADD 1 TO Z9. - this statement will cous SOC7, because Z9 contains non numeric value.
I hope this will help.