Re: COBOL Field Length problem

2023-05-25 Thread Frank Swarbrick
I'm going to go out on a limb and say it's a compiler bug.  I recreated the 
issue (with this program) with both V6.3 and V6.4.

I also "solved" the issue by using BYTE-LENGTH instead of LENGTH.  But that's 
just a work-around, of course.  So you need to open a CASE with IBM to get it 
fixed.

From: IBM Mainframe Discussion List  on behalf of 
Binyamin Dissen 
Sent: Wednesday, May 24, 2023 10:42 AM
To: IBM-MAIN@LISTSERV.UA.EDU 
Subject: Re: COBOL Field Length problem

My next step would be to look at the generated code to see if it is using the
right element. I am not super trustful of compilers.

On Wed, 24 May 2023 16:25:21 + Billy Ashton 
wrote:

:>Hey everyone - back again with another COBOL problem. Your help with my
:>COPY REPLACING question was great and the programmer is quite happy with
:>that solution. Now, he came to me with what looks like a problem, and I
:>am not sure if we are doing something wrong, or if it is a bug in our
:>Enterprise COBOL for z/OS  6.3.0 P220314 system.
:>
:>In a nutshell, when using the LENGTH(TRIM(some-field)) function against
:>any elementary data item, it works great. However, when using it against
:>an item within an occurs (think data table), every reference beyond 1
:>gets handled as item #1. For example, if I have a group with 8 items,
:>the length of item #1 is right, but the length of item(2) through
:>item(8) is always the value of item(1). The table index can be display
:>numeric, packed, or binary, and the results are the same, so I don't
:>think it is a problem with the index, but somehow the reference is not
:>resolved correctly within the nested function.
:>
:>Maybe a short program would be helpful. I hope a 60 line program is ok!
:>Let me know what you think is happening.
:>
:>IDENTIFICATION DIVISION.
:>PROGRAM-ID. TSTPG002.
:>ENVIRONMENT DIVISION.
:>Configuration   Section.
:>Repository.
:>Function  All  Intrinsic.
:>DATA DIVISION.
:>WORKING-STORAGE SECTION.
:>01  WS.
:>05  INL-NO  PIC S9(08)  VALUE ZERO BINARY.
:>05  INL-I1  PIC S9(08)  VALUE ZERO BINARY.
:>05  INL-I2  PIC S9(08)  VALUE ZERO BINARY.
:>05  INL-H   PIC S9(08)  VALUE ZERO BINARY.
:>05  IN-GRP-X.
:>10  L1 PIC X(65) VALUE '* THIS_IS_A_COMMENT Here .28'.
:>10  L2 PIC X(65) VALUE SPACE.
:>10  L3 PIC X(65) VALUE 'COMND   VALUE1 17'.
:>10  L4 PIC X(65) VALUE 'COMND   VALUE2 21'.
:>10  L5 PIC X(65) VALUE '  COMND VALUE3 21'.
:>10  L6 PIC X(65) VALUE 'COMND VALUE4 15  '.
:>10  L7 PIC X(65) VALUE ' COMND  VAL* 27 '.
:>10  L8 PIC X(65) VALUE '* THIS_IS_A_COMMENT... 29'.
:>05   REDEFINES IN-GRP-X  OCCURS 8.
:>10  IN-LINE PIC  X(65).
:>05  Hold-L  PIC  X(65).
:>05  I1  PIC S9(08)  VALUE ZERO Binary.
:>05  I2  PIC S9(08)  VALUE ZERO.
:>
:>PROCEDURE DIVISION.
:>PERFORM VARYING I1 FROM 1 BY 1 UNTIL I1 GREATER 8
:>Move I1 to I2
:>Move In-line(I1) to Hold-L
:>Display I1 '  '
:>'+1+2+3+4'
:>'+5+6+'
:>Display '   Original: >' IN-LINE(I1) '<'
:>Display '   Trim: >' Trim(In-line(I1) Trailing) '<'
:>Compute INL-I1 = Length(Trim(In-line(I1) Trailing))
:>Compute INL-I2 = Length(Trim(In-line(I2) Trailing))
:>Compute INL-H  = Length(Trim(Hold-L  Trailing))
:>Evaluate TRUE
:>  When I1 = 1 Compute INL-NO = Length(Trim(L1 Trailing))
:>  When I1 = 2 Compute INL-NO = Length(Trim(L2 Trailing))
:>  When I1 = 3 Compute INL-NO = Length(Trim(L3 Trailing))
:>  When I1 = 4 Compute INL-NO = Length(Trim(L4 Trailing))
:>  When I1 = 5 Compute INL-NO = Length(Trim(L5 Trailing))
:>  When I1 = 6 Compute INL-NO = Length(Trim(L6 Trailing))
:>  When I1 = 7 Compute INL-NO = Length(Trim(L7 Trailing))
:>  When Other  Compute INL-NO = Length(Trim(L8 Trailing))
:>End-Evaluate
:>Display '   Lengths:'
:>'   I1(' INL-I1 ')'
:>' I2(' INL-I2 ')'
:>' Hold(' INL-H ')'
:>' By name(' INL-NO ')'
:>Display ' '
:>END-PERFORM
:&

Re: COBOL Field Length problem

2023-05-24 Thread Jon Butler
It works for me using the Repository definition.  If you look at the variable 
list at the end of the compilation you will see all the intrinsic functions 
listed...if you coded "Repository. Function all Intrinsic."

1 filler.  
  3 input-array  occurs 10 times   
   pic x(15) value 'AB23.45D'. 

move '  XYZ' to input-array(1)
move trim(input-array(1), trailing) to Variable-data   
display 'Variable-Data = "' Variable-Data '"'
compute Char-Length = length(trim(input-array(1), trailing))   
display 'Variable-Length = ' Char-Length

Variable-Data = "  XYZ"  
Variable-Length = +5

Cheers,

Jon Butler

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL Field Length problem

2023-05-24 Thread Billy Ashton

Just for fun, I tried another quick 6.3 test using the Repository setup.

Here are the nested function results:
Function Length(Function Trim(indexed field))  - Worked fine
Function Length( Trim(indexed field))  - Worked fine
 Length(Function Trim(indexed field))  - Failed - only used 
indexedfield(1)
 Length( Trim(indexed field))  - Failed - only used 
indexedfield(1)


So it seems the problem seems to be with the Length function, when 
called using the Repository Intrinsic functions description.


Got to get this programmer back in the saddle, so that's all I have time 
for here. Thanks again!


Billy

-- Original Message --

From "Billy Ashton" 

To "IBM Mainframe Discussion List" 
Date 5/24/2023 1:24:05 PM
Subject Re[2]: COBOL Field Length problem


Michael, you gave me something interesting to try. It seems the Configuration 
Section use of the Repository for Intrinsic functions is new with 6.3, as it 
did not compile under 6.2.

So...I removed that paragraph and added the explicit references to the FUNCTION 
keyword and got the same results that you did - everything worked fine. I then 
moved up to 6.3 with that working code, and guess what? It worked there, too.

So it seems that there is some problem with how that Repository Intrinsic 
function thing is not working, and I haven't the time to chase it down right 
now. I will just use explicit FUNCTION calls to get past the problem.

Thanks for pointing me the right direction through the fog!
Billy Ashton


-- Original Message --
From "Schmitt, Michael" 
To IBM-MAIN@listserv.ua.edu
Date 5/24/2023 1:03:18 PM
Subject Re: COBOL Field Length problem


I don't have 6.3, but I tried your program on 6.2 after adding FUNCTION before 
the TRIM and LENGTH functions.

The results seem to be as expected.  For example:

0005  +1+2+3+4+5+6+
   Original: >  COMND VALUE3 21<
   Trim: >  COMND VALUE3 21<
   Lengths:   I1(0021) I2(0021) Hold(0021) By name(0021)

0006  +1+2+3+4+5+6+
   Original: >COMND VALUE4 15  <
   Trim: >COMND VALUE4 15<
   Lengths:   I1(0015) I2(0015) Hold(0015) By name(0015)


I'd suggest reducing the test case down to the MINIMUM amount of code that 
demonstrates the issue.

Then look at the p-map to see what the compiler is doing.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Billy Ashton
Sent: Wednesday, May 24, 2023 11:25 AM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: COBOL Field Length problem

Hey everyone - back again with another COBOL problem. Your help with my
COPY REPLACING question was great and the programmer is quite happy with
that solution. Now, he came to me with what looks like a problem, and I
am not sure if we are doing something wrong, or if it is a bug in our
Enterprise COBOL for z/OS  6.3.0 P220314 system.

In a nutshell, when using the LENGTH(TRIM(some-field)) function against
any elementary data item, it works great. However, when using it against
an item within an occurs (think data table), every reference beyond 1
gets handled as item #1. For example, if I have a group with 8 items,
the length of item #1 is right, but the length of item(2) through
item(8) is always the value of item(1). The table index can be display
numeric, packed, or binary, and the results are the same, so I don't
think it is a problem with the index, but somehow the reference is not
resolved correctly within the nested function.

Maybe a short program would be helpful. I hope a 60 line program is ok!
Let me know what you think is happening.

IDENTIFICATION DIVISION.
PROGRAM-ID. TSTPG002.
ENVIRONMENT DIVISION.
Configuration   Section.
Repository.
Function  All  Intrinsic.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  WS.
05  INL-NO  PIC S9(08)  VALUE ZERO BINARY.
05  INL-I1  PIC S9(08)  VALUE ZERO BINARY.
05  INL-I2  PIC S9(08)  VALUE ZERO BINARY.
05  INL-H   PIC S9(08)  VALUE ZERO BINARY.
05  IN-GRP-X.
10  L1 PIC X(65) VALUE '* THIS_IS_A_COMMENT Here .28'.
10  L2 PIC X(65) VALUE SPACE.
10  L3 PIC X(65) VALUE 'COMND   VALUE1 17'.
10  L4 PIC X(65) VALUE 'COMND   VALUE2 21'.
10  L5 PIC X(65) VALUE '  COMND VALUE3 21'.
10  L6 PIC X(65) VALUE 'COMND VALUE4 15  '.
10  L7 PIC X(65) VALUE ' COMND  VAL* 27 '.
10  L8 PIC X(65) VALUE '* THIS_IS_A_COMMENT... 29'.
05   REDEFINES IN-GRP-X  OCCURS 8.
10  IN-LINE PIC  X(65).
05  Hold

Re: COBOL Field Length problem

2023-05-24 Thread Billy Ashton
Michael, you gave me something interesting to try. It seems the 
Configuration Section use of the Repository for Intrinsic functions is 
new with 6.3, as it did not compile under 6.2.


So...I removed that paragraph and added the explicit references to the 
FUNCTION keyword and got the same results that you did - everything 
worked fine. I then moved up to 6.3 with that working code, and guess 
what? It worked there, too.


So it seems that there is some problem with how that Repository 
Intrinsic function thing is not working, and I haven't the time to chase 
it down right now. I will just use explicit FUNCTION calls to get past 
the problem.


Thanks for pointing me the right direction through the fog!
Billy Ashton


-- Original Message --

From "Schmitt, Michael" 

To IBM-MAIN@listserv.ua.edu
Date 5/24/2023 1:03:18 PM
Subject Re: COBOL Field Length problem


I don't have 6.3, but I tried your program on 6.2 after adding FUNCTION before 
the TRIM and LENGTH functions.

The results seem to be as expected.  For example:

0005  +1+2+3+4+5+6+
   Original: >  COMND VALUE3 21<
   Trim: >  COMND VALUE3 21<
   Lengths:   I1(0021) I2(0021) Hold(0021) By name(0021)

0006  +1+2+3+4+5+6+
   Original: >COMND VALUE4 15  <
   Trim: >COMND VALUE4 15<
   Lengths:   I1(0015) I2(0015) Hold(0015) By name(0015)


I'd suggest reducing the test case down to the MINIMUM amount of code that 
demonstrates the issue.

Then look at the p-map to see what the compiler is doing.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Billy Ashton
Sent: Wednesday, May 24, 2023 11:25 AM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: COBOL Field Length problem

Hey everyone - back again with another COBOL problem. Your help with my
COPY REPLACING question was great and the programmer is quite happy with
that solution. Now, he came to me with what looks like a problem, and I
am not sure if we are doing something wrong, or if it is a bug in our
Enterprise COBOL for z/OS  6.3.0 P220314 system.

In a nutshell, when using the LENGTH(TRIM(some-field)) function against
any elementary data item, it works great. However, when using it against
an item within an occurs (think data table), every reference beyond 1
gets handled as item #1. For example, if I have a group with 8 items,
the length of item #1 is right, but the length of item(2) through
item(8) is always the value of item(1). The table index can be display
numeric, packed, or binary, and the results are the same, so I don't
think it is a problem with the index, but somehow the reference is not
resolved correctly within the nested function.

Maybe a short program would be helpful. I hope a 60 line program is ok!
Let me know what you think is happening.

IDENTIFICATION DIVISION.
PROGRAM-ID. TSTPG002.
ENVIRONMENT DIVISION.
Configuration   Section.
Repository.
Function  All  Intrinsic.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  WS.
05  INL-NO  PIC S9(08)  VALUE ZERO BINARY.
05  INL-I1  PIC S9(08)  VALUE ZERO BINARY.
05  INL-I2  PIC S9(08)  VALUE ZERO BINARY.
05  INL-H   PIC S9(08)  VALUE ZERO BINARY.
05  IN-GRP-X.
10  L1 PIC X(65) VALUE '* THIS_IS_A_COMMENT Here .28'.
10  L2 PIC X(65) VALUE SPACE.
10  L3 PIC X(65) VALUE 'COMND   VALUE1 17'.
10  L4 PIC X(65) VALUE 'COMND   VALUE2 21'.
10  L5 PIC X(65) VALUE '  COMND VALUE3 21'.
10  L6 PIC X(65) VALUE 'COMND VALUE4 15  '.
10  L7 PIC X(65) VALUE ' COMND  VAL* 27 '.
10  L8 PIC X(65) VALUE '* THIS_IS_A_COMMENT... 29'.
05   REDEFINES IN-GRP-X  OCCURS 8.
10  IN-LINE PIC  X(65).
05  Hold-L  PIC  X(65).
05  I1  PIC S9(08)  VALUE ZERO Binary.
05  I2  PIC S9(08)  VALUE ZERO.

PROCEDURE DIVISION.
PERFORM VARYING I1 FROM 1 BY 1 UNTIL I1 GREATER 8
Move I1 to I2
Move In-line(I1) to Hold-L
Display I1 '  '
'+1+2+3+4'
'+5+6+'
Display '   Original: >' IN-LINE(I1) '<'
Display '   Trim: >' Trim(In-line(I1) Trailing) '<'
Compute INL-I1 = Length(Trim(In-line(I1) Trailing))
Compute INL-I2 = Length(Trim(In-line(I2) Trailing))
Compute INL-H  = Length(Trim(Hold-L  Trailing))
Evalu

Re: COBOL Field Length problem

2023-05-24 Thread Schmitt, Michael
I don't have 6.3, but I tried your program on 6.2 after adding FUNCTION before 
the TRIM and LENGTH functions.

The results seem to be as expected.  For example:

0005  +1+2+3+4+5+6+
   Original: >  COMND VALUE3 21<
   Trim: >  COMND VALUE3 21<
   Lengths:   I1(0021) I2(0021) Hold(0021) By name(0021)

0006  +1+2+3+4+5+6+
   Original: >COMND VALUE4 15  <
   Trim: >COMND VALUE4 15<
   Lengths:   I1(0015) I2(0015) Hold(0015) By name(0015)


I'd suggest reducing the test case down to the MINIMUM amount of code that 
demonstrates the issue.

Then look at the p-map to see what the compiler is doing.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Billy Ashton
Sent: Wednesday, May 24, 2023 11:25 AM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: COBOL Field Length problem

Hey everyone - back again with another COBOL problem. Your help with my
COPY REPLACING question was great and the programmer is quite happy with
that solution. Now, he came to me with what looks like a problem, and I
am not sure if we are doing something wrong, or if it is a bug in our
Enterprise COBOL for z/OS  6.3.0 P220314 system.

In a nutshell, when using the LENGTH(TRIM(some-field)) function against
any elementary data item, it works great. However, when using it against
an item within an occurs (think data table), every reference beyond 1
gets handled as item #1. For example, if I have a group with 8 items,
the length of item #1 is right, but the length of item(2) through
item(8) is always the value of item(1). The table index can be display
numeric, packed, or binary, and the results are the same, so I don't
think it is a problem with the index, but somehow the reference is not
resolved correctly within the nested function.

Maybe a short program would be helpful. I hope a 60 line program is ok!
Let me know what you think is happening.

IDENTIFICATION DIVISION.
PROGRAM-ID. TSTPG002.
ENVIRONMENT DIVISION.
Configuration   Section.
Repository.
Function  All  Intrinsic.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  WS.
05  INL-NO  PIC S9(08)  VALUE ZERO BINARY.
05  INL-I1  PIC S9(08)  VALUE ZERO BINARY.
05  INL-I2  PIC S9(08)  VALUE ZERO BINARY.
05  INL-H   PIC S9(08)  VALUE ZERO BINARY.
05  IN-GRP-X.
10  L1 PIC X(65) VALUE '* THIS_IS_A_COMMENT Here .28'.
10  L2 PIC X(65) VALUE SPACE.
10  L3 PIC X(65) VALUE 'COMND   VALUE1 17'.
10  L4 PIC X(65) VALUE 'COMND   VALUE2 21'.
10  L5 PIC X(65) VALUE '  COMND VALUE3 21'.
10  L6 PIC X(65) VALUE 'COMND VALUE4 15  '.
10  L7 PIC X(65) VALUE ' COMND  VAL* 27 '.
10  L8 PIC X(65) VALUE '* THIS_IS_A_COMMENT... 29'.
05   REDEFINES IN-GRP-X  OCCURS 8.
10  IN-LINE PIC  X(65).
05  Hold-L  PIC  X(65).
05  I1  PIC S9(08)  VALUE ZERO Binary.
05  I2  PIC S9(08)  VALUE ZERO.

PROCEDURE DIVISION.
PERFORM VARYING I1 FROM 1 BY 1 UNTIL I1 GREATER 8
Move I1 to I2
Move In-line(I1) to Hold-L
Display I1 '  '
'+1+2+3+4'
'+5+6+'
Display '   Original: >' IN-LINE(I1) '<'
Display '   Trim: >' Trim(In-line(I1) Trailing) '<'
Compute INL-I1 = Length(Trim(In-line(I1) Trailing))
Compute INL-I2 = Length(Trim(In-line(I2) Trailing))
Compute INL-H  = Length(Trim(Hold-L  Trailing))
Evaluate TRUE
  When I1 = 1 Compute INL-NO = Length(Trim(L1 Trailing))
  When I1 = 2 Compute INL-NO = Length(Trim(L2 Trailing))
  When I1 = 3 Compute INL-NO = Length(Trim(L3 Trailing))
  When I1 = 4 Compute INL-NO = Length(Trim(L4 Trailing))
  When I1 = 5 Compute INL-NO = Length(Trim(L5 Trailing))
  When I1 = 6 Compute INL-NO = Length(Trim(L6 Trailing))
  When I1 = 7 Compute INL-NO = Length(Trim(L7 Trailing))
  When Other  Compute INL-NO = Length(Trim(L8 Trailing))
End-Evaluate
Display '   Lengths:'
'   I1(' INL-I1 ')'
' I2(' INL-I2 ')'
' Hold(' INL-H ')'
' By name(' INL-NO ')'
Display ' '
END-PERFORM
   

Re: COBOL Field Length problem

2023-05-24 Thread Binyamin Dissen
My next step would be to look at the generated code to see if it is using the
right element. I am not super trustful of compilers.

On Wed, 24 May 2023 16:25:21 + Billy Ashton 
wrote:

:>Hey everyone - back again with another COBOL problem. Your help with my 
:>COPY REPLACING question was great and the programmer is quite happy with 
:>that solution. Now, he came to me with what looks like a problem, and I 
:>am not sure if we are doing something wrong, or if it is a bug in our 
:>Enterprise COBOL for z/OS  6.3.0 P220314 system.
:>
:>In a nutshell, when using the LENGTH(TRIM(some-field)) function against 
:>any elementary data item, it works great. However, when using it against 
:>an item within an occurs (think data table), every reference beyond 1 
:>gets handled as item #1. For example, if I have a group with 8 items, 
:>the length of item #1 is right, but the length of item(2) through 
:>item(8) is always the value of item(1). The table index can be display 
:>numeric, packed, or binary, and the results are the same, so I don't 
:>think it is a problem with the index, but somehow the reference is not 
:>resolved correctly within the nested function.
:>
:>Maybe a short program would be helpful. I hope a 60 line program is ok! 
:>Let me know what you think is happening.
:>
:>IDENTIFICATION DIVISION.
:>PROGRAM-ID. TSTPG002.
:>ENVIRONMENT DIVISION.
:>Configuration   Section.
:>Repository.
:>Function  All  Intrinsic.
:>DATA DIVISION.
:>WORKING-STORAGE SECTION.
:>01  WS.
:>05  INL-NO  PIC S9(08)  VALUE ZERO BINARY.
:>05  INL-I1  PIC S9(08)  VALUE ZERO BINARY.
:>05  INL-I2  PIC S9(08)  VALUE ZERO BINARY.
:>05  INL-H   PIC S9(08)  VALUE ZERO BINARY.
:>05  IN-GRP-X.
:>10  L1 PIC X(65) VALUE '* THIS_IS_A_COMMENT Here .28'.
:>10  L2 PIC X(65) VALUE SPACE.
:>10  L3 PIC X(65) VALUE 'COMND   VALUE1 17'.
:>10  L4 PIC X(65) VALUE 'COMND   VALUE2 21'.
:>10  L5 PIC X(65) VALUE '  COMND VALUE3 21'.
:>10  L6 PIC X(65) VALUE 'COMND VALUE4 15  '.
:>10  L7 PIC X(65) VALUE ' COMND  VAL* 27 '.
:>10  L8 PIC X(65) VALUE '* THIS_IS_A_COMMENT... 29'.
:>05   REDEFINES IN-GRP-X  OCCURS 8.
:>10  IN-LINE PIC  X(65).
:>05  Hold-L  PIC  X(65).
:>05  I1  PIC S9(08)  VALUE ZERO Binary.
:>05  I2  PIC S9(08)  VALUE ZERO.
:>
:>PROCEDURE DIVISION.
:>PERFORM VARYING I1 FROM 1 BY 1 UNTIL I1 GREATER 8
:>Move I1 to I2
:>Move In-line(I1) to Hold-L
:>Display I1 '  '
:>'+1+2+3+4'
:>'+5+6+'
:>Display '   Original: >' IN-LINE(I1) '<'
:>Display '   Trim: >' Trim(In-line(I1) Trailing) '<'
:>Compute INL-I1 = Length(Trim(In-line(I1) Trailing))
:>Compute INL-I2 = Length(Trim(In-line(I2) Trailing))
:>Compute INL-H  = Length(Trim(Hold-L  Trailing))
:>Evaluate TRUE
:>  When I1 = 1 Compute INL-NO = Length(Trim(L1 Trailing))
:>  When I1 = 2 Compute INL-NO = Length(Trim(L2 Trailing))
:>  When I1 = 3 Compute INL-NO = Length(Trim(L3 Trailing))
:>  When I1 = 4 Compute INL-NO = Length(Trim(L4 Trailing))
:>  When I1 = 5 Compute INL-NO = Length(Trim(L5 Trailing))
:>  When I1 = 6 Compute INL-NO = Length(Trim(L6 Trailing))
:>  When I1 = 7 Compute INL-NO = Length(Trim(L7 Trailing))
:>  When Other  Compute INL-NO = Length(Trim(L8 Trailing))
:>End-Evaluate
:>Display '   Lengths:'
:>'   I1(' INL-I1 ')'
:>' I2(' INL-I2 ')'
:>' Hold(' INL-H ')'
:>' By name(' INL-NO ')'
:>Display ' '
:>END-PERFORM
:>GOBACK.
:>
:>Thank you and best regards,
:>Billy Ashton
:>
:>--
:>For IBM-MAIN subscribe / signoff / archive access instructions,
:>send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
Binyamin Dissen 
http://www.dissensoftware.com

Director, Dissen Software, Bar & Grill - Israel

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


COBOL Field Length problem

2023-05-24 Thread Billy Ashton
Hey everyone - back again with another COBOL problem. Your help with my 
COPY REPLACING question was great and the programmer is quite happy with 
that solution. Now, he came to me with what looks like a problem, and I 
am not sure if we are doing something wrong, or if it is a bug in our 
Enterprise COBOL for z/OS  6.3.0 P220314 system.


In a nutshell, when using the LENGTH(TRIM(some-field)) function against 
any elementary data item, it works great. However, when using it against 
an item within an occurs (think data table), every reference beyond 1 
gets handled as item #1. For example, if I have a group with 8 items, 
the length of item #1 is right, but the length of item(2) through 
item(8) is always the value of item(1). The table index can be display 
numeric, packed, or binary, and the results are the same, so I don't 
think it is a problem with the index, but somehow the reference is not 
resolved correctly within the nested function.


Maybe a short program would be helpful. I hope a 60 line program is ok! 
Let me know what you think is happening.


   IDENTIFICATION DIVISION.
   PROGRAM-ID. TSTPG002.
   ENVIRONMENT DIVISION.
   Configuration   Section.
   Repository.
   Function  All  Intrinsic.
   DATA DIVISION.
   WORKING-STORAGE SECTION.
   01  WS.
   05  INL-NO  PIC S9(08)  VALUE ZERO BINARY.
   05  INL-I1  PIC S9(08)  VALUE ZERO BINARY.
   05  INL-I2  PIC S9(08)  VALUE ZERO BINARY.
   05  INL-H   PIC S9(08)  VALUE ZERO BINARY.
   05  IN-GRP-X.
   10  L1 PIC X(65) VALUE '* THIS_IS_A_COMMENT Here .28'.
   10  L2 PIC X(65) VALUE SPACE.
   10  L3 PIC X(65) VALUE 'COMND   VALUE1 17'.
   10  L4 PIC X(65) VALUE 'COMND   VALUE2 21'.
   10  L5 PIC X(65) VALUE '  COMND VALUE3 21'.
   10  L6 PIC X(65) VALUE 'COMND VALUE4 15  '.
   10  L7 PIC X(65) VALUE ' COMND  VAL* 27 '.
   10  L8 PIC X(65) VALUE '* THIS_IS_A_COMMENT... 29'.
   05   REDEFINES IN-GRP-X  OCCURS 8.
   10  IN-LINE PIC  X(65).
   05  Hold-L  PIC  X(65).
   05  I1  PIC S9(08)  VALUE ZERO Binary.
   05  I2  PIC S9(08)  VALUE ZERO.

   PROCEDURE DIVISION.
   PERFORM VARYING I1 FROM 1 BY 1 UNTIL I1 GREATER 8
   Move I1 to I2
   Move In-line(I1) to Hold-L
   Display I1 '  '
   '+1+2+3+4'
   '+5+6+'
   Display '   Original: >' IN-LINE(I1) '<'
   Display '   Trim: >' Trim(In-line(I1) Trailing) '<'
   Compute INL-I1 = Length(Trim(In-line(I1) Trailing))
   Compute INL-I2 = Length(Trim(In-line(I2) Trailing))
   Compute INL-H  = Length(Trim(Hold-L  Trailing))
   Evaluate TRUE
 When I1 = 1 Compute INL-NO = Length(Trim(L1 Trailing))
 When I1 = 2 Compute INL-NO = Length(Trim(L2 Trailing))
 When I1 = 3 Compute INL-NO = Length(Trim(L3 Trailing))
 When I1 = 4 Compute INL-NO = Length(Trim(L4 Trailing))
 When I1 = 5 Compute INL-NO = Length(Trim(L5 Trailing))
 When I1 = 6 Compute INL-NO = Length(Trim(L6 Trailing))
 When I1 = 7 Compute INL-NO = Length(Trim(L7 Trailing))
 When Other  Compute INL-NO = Length(Trim(L8 Trailing))
   End-Evaluate
   Display '   Lengths:'
   '   I1(' INL-I1 ')'
   ' I2(' INL-I2 ')'
   ' Hold(' INL-H ')'
   ' By name(' INL-NO ')'
   Display ' '
   END-PERFORM
   GOBACK.

Thank you and best regards,
Billy Ashton

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN