IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

How to store 2 digit numeric data in a single byte?


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
cnugemini

New User


Joined: 11 Jun 2014
Posts: 1
Location: india

PostPosted: Thu Jun 26, 2014 8:02 pm
Reply with quote

Hi all,

Could you please help me in knowing how we can store a 2 digit numeric value in a single byte space. I want to know the Picture clause that we use to achieve this. I have only 1 byte of space left in my IMS data base, but I have to store a new 2 digit numeric value in it.

I tried googling and searching many forums, may be I wasn't efficient at it.

Thank you,
Srinivas
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Thu Jun 26, 2014 8:28 pm
Reply with quote

Code:
01  a-nice-name COMP-3 PIC 99V9.
01  FILLER REDEFINES a-nice-name.
    05  another-nice-name PIC X.
    05  FILLER PIC X.

MOVE your-two-digit-field TO a-nice-name
MOVE another-nice-name TO your-one-byte


To get it back again, just do the reverse.

Say you have 12. It appears in a-nice-name after the first MOVE as X'120F'. The REDEFINES allows another-nice-name to contain X'12', which is the value you want.
Back to top
View user's profile Send private message
Terry Heinze

JCL Moderator


Joined: 14 Jul 2008
Posts: 1249
Location: Richfield, MN, USA

PostPosted: Thu Jun 26, 2014 11:01 pm
Reply with quote

Very clever, Bill. I hope I never have to resort to the days when 8 switches had to be stored in 1 byte though! Back then, we had to rely on Assembler routines to perform our BIT2BYTE and BYTE2BIT functions.
Back to top
View user's profile Send private message
Akatsukami

Global Moderator


Joined: 03 Oct 2009
Posts: 1788
Location: Bloomington, IL

PostPosted: Thu Jun 26, 2014 11:50 pm
Reply with quote

These days one could do it in PL/I or C, possibly in COBOL itself (I'm not up on the latest bells and whistles).
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Fri Jun 27, 2014 4:10 pm
Reply with quote

Byte to bit "string".

Code:
WORKING-STORAGE:
01  HERES-OUR-VALUE-FOR-BITS BINARY PIC 9(4) VALUE ZERO.
01  FILLER REDEFINES HERES-OUR-VALUE-FOR-BITS.
    05 FILLER PIC X.
    05 BYTE-TO-CONVERT PIC X.
01 BIT-TABLE.
    05 FILLER PIC X(56) VALUE
    '00000000000000010000001000000011000001000000010100000110'.
    05 FILLER PIC X(56) VALUE
    '00000111000010000000100100001010000010110000110000001101'.
....
05 FILLER PIC X(32) VALUE
'11111100111111011111111011111111'.
01  FILLER REDEFINES BIT-TABLE.
    05 FILLER OCCURS 256 TIMES.
        10 BIT-VALUE PIC X(8).
...
    MOVE source- byte TO BYTE-TO-CONVERT
    DISPLAY "PARM>" CHAR "<BITS>"
            BIT-VALUE ( HERES-OUR-VALUE-FOR-BITS + 1 ) "<"
    GOBACK
    .


Bit string to byte:

Code:
01  HERES-OUR-VALUE-FOR-BITS BINARY PIC 9(4) VALUE ZERO.
01  FILLER REDEFINES HERES-OUR-VALUE-FOR-BITS.
    05  FILLER PIC X.
    05  BACK-AS-A-BYTE PIC X.
01  BIT-STRING.
    05  BITS.
        10  FILLER PIC X.
            88  BIT08-ON VALUE "1".
        10  FILLER PIC X.
            88  BIT07-ON VALUE "1".
        10  FILLER PIC X.
            88  BIT06-ON VALUE "1".
        10  FILLER PIC X.
            88  BIT05-ON VALUE "1".
        10  FILLER PIC X.
            88  BIT04-ON VALUE "1".
        10  FILLER PIC X.
            88  BIT03-ON VALUE "1".
        10  FILLER PIC X.
            88  BIT02-ON VALUE "1".
        10  FILLER PIC X.
            88  BIT01-ON VALUE "1".
PROCEDURE DIVISION USING PARM-IN.
    MOVE ZERO TO HERES-OUR-VALUE-FOR-BITS
    MOVE source-string TO BIT-STRING
    IF BIT08-ON
        ADD 128 TO HERES-OUR-VALUE-FOR-BITS
    END-IF
    IF BIT07-ON
        ADD 64 TO HERES-OUR-VALUE-FOR-BITS
    END-IF
    IF BIT06-ON
        ADD 32 TO HERES-OUR-VALUE-FOR-BITS
    END-IF
    IF BIT05-ON
        ADD 16 TO HERES-OUR-VALUE-FOR-BITS
    END-IF
    IF BIT04-ON
        ADD 8 TO HERES-OUR-VALUE-FOR-BITS
    END-IF
    IF BIT03-ON
        ADD 4 TO HERES-OUR-VALUE-FOR-BITS
    END-IF
    IF BIT02-ON
        ADD 2 TO HERES-OUR-VALUE-FOR-BITS
    END-IF
    IF BIT01-ON
        ADD 1 TO HERES-OUR-VALUE-FOR-BITS
    END-IF
    DISPLAY "BIT STRING>" BITS "<BYTE>" BACK-AS-A-BYTE "<"
    GOBACK
    .


Data-names for explanation only (use better ones in for-real code).

Works from COBOL Day One. First conversion is heavy on storage (people may giggle at that, but when I started we had a maximum of 1MB for the WORKING-STORAGE). Can be replaced by loops of various activities if short of WORKING-STORAGE.
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts How to save SYSLOG as text data via P... All Other Mainframe Topics 4
No new posts Issues Converting From ZD to Signed N... DFSORT/ICETOOL 4
No new posts Store the data for fixed length COBOL Programming 1
No new posts Data set Rec-Cnt and Byte-Cnt Testing & Performance 2
No new posts SCOPE PENDING option -check data DB2 2
Search our Forums:

Back to Top