|
------Activation Group------ Control
Program Name Number Boundary
QCMD QSYS *DFTACTGRP 0000000000000001 Yes
QUICMENU QSYS *DFTACTGRP 0000000000000001 No
QUIMNDRV QSYS *DFTACTGRP 0000000000000001 No
QUIMGFLW QSYS *DFTACTGRP 0000000000000001 No
QUICMD QSYS *DFTACTGRP 0000000000000001 No
QUOCPP QPDA *DFTACTGRP 0000000000000001 No
QUOMAIN QPDA *DFTACTGRP 0000000000000001 No
QUOCMD QSYS *DFTACTGRP 0000000000000001 No
CBLTEST JVAUGHN CBL 0000000000000034 Yes
CBLTEST JVAUGHN CBL 0000000000000034 No
CBL00000S JVAUGHN CBL 0000000000000034 No
From the command line, you show calling a program named CBLTEST. The first entry should be the primary-entry-point of a COBOL program, then comes the main procedure of that program. Then I would expect to see the COBOL module/procedure name somewhere in the stack after the call to the CBL0000S service program. This would indicate that you're not really in the module yet. But there's more missing---
CRTSQLCBLI OBJ(JVAUGHN/CBL00000M)That will create a program called COBOL *program* named CBL00000M (unless you're specifying OBJTYPE(*MODULE) somewhere).
CRTSRVPGM SRVPGM(JVAUGHN/CBL00000S)
MODULE(JVAUGHN/CBL00000M JVAUGHN/CBL00001M)
EXPORT(*SRCFILE)
SRCFILE(JVAUGHN/COBOL)
SRCMBR(CBL00000B)
ACTGRP(*CALLER)
-----Original Message-----
message: 4
date: Tue, 11 Apr 2023 12:37:19 -0400
from: Jay Vaughn <jeffersonvaughn@xxxxxxxxx>
subject: Re: [COBOL400-L] sqlcblle - pointer error on select into?
complete module source... (just ran this and got the error)...
*//////////////////////////////////////////////////////////////
* COBOL EXPORTABLE PROGRAM 1
*//////////////////////////////////////////////////////////////
PROCESS OPTIONS.
PROCESS NOMONOPRC.
IDENTIFICATION DIVISION.
PROGRAM-ID. CBL00000M.
**********************************************************
****
**********************************************************
****
ENVIRONMENT DIVISION.
**********************************************************
****
CONFIGURATION SECTION.
SPECIAL-NAMES.
**********************************************************
****
DATA DIVISION.
**********************************************************
****
WORKING-STORAGE SECTION.
77 WS-MESSAGE PIC X(50).
LINKAGE SECTION.
01 INCOMING-VALUE1 PIC X(5).
01 OUTGOING-VALUE1 PIC X(50).
exec sql
set option
commit = *NONE,
closqlcsr = *ENDMOD,
datfmt = *ISO
end-exec.
exec sql
include sqlca
end-exec.
**********************************************************
****
PROCEDURE DIVISION USING INCOMING-VALUE1
OUTGOING-VALUE1.
**********************************************************
****
exec sql
select "SQL row count from CBL00000M SQL: " concat
char(count(*))
into :WS-MESSAGE
from lib.file
end-exec.
move ws-message to outgoing-value1.
* MOVE "SUCCESSFUL CALL TO CBL00000S/CBL00000m COBOL Proc"
* TO OUTGOING-VALUE1.
END PROGRAM CBL00000M.
*//////////////////////////////////////////////////////////////
* COBOL EXPORTABLE PROGRAM 2
*//////////////////////////////////////////////////////////////
PROCESS NOMONOPRC.
IDENTIFICATION DIVISION.
PROGRAM-ID. CBL00001M.
**********************************************************
****
**********************************************************
****
ENVIRONMENT DIVISION.
**********************************************************
****
CONFIGURATION SECTION.
SPECIAL-NAMES.
**********************************************************
****
DATA DIVISION.
**********************************************************
****
WORKING-STORAGE SECTION.
01 WS-WINDOWMESSAGE PIC X(10000).
01 WS-RETURNACTION PIC X(6).
LINKAGE SECTION.
01 INCOMING-VALUE1 PIC X(5).
01 OUTGOING-VALUE1 PIC X(50).
**********************************************************
****
PROCEDURE DIVISION USING INCOMING-VALUE1, OUTGOING-VALUE1.
**********************************************************
****
MOVE "SUCCESSFUL CALL TO CBL00000S/CBL00001m COBOL Proc"
TO OUTGOING-VALUE1.
END PROGRAM CBL00001M.
Module creation...
CRTSQLCBLI OBJ(JVAUGHN/CBL00000M) over my source.
srvpgm creation...
CRTSRVPGM SRVPGM(JVAUGHN/CBL00000S)
MODULE(JVAUGHN/CBL00000M JVAUGHN/CBL00001M)
EXPORT(*SRCFILE)
SRCFILE(JVAUGHN/COBOL)
SRCMBR(CBL00000B)
ACTGRP(*CALLER)
My sqlrpgle *PGM...
ctl-opt debug option(*nodebugio)
dftactgrp(*no) actgrp('CBL')
bnddir('CBL');
dcl-s g_pgm1Rtn char(50) inz;
dcl-pr cbl00000m extproc('CBL00000M');
i_parm1 char(5) const;
o_parm1 char(50);
end-pr;
cbl00000m('test1'
:g_pgm1Rtn);
The call stack at run time and when I get the pointer error...
------Activation Group------ Control
Program Name Number Boundary
QCMD QSYS *DFTACTGRP 0000000000000001 Yes
QUICMENU QSYS *DFTACTGRP 0000000000000001 No
QUIMNDRV QSYS *DFTACTGRP 0000000000000001 No
QUIMGFLW QSYS *DFTACTGRP 0000000000000001 No
QUICMD QSYS *DFTACTGRP 0000000000000001 No
QUOCPP QPDA *DFTACTGRP 0000000000000001 No
QUOMAIN QPDA *DFTACTGRP 0000000000000001 No
QUOCMD QSYS *DFTACTGRP 0000000000000001 No
CBLTEST JVAUGHN CBL 0000000000000034 Yes
CBLTEST JVAUGHN CBL 0000000000000034 No
CBL00000S JVAUGHN CBL 0000000000000034 No
As an Amazon Associate we earn from qualifying purchases.
This mailing list archive is Copyright 1997-2024 by midrange.com and David Gibbs as a compilation work. Use of the archive is restricted to research of a business or technical nature. Any other uses are prohibited. Full details are available on our policy page. If you have questions about this, please contact [javascript protected email address].
Operating expenses for this site are earned using the Amazon Associate program and Google Adsense.