How access array in copybook from cobol to local in natural?

Alysson, it would help us understand the problem if you could show how the arrays are defined in the Cobol DFHCOMMAREA and in the Natural #LOCAL data area. For the values in the passed parameters to match up correctly, the internal memory layouts of both parameter areas must match up. Just because they look the same at the source level doesn’t mean they will match up the same at the internal memory level. As Wolfgang explained, Natural doesn’t align groups in memory the same way Cobol does.

The fact that only the 1st occurrence of the first parameter #X1 gets the correct value indicates to me that the arrays are not aligned correctly.

So do your arrays look something like this? (Sorry my Cobol is a bit rusty…)

LINKAGE SECTION
01 DFHCOMMAREA.
02 … other variables?
02 X-ARRAY (10)
05 x1 PIC S9(04) COMP-5
05 x2 PIC S9(04) COMP-5
05 x3 PIC S9(04) COMP-5
05 x4 PIC X(06)
05 x5 PIC S9(04) COMP-5

Natural

DEFINE DATA LOCAL
1 #LOCAL
2 … other variables?
2 #X-ARRAY (10)
3 #x1 (I02)
3 #x2 (I02)
3 #x3 (I02)
3 #x4 (A06)
3 #x5 (I02)

If this is how you are setting up the array definitions I don’t think it will work. But it would really help us help you if you would show us how your arrays are defined so we can stop guessing.

Thank you,
George

in the cobol is 01 DFHCOMMAREA. plus the copybook. the copybook is like:
03 TAB-OCR OCCURS 0150 TIMES.
05 x1 PIC S9(04) COMP-5
05 x2 PIC S9(04) COMP-5
05 x3 PIC S9(04) COMP-5
05 x4 PIC X(06)
05 x5 PIC S9(04) COMP-5

Natural:
1 #LOCAL
2 … other variables?
2 #X-ARRAY (1:150)
3 #x1 (I02)
3 #x2 (I02)
3 #x3 (I02)
3 #x4 (A06)
3 #x5 (I02)

OK, that’s good to confirm. Sorry I don’t have mainframe access anymore, but maybe I can get a PC Natural version running in a little bit to check out some things, but assuming my memory is still more or less correct, and hopefully Wolfgang will correct me if I’m totally off base, this is what I remember how these would be laid out internally.

Cobol lays out like the table:

X1(001) X2 (001) X3 (001) X4 (001) X5 (001)
X1(002) X2 (002) X3 (002) X4 (002) X5 (002)

X1(150) X2 (150) X3 (150) X4 (150) X5 (150)

… and I am pretty sure that Natural lays them out in individual arrays like this:

#X1 (001) #X1 (002) #X1 (003) … #X1 (150)
#X2 (001) #X2 (002) #X2 (003) … #X2 (150)
#X3 (001) #X3 (002) #X3 (003) … #X3 (150)
#X4 (001) #X4 (002) #X4 (003) … #X4 (150)
#X5 (001) #X5 (002) #X5 (003) … #X5 (150)

So maybe you can confirm this by redefining #X-ARRAY as #X-TEMP (A2100) and displaying #X-TEMP (EM=H(2100)) right after the return from the Cobol routine. Or maybe you could just display #X1 (002) to see if it contains the value from Cobol’s X2, 00002, and #X1 (003) should have X3 = 09909.

Hope that helps,
George

Basically Natural will allocate the array the way you sketch for Cobol, @George_Cooper
BUT (there always is a BUT, isn’t there ?)

For %P=C , the restriction applies that group arrays cannot be passed"

In that case Natural will “flatten” the array and it will really end up as

#X1 (001) #X1 (002) #X1 (003) … #X1 (150)
#X2 (001) #X2 (002) #X2 (003) … #X2 (150)

BUT [2] you won’t see this with a REDEFINE as it is only passed to the called program this way.

So @alysson.oliveira please read up on the implications of P=C and make sure the COBOL and NATURAL definitions match.

Thanks for the clarification and the link to the %P=C doc page. I remember now why I hated CICS and only wanted to work on “pure” Natural applications.

So, the documentation says either define both Cobol and Natural the same with individual arrays so they match up internally, or I guess if the Cobol copybook can’t be changed, (3rd party product, other Cobol users, etc.) then redefine the Natural parameters as individual rows, and then redefine #X1, #X2 variables over the row…?

Something like this ?

Natural:
1 #LOCAL
2 … other variables?
2 #X-ARRAY-ROW (A14/1:150)
2 REDEFINE #X-ARRAY-ROW
3 #x1 (I02)
3 #x2 (I02)
3 #x3 (I02)
3 #x4 (A06)
3 #x5 (I02)

I think this would get the data passed across correctly, but not sure if #X1 can be referenced as array or if array syntax only works at the #X-ARRAY-ROW level, requiring movement into LOCAL arrays.

Cheers, and good luck @alysson.oliveira,
George

Hello,
sorry for the delay in awnsered back. i was trying the sugestions. i tried pass the individual array and also tried redefine group to the array. both doesn’t work. i keep the same result. the first field correct and the rest of the array off…

I don’t have a COBOL compiler to test this myself, but I suggest that you try

DEFINE DATA LOCAL
1 #M (I4)   CONST <10>
1 #LOCAL
  2 ... other variables
  2 #X-ARRAY
    3 #X1 (I02/#M)
    3 #X2 (I02/#M)
    3 #X3 (I02/#M)
    3 #X4 (A06/#M)
    3 #X5 (I02/#M)
END-DEFINE
CALL "PGM-NAME" USING #LOCAL
END

i just did now, and still the same… :frowning:

try it
#X1 (I02/1:10)

OR
#X1 (I02/1:#M)

Alysson Oliveira via Software AG Tech Community & Forums <techcommunity@discoursemail.com> escreveu no dia segunda, 18/04/2022 à(s) 15:45:

i just tried both and still the same result… :frowning:

Hi Alysson,

I’m sorry I left my last proposed solution only partially built. I finally got my PC Natural version working, sort of, but I could not figure out how to index through the #Xi’s when redefined over the parameter data area like this.

1 #LOCAL
2 #X-ARRAY-ROW (A14/1:150)
2 REDEFINE #X-ARRAY-ROW
3 #x1 (I02)
3 #x2 (I02)
3 #x3 (I02)
3 #x4 (A06)
3 #x5 (I02)

But this is close to the solution I had in mind. You will have to move the data out of each #X-ARRAY_ROW (i) into locally defined individual #X1(), #X2 () … #X5(*) separate arrays. I think this code sample does that for you.

Define Data Local
1 #LOCAL
** Other parms ?
2 #X-ARRAY (A14/1:150)
*
1 #LOCAL-VARIABLES
2 #X-ARRAY-ROW (A14)
2 REDEFINE #X-ARRAY-ROW
3 #x1-row (I02)
3 #x2-row (I02)
3 #x3-row (I02)
3 #x4-row (A06)
3 #x5-row (I02)

2 #x1 (I02/150)
2 #x2 (I02/150)
2 #x3 (I02/150)
2 #x4 (A06/150)
2 #x5 (I02/150)
*
1 #I (I4)
END-DEFINE

SET CONTROL ‘P=C’
CALL ‘PGM-Name’ USING #LOCAL
*

  • Now move the array passed from Cobol routine to #Xi arrays, 1 row/occurrence at a time

FOR #I = 1 to 150
MOVE #X-ARRAY (#I) TO #X-ARRAY-ROW
#X1 (#I) := #x1-row
#X2 (#I) := #x2-row
#X3 (#I) := #x3-row
#X4 (#I) := #x4-row
#X5 (#I) := #x5-row
END-FOR
*
** Now #X1(), #X2(), #X3(), X4(), and #X5(*) should match the Cobol X1, X2, etc. arrays, and can be processed normally within Natural programs.
** But if you need to pass them back to the Cobol system, (hopefully not) then you would need to
reverse this process to rebuild the #X-ARRAY parameter for Cobol.

END

I hope that works for you. Let us know.
Good luck!
George

As Wolfgang pointed out, passing “#LOCAL” will expand into the elements of #LOCAL. Without seeing the full data area defined for DFHCOMMAREA, we can’t see what is really expected by the COBOL program. If it is indeed one Level 1 parameter, then there can only be ONE parameter passed from Natural that is the address of the start of the data area. If there are “other parms” then the FIRST of these “other parms” is the ONLY variable that should be passed to COBOL from Natural. If there are no “other parms”, then just pass #X-ARRAY(1):

CALL ‘PGM-NAME’ USING #X-ARRAY(1)

This topic was automatically closed 90 days after the last reply. New replies are no longer allowed.