Parameters changing to NULL

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

 



Gnu Crew,

I have C calling cobol like this:

      printf("LINK EIB == %p COMMAREA == %p", dfheibPointer(), Commarea);
      ProgramEntry(dfheibPointer(), Commarea);


with the cobol program looking like this:

       PROCEDURE DIVISION USING DFHEIBLK, DFHCOMMAREA.
           MOVE LENGTH OF DFHCOMMAREA TO OPENKICKS-NUM1
           SET OPENKICKS-PTR1 TO ADDRESS OF DFHCOMMAREA
           DISPLAY 'DFHCOMMAREA:' OPENKICKS-PTR1
           SET OPENKICKS-PTR1 TO ADDRESS OF DFHEIBLK
           DISPLAY 'DFHEIBLK:' OPENKICKS-PTR1
the output looks like this:
LINK EIB == 0x55ae33b6bd20 COMMAREA == 0x7fed14f78890
DFHCOMMAREA:0x0000000000000000
DFHEIBLK:0x000055ae33b6bd20

I have other identical code where COMMAREA is passed in just fine.
I am just at wits end on what I am doing wrong that DFHCOMMAREA is not passed in.
It is especially curious because DFHEIBLK is passed in just fine.
It is also very curious that is sometimes works.

My questions are: 
1. Is there anything in GnuCOBOL runtime system that is checking the address range of the parameters and changing the pointer to NULL?
2. what else could I be going wrong?




[Index of Archives]     [Gcc Help]     [Linux USB Devel]     [Linux Audio Users]     [Yosemite Info]     [Linux Kernel]     [Linux SCSI]     [Big List of Linux Books]

  Powered by Linux