This appendix contains the JCL used to prepare COBOL source code that contains DML statements for execution. Link-edit considerations are also discussed. Samples of z/OS, z/VSE, and z/VM JCL are included.
This section contains the following topics:
Passing Parameters to the Precompiler
To compile a COBOL program under the DML precompiler:
Input to IDMSDMLC consists of source code written in COBOL/DML, protocol/control information, and data dictionary record descriptions. Output from IDMSDMLC is as follows:
Input to the COBOL compiler consists of the source program produced by IDMSDMLC. Output is as follows:
Input to the linkage editor consists of the object program produced by the COBOL compiler. Output is as follows:
The following figure illustrates the steps involved in compiling a COBOL program.
Sample JCL for z/OS operating systems is shown below, followed by a description of statements that need tailoring for site-specific conditions.
//***************************************************************** //** PRECOMPILE COBOL PROGRAM ** //***************************************************************** //precomp EXEC PGM=IDMSDMLC,REGION=4096K, // PARM='precompiler-options' //STEPLIB DD DSN=idms.dba.loadlib,DISP=SHR // DD DSN=idms.custom.loadlib,DISP=SHR // DD DSN=idms.cagjload,DISP=SHR //sysctl DD DSN=idms.sysctl,DISP=SHR //dcmsg DD DSN=idms.sysmsg.ddldcmsg,DISP=SHR //SYS001 DD UNIT=sysda,SPACE=(TRK,(10,10)), // DCB=(RECFM=VB,LRECL=133,BLKSIZE=1334,DSORG=PS) //SYS002 DD UNIT=sysda,SPACE=(TRK,(10,10)), // DCB=(RECFM=VB,LRECL=133,BLKSIZE=1334,DSORG=PS) //SYS003 DD UNIT=sysda,SPACE=(TRK,(10,10)), // DCB=(RECFM=VB,LRECL=133,BLKSIZE=1334,DSORG=PS) //SYSPCH DD DSN=&&SOURCE.,DISP=(NEW,PASS), // UNIT=sysda,SPACE=(TRK,(10,5),RLSE), // DCB=(RECFM=FB,LRECL=80,BLKSIZE=3120) //SYSLST DD SYSOUT=A //SYSIDMS DD * DMCL=dmcl-name sysidms-input-parms /* //SYSIPT DD * COBOL DML source statements /* //***************************************************************** //** COMPILE COBOL PROGRAM ** //***************************************************************** //cblcmp EXEC PGM=igycrctl,REGION=4096K, // PARM='compiler-options' //STEPLIB DD DSN=cobol.loadlib,DISP=SHR //SYSUT1 DD UNIT=sysda,SPACE=(TRK,(10,5)) //SYSUT2 DD UNIT=sysda,SPACE=(TRK,(10,5)) //SYSUT3 DD UNIT=sysda,SPACE=(TRK,(10,5)) //SYSUT4 DD UNIT=sysda,SPACE=(TRK,(10,5)) //SYSUT5 DD UNIT=sysda,SPACE=(TRK,(10,5)) //SYSUT6 DD UNIT=sysda,SPACE=(TRK,(10,5)) //SYSUT7 DD UNIT=sysda,SPACE=(TRK,(10,5)) //syslin DD DSN=&&OBJECT.,DISP=(NEW,PASS), // UNIT=sysda,SPACE=(TRK,(10,5),RLSE), // DCB=(RECFM=FB,LRECL=80,BLKSIZE=3120) //SYSPRINT DD SYSOUT=A //SYSIN DD DSN=&&SOURCE.,DISP=(OLD,DELETE)
//***************************************************************** //** LINK PROGRAM MODULE ** //***************************************************************** //link EXEC PGM=HEWL,REGION=1024K,PARM='LET,LIST,MAP,XREF' //SYSUT1 DD UNIT=sysda,SPACE=(TRK,(20,5)) //SYSLIB DD DSN=cobol.linklib,DISP=SHR //vanilla DD DSN=idms.cagjload,DISP=SHR //custom DD DSN=idms.custom.loadlib,DISP=SHR //SYSLMOD DD DSN=idms.custom.loadlib,DISP=SHR //SYSPRINT DD SYSOUT=A //SYSLIN DD DSN=&&OBJECT.,DISP=(OLD,DELETE) // DD * INCLUDE vanilla(IDMS) required, except omit for CICS INCLUDE vanilla(IDMSCANC) required for BATCH and DC-BATCH if using IDMS-STATUS module INCLUDE custom(IDMSOPTI) optional; BATCH and DC-BATCH only INCLUDE custom(idmscint) required for CICS, otherwise omit ENTRY userentry NAME userprog(R) /* //*
Note: If using the IDMSOPTI module, you must assemble and link edit it before using the JCL above.
The link of CICS application programs that use IDMSCINT must incorporate JCL to resolve external reference DFHEI1. The particular JCL depends on the nature and language of your application. See the appropriate IBM CICS application programming documentation for details.
precompiler-options |
Options that control various aspects of the precompile process. See Passing Parameters to the Precompiler for a complete description of the options. |
idms.dba.loadlib |
Data set name of the load library containing the DMCL and database name table |
idms.cagjload |
Data set name of the load library containing the vanilla CA IDMS executable modules |
idms.custom.loadlib |
Data set name of the load library containing the customized CA IDMS executable modules |
sysctl |
DDname of SYSCTL file |
idms.sysctl |
Data set name of SYSCTL file |
dcmsg |
DDname of the system message (DDLDCMSG) area |
idms.sysmsg.ddldcmsg |
Data set name of the system message (DDLDCMSG) area |
sysda |
Symbolic device name for work files |
sysidms-input-parms |
Parameters that specify physical requirements of the environment, runtime directives, or operating system-dependent file information. For a complete description of all SYSIDMS parameters and syntax, see CA IDMS Common Facilities Guide. Also see Passing Parameters to the Precompiler for a discussion of parameters that can be passed using the PARM=SYSIDMS input statement. |
dmcl-name |
Specifies the name of the DMCL that the precompiler should use to access the message dictionary |
igycrctl |
Program name of the COBOL compiler |
compiler-options |
Parameters that specify options that are appropriate to your version of the COBOL compiler. See Chapter 2:, VS COBOL II Support, and Considerations for IBM Language Environment for restrictions and recommendations specific to CA IDMS access. Also see the IBM documentation for your compiler. |
cobol.loadlib |
Load library that contains COBOL compiler |
syslin |
DDname of the object data set output by the COBOL compiler |
cobol.linklib |
Load library that contains COBOL support modules |
user.loadlib |
User application load library |
idmscint |
Load module created by compiling IDMSCINT or IDMSCINL. For more information, see the CA IDMS System Operations Guide. |
userentry |
Name of program entry point |
userprog |
Name of program in load library |
Note: Depending on the central version operating environment, an IDMSOPTI module link edited with IDMSDMLC can be used in place of or in addition to the SYSCTL file.
Local Mode JCL
To execute the compiler in local mode, remove the SYSCTL statement from the precompile step and replace it with the following:
//dictdb DD DSN=idms.appldict.ddldml,DISP=SHR //sysjrnl DD DSN=idms.tapejrnl,DISP=(NEW,CATLG),UNIT=tape
dictdb |
DDname of the application dictionary DDLDML area |
idms.appldict.ddldml |
Data set name of application dictionary |
sysjrnl |
DDname of the tape journal file |
idms.tapejrnl |
Data set name of the tape journal file |
tape |
Symbolic device name of the tape journal file |
IDMSDMLC ('VSE')
/****************************************************************** /** PRECOMPILE PROGRAM ** /****************************************************************** * step1 // EXEC PROC=IDMSLBLS // UPSI b if specified in IDMSOPTI module // DLBL sysctl,'idms.sysctl',0 // EXTENT SYS000,nnnnnn,,,ssss,llll // ASSGN SYS000,DISK,VOL=nnnnnn,SHR // DLBL idmspch,'temp.dmlc',0 // EXTENT SYS020,nnnnnn,,,ssss,llll // ASSGN SYS020,DISK,VOL=nnnnnn,SHR // DLBL SYS001,'wkfile1',0 // EXTENT SYS001,nnnnnn,,,ssss,llll // ASSGN SYS001,DISK,VOL=nnnnnn,SHR // DLBL SYS002,'wkfile2',0 // EXTENT SYS002,nnnnnn,,,ssss,llll // ASSGN SYS002,DISK,VOL=nnnnnn,SHR // DLBL SYS003,'wkfile3',0 // EXTENT SYS003,nnnnnn,,,ssss,llll // ASSGN SYS003,DISK,VOL=nnnnnn,SHR // EXEC IDMSDMLC,PARM='COBOL=2' Input SYSIDMS parameters here, as required /* COBOL/DML source statements /****************************************************************** /** COMPILE PROGRAM ** /****************************************************************** /* * step2 // DLBL IJSYSIN,'temp.dmlc',0 // EXTENT SYSIPT,nnnnnn ASSGN SYSIPT,DISK,VOL=nnnnnn,SHR // OPTION CATAL,NODECK,NOSYM PHASE userprog,* // EXEC IGYCRCTL /****************************************************************** /** LINK PROGRAM MODULE ** /****************************************************************** * step3 CLOSE SYSIPT,SYSRDR ENTRY (dmlc) // EXEC LNKEDT /*
IDMSLBLS |
Name of the procedure provided at installation that contains the file definitions for CA IDMS dictionaries and databases. Note: For complete listing of IDMSLBLS, see IDMSLBLS Procedure. |
b |
appropriate UPSI switch, 1 through 8 characters, if specified in the IDMSOPTI module |
sysctl |
filename of SYSCTL file |
idms.sysctl |
file-ID of SYSCTL file |
idmspch |
filename of data set output from the IDMSDMLC precompiler |
temp.dmlc |
file ID of data set output from the IDMSDMLC precompiler |
SYS020 |
logical unit assignment of the DMLC output |
nnnnnn |
volume serial identifier of appropriate disk volume |
ssss |
starting track (CKD) or block (FBA) of disk extent |
llll |
number of tracks (CKD) or blocks (FBA) of disk extent |
userprog |
name of program in the library |
precompiler-options |
options that control various aspects of the precompile process. See Passing Parameters to the Precompiler for a complete description of the options. |
dmlc |
name of COBOL/DML module |
You can use SYSIDMS parameters to specify information about your runtime environment.
Note: For more information about SYSIDMS parameters, see the CA IDMS Common Facilities Guide.
To execute the IDMSDMLC precompiler in local mode:
// TLBL sysjrnl,'idms.tapejrnl',,nnnnnn,,f // ASSGN SYS009,TAPE,VOL=nnnnnn
idms.tapejrnl |
file ID of tape journal file |
f |
file number of tape journal file |
sys009 |
logical unit assignment for journal file |
INCLUDE statements should be provided in local mode or central version JCL as follows:
INCLUDE IDMS IDMS interface INCLUDE IDMSOPTI IDMSOPTI module INCLUDE IDMSCANC Local mode abort entry point omit IDMSCANC if TP application) INCLUDE IDMSCINT For CICS only, replaces INCLUDE IDMS
INCLUDE IDMSOPTI can be omitted for programs executed in local mode.
Note: COBOL overlay programs must resolve references to IDMS within their root segment; care must be taken to prevent the overlaying of the IDMS interface. Use of IDMS and IDMSLDPT is recommended for these programs.
IDMSLBLS is a procedure provided during an CA IDMS z/VSE installation. It contains file definitions for the CA IDMS components listed below. These components are provided during installation:
Tailor the IDMSLBLS procedure to reflect the filenames and definitions in use at your site and include this procedure in z/VSE JCL job streams.
The sample z/VSE JCL provided in this document includes the IDMSLBLS procedure. Therefore, individual file definitions for CA IDMS dictionaries, sample databases, disk journal files, and SYSIDMS files are not included in the sample JCL.
IDMSLBLS procedure (z/VSE)
* -------- LIBDEFS -------- // LIBDEF *,SEARCH=idmslib.sublib // LIBDEF *,CATALOG=user.sublib /* ------------------------- LABELS ------------------------- // DLBL idmslib,'idms.library',1999/365 // EXTENT ,nnnnnn,,,ssss,1500 // DLBL dccat,'idms.system.dccat',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,31 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dccatl,'idms.system.dccatlod',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,6 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dccatx,'idms.system.dccatx',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,11 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dcdml,'idms.system.ddldml',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,101 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dclod,'idms.system.ddldclod',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,21 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dclog,'idms.system.ddldclog',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,401 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dcrun,'idms.system.ddldcrun',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,68 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dcscr,'idms.system.ddldcscr',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,135 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dcmsg,'idms.sysmsg.ddldcmsg',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,201 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dclscr,'idms.sysloc.ddlocscr',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,6 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dirldb,'idms.sysdirl.ddldml',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,201 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dirllod,'idms.sysdirl.ddldclod',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,2 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL empdemo,'idms.empdemo1',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,11 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL insdemo,'idms.insdemo1',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,6 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL orgdemo,'idms.orgdemo1',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,6 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL empldem,'idms.sqldemo.empldemo',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,11 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL infodem,'idms.sqldemo.infodemo',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,6 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL projdem,'idms.projseg.projdemo',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,6
// ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL indxdem,'idms.sqldemo.indxdemo',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,6 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL sysctl,'idms.sysctl',1999/365,SD // EXTENT SYSnnn,nnnnnn,,,ssss,2 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL secdd,'idms.sysuser.ddlsec',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,26 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dictdb,'idms.appldict.ddldml',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,51 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL dloddb,'idms.appldict.ddldclod',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,51 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL sqldd,'idms.syssql.ddlcat',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,101 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL sqllod,'idms.syssql.ddlcatl',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,51 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL sqlxdd,'idms.syssql.ddlcatx',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,26 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL asfdml,'idms.asfdict.ddldml',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,201 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL asflod,'idms.asfdict.asflod',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,401 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL asfdata,'idms.asfdict.asfdata',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,201 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL ASFDEFN,'idms.asfdict.asfdefn',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,101 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL j1jrnl,'idms.j1jrnl',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,54 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL j2jrnl,'idms.j2jrnl',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,54 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL j3jrnl,'idms.j3jrnl',1999/365,DA // EXTENT SYSnnn,nnnnnn,,,ssss,54 // ASSGN SYSnnn,DISK,VOL=nnnnnn,SHR // DLBL SYSIDMS,'#SYSIPT',0,SD /+ /*
idmslib.sublib |
name of the sublibrary within the library containing CA IDMS modules |
user.sublib |
name of the sublibrary within the library containing user modules |
idmslib |
filename of the file containing CA IDMS modules |
idms.library |
file-ID associated with the file containing CA IDMS modules |
SYSnnn |
logical unit of the volume for which the extent is effective |
nnnnnn |
volume serial identifier of appropriate disk volume |
ssss |
starting track (CKD) or block (FBA) of disk extent |
dccat |
filename of the system dictionary catalog (DDLCAT) area |
idms.system.dccat |
file-ID of the system dictionary catalog (DDLCAT) area |
dccatl |
filename of the system dictionary catalog load (DDLCATLOD) area |
idms.system.dccatlod |
file-ID of the system dictionary catalog load (DDLCATLOD) area |
dccatx |
filename of the system dictionary catalog index (DDLCATX) area |
idms.system.dccatx |
file-ID of the system dictionary catalog index (DDLCATX) area |
dcdml |
filename of the system dictionary definition (DDLDML) area |
idms.system.ddldml |
file-ID of the system dictionary definition (DDLDML) area |
dclod |
filename of the system dictionary definition load (DDLDCLOD) area |
idms.system.ddldclod |
file-ID of the system dictionary definition load (DDLDCLOD) area |
dclog |
filename of the system log area (DDLDCLOG) area |
idms.system.ddldclog |
file-ID of the system log (DDLDCLOG) area |
dcrun |
filename of the system queue (DDLDCRUN) area |
idms.system.ddldcrun |
file-ID of the system queue (DDLDCRUN) area |
dcscr |
filename of the system scratch (DDLDCSCR) area |
idms.system.ddldcscr |
file-ID of the system scratch (DDLDCSCR) area |
dcmsg |
filename of the system message (DDLDCMSG) area |
idms.sysmsg.ddldcmsg |
file-ID of the system message (DDLDCMSG) area |
dclscr |
filename of the local mode system scratch (DDLOCSCR) area |
idms.sysloc.ddlocscr |
file-ID of the local mode system scratch (DDLOCSCR) area |
dirldb |
filename of the IDMSDIRL definition (DDLDML) area |
idms.sysdirl.ddldml |
file-ID of the IDMSDIRL definition (DDLDML) area |
dirllod |
filename of the IDMSDIRL definition load (DDLDCLOD) area |
idms.sysdirl.dirllod |
file-ID of the IDMSDIRL definition load (DDLDCLOD) area |
empdemo |
filename of the EMPDEMO area |
idms.empdemo1 |
file-ID of the EMPDEMO area |
insdemo |
filename of the INSDEMO area |
idms.insdemo1 |
file-ID of the INSDEMO area |
orgdemo |
filename of the ORGDEMO area |
idms.orgdemo1 |
file-ID of the ORDDEMO area |
empldem |
filename of the EMPLDEMO area |
idms.sqldemo.empldemo |
file-ID of the EMPLDEMO area |
infodem |
filename of the INFODEMO area |
idms.sqldemo.infodemo |
file-ID of the INFODEMO area |
projdem |
filename of the PROJDEMO area |
idms.projseg.projdemo |
file-ID of the PROJDEMO area |
indxdem |
filename of the INDXDEMO area |
idms.sqldemo.indxdemo |
file-ID of the INDXDEMO area |
sysctl |
filename of the SYSCTL file |
idms.sysctl |
file-ID of the SYSCTL file |
secdd |
filename of the system user catalog (DDLSEC) area |
idms.sysuser.ddlsec |
file-ID of the system user catalog (DDLSEC) area |
dictdb |
filename of the application dictionary definition area |
idms.appldict.ddldml |
file-ID of the application dictionary definition (DDLDML) area |
dloddb |
filename of the application dictionary definition load area |
idms.appldict.ddldclod |
file-ID of the application dictionary definition load (DDLDCLOD) area |
sqldd |
filename of the SQL catalog (DDLCAT) area |
idms.syssql.ddlcat |
file-ID of the SQL catalog (DDLCAT) area |
sqllod |
filename of the SQL catalog load (DDLCATL) area |
idms.syssql.ddlcatl |
file-ID of SQL catalog load (DDLCATL) area |
sqlxdd |
filename of the SQL catalog index (DDLCATX) area |
idms.syssql.ddlcatx |
file-ID of the SQL catalog index (DDLCATX) area |
asfdml |
filename of the asf dictionary definition (DDLDML) area |
idms.asfdict.ddldml |
file-ID of the asf dictionary definition (DDLDML) area |
asflod |
filename of the asf dictionary definition load (ASFLOD) area |
idms.asfdict.asflod |
file-ID of the asf dictionary definition load (ASFLOD) area |
asfdata |
filename of the asf data (ASFDATA) area |
idms.asfdict.asfdata |
file-ID of the asf data area (ASFDATA) area |
ASFDEFN |
filename of the asf data definition (ASFDEFN) area |
idms.asfdict.asfdefn |
file-ID of the asf data definition area (ASFDEFN) area |
j1jrnl |
filename of the first disk journal file |
idms.j1jrnl |
file-ID of the first disk journal file |
j2jrnl |
filename of the second disk journal file |
idms.j2jrnl |
file-ID of the second disk journal file |
j3jrnl |
filename of the third disk journal file |
idms.j3jrnl |
file-ID of the third disk journal file |
SYSIDMS |
filename of the SYSIDMS parameter file |
IDMSDMLC
/ADD-FILE-LINK L-NAME=CDMSLIB,F-NAME=idms.dba.loadlib /ADD-FILE-LINK L-NAME=CDMSLIB1,F-NAME=idms.loadlib /ADD-FILE-LINK L-NAME=CDMSLODR,F-NAME=idms.loadlib /ADD-FILE-LINK L-NAME=sysctl,F-NAME=idms.sysctl,SHARED-UPD=*YES /ADD-FILE-LINK L-NAME=SYSIDMS,F-NAME=*DUMMY /ASSIGN-SYSOPT TO=temp.punch /ASSIGN-SYSDTA TO=*SYSCMD /START-PROG *MOD(ELEM=IDMSDMLC,LIB=idms.dba.loadlib,RUN-MODE=*ADV) DICTNAME=dictionary-name DMCL=dmcl-name sysidms-input-parms PARM='precompiler-options' END-SYSIDMS
COBOL/DML source statements
/ASSIGN-SYSOPT TO=*PRIMARY /ASSIGN-SYSDTA TO=temp.punch /START-COBOL85-COMPILER - / MODULE-OUTPUT=LIB-ELEM(LIB=idms.objlib.user,ELEM=userprog, - / COMPILER-ACTION=MODULE-GENERATION(MODULE-FORMAT=OM), - / LISTING=(SOURCE=YES,DIAGNOSTICS=YES,OUTPUT=SYSLIST) /START-BINDER //START-LLM-CREATION INTERNAL-NAME=userprog //INC-MOD LIB=idms.objlib.user,ELEM=userprog //INC-MOD LIB=idms.loadlib,ELEM=IDMSPBS2 For DC, BATCH and DCBATCH //INC-MOD LIB=idms.loadlib,ELEM=IDMSTCM UTM only //RESOLVE-BY-AUTOLINK LIB=cobol.objlib //SAVE-LLM LIB=idms.loadlib.user,ELEM=userprog(VER=@),OVER=YES //END /DELETE-FILE temp.punch
idms.loadlib |
filename of the load library containing the CA IDMS executable modules |
idms.dba.loadlib |
filename of the load library containing the DMCL and database name table load modules |
sysctl |
linkname of SYSCTL file |
idms.sysctl |
filename of SYSCTL file |
temp.punch |
filename of temporary file that contains DML compiler output |
sysidms-input-parms |
parameters that specify physical requirements of the environment, runtime directives, or operating system-dependent file information. For a complete description of all SYSIDMS parameters and syntax, see CA IDMS Common Facilities Guide. |
precompiler-options |
options that control various aspects of the precompile process. See Passing Parameters to the Precompiler for a complete description of the options. |
idms.objlib.user |
filename of user object library |
userprog |
name of user application program |
cobol.objlib |
filename of the COBOL runtime object library |
idms.loadlib.user |
filename of the user load library |
Note: Depending on the CV operating environment, an IDMSOPTI module link edited with the DML compiler can be used in place of or in addition to the SYSCTL file.
Local Mode
To execute the compiler in local mode:
/ADD-FILE-LINK L-NAME=dictdb,F-NAME=idms.appldict.ddldml,SHARED-UPD=*YES [/CREATE-FILE F-NAME=idms.tapejrnl,SUPPRESS-ERRORS=*FILE-EXIST, - / SUP=*TAPE(VOLUME=nnnnnn,DEVICE=tape)] /ADD-FILE-LINK L-NAME=sysjrnl,F-NAME=idms.tapejrnl [,BUF-LEN=bbbb, - / SUP=*TAPE(F-SEQ=1)] Statements and parameters between brackets must be specified only when using the journal file on tape.
dictdb |
linkname of the data dictionary file |
idms.appldict.ddldml |
filename of the data dictionary file |
sysjrnl |
linkname of the tape journal file |
idms.tapejrnl |
filename of the tape journal file |
bbbb |
page size of the file |
nnnnnn |
volume serial number of the tape archive file |
tape |
device name for the tape journal file |
IDMSDMLC ('CMS')
FILEDEF SYSIPT DISK sysipt data a (RECFM F LRECL ppp BLKSIZE nnn FILEDEF SYSPCH DISK prgnme cobol a FILEDEF SYSIDMS DISK sysidms parms a (RECFM F LRECL ppp. BLKSIZE nnn EXEC IDMSFD OSRUN IDMSDMLC PARM='CVMACH=vmid,precompiler-options' FILEDEF TEXT DISK prgnme TEXT A GLOBAL TXTLIB coblibvs IDMSLIB1 COBOL prgnme (OSDECK APOST LIB COBOL compile step TXTLIB DEL utextlib prgnme TXTLIB ADD utextlib prgnme FILEDEF SYSLMOD uloadlib LOADLIB a (RECFM V LRECL 1024 BLKSIZE 10 24 FILEDEF objlibl DISK IDMSLIB1 TXTLIB A FILEDEF objlib DISK utextlib TXTLIB a FILEDEF SYSLIB DISK coblibvs TXTLIB p FILEDEF SYS001 DISK wfn wft wfm LKED linkctl (LIST XREF LET MAP RENT NOTERM PRINT SIZE 512K 64K Link edit step
sysipt data a |
Filename, type, and mode of the file containing the COBOL/DML source statements |
ppp |
Record length of the data file |
nnn |
Block size of the data file |
prgnme cobol a |
Filename of the COBOL program |
sysidms parms a |
Filename, filetype, and filemode of the file that contains SYSIDMS parameters (parameters that define your runtime environment) |
vmid |
ID of the virtual machine running the central version |
precompiler-options |
options that control various aspects of the precompile process. See Passing Parameters to the Precompiler for a complete description of the options. |
coblibvs |
Filename of the library that contains COBOL logic modules |
utextlib |
Filename of the user text library |
uloadlib LOADLIB a |
Filename, filetype, and filemode of the user load library |
objlib1 |
DDname of the first CA IDMS object library |
objlib |
DDname of the user object library |
coblibvs TXTLIB p |
Filename, filetype, and filemode of the library that contains COBOL logic modules |
wfn wft wfm |
Filename, type, and mode of the files to be used as intermediate work files by IDMSDMLC |
linkctl |
Filename of the file that contains the linkage editor control statements |
How to Edit the SYSIDMS File
To create the SYSIDMS file, enter these CMS commands:
XEDIT sysidms parms a (NOPROF INPUT . . . SYSIDMS parameters . . . FILE
To run IDMSDMLC, you must include the NODENAME and DICTNAME SYSIDMS parameters.
Note: For more information about SYSIDMS parameters, see the CA IDMS Common Facilities Guide.
How to Create the SYSIPT File
To create the SYSIPT file, enter these CMS commands:
XEDIT sysipt data a (NOPROF INPUT . . . DML source statements . . . FILE
How to Create the LINKCTL File
To create the LINKCTL file, enter these CMS commands:
XEDIT linkctl data a (NOPROF INPUT . . . INCLUDE objlib(prgnme) INCLUDE objlib1(IDMS) IDMS is required, omit for CICS INCLUDE objlib1(IDMSCINT) for CICS only INCLUDE objlib1(IDMSCANC) IDMSCANC for BATCH and DC_BATCH ENTRY prgnme NAME prgnme(R) . . . FILE
Executing in Local Mode
To execute IDMSDMLC in local mode, remove the CVMACH parameter from OSRUN, and do one of the following:
OSRUN IDMSDMLC PARM='*LOCAL*'
Note: This option is valid only if the OSRUN command is issued from a System Product Interpreter or from an EXEC2 file.
The modules involved in the link edit of an application program contain three external references. Some must be resolved, others can be left unresolved depending on the mode of operation. The table below lists and explains the external references.
Reference |
Referenced by |
Resolved by |
Comments |
---|---|---|---|
ABORT |
Application program |
IDMSCANC |
Should be resolved ONLY in a batch environment; should NOT be included in a tp environment. |
IDMS |
Application program |
IDMS |
Must be resolved |
IDMSOPTI* |
IDMS |
IDMSOPTI module |
Must be resolved if using the central version without a SYSCTL file |
* IDMSOPTI is a weak external reference (WXTRN).
A number of parameters can be provided to control the action taken by the precompiler. The parameters can be specified in one of three ways:
Precompiler Options
Parameter options available to code in the EXEC statement of the precompile step are:
Specifies the name of the RCM created for the program by the precompiler if the program uses SQL access.
Specifies the version number of the RCM created for the program by the precompiler.
Specifies the name of the access module to be executed for the program at runtime if the program uses SQL access.
Specifies the default schema-name qualifier for the precompiler to use when processing an INCLUDE TABLE statement that does not supply a qualifier.
Specifies that the precompiler should only check syntax.
Specifies the name of the dictionary the precompiler should access.
Specifies the SQL syntax standard that the precompiler should apply when checking the validity of SQL statements in the program.
Option NO, the default, means that compliance with a named SQL standard is not checked or enforced, and all CA IDMS extensions are permitted.
Option 89 directs the precompiler to use ANSI X3.135-1989 (Rev), Database Language SQL with integrity enhancement as the standard for compliance.
Option FIPS directs the precompiler to use FIPS PUB 127-1, Database Language SQL as the standard for compliance.
Option DISABLED directs the precompiler not to process any SQL commands (denoted by EXEC SQL, END-EXEC delimiters) in the program.
LIST directs the precompiler to create a listing of the program with precompiler messages. NOList directs the compiler not to create a listing of the program with precompiler messages.
Specifies the format of the DATE data type to be used for communication between the program and the database when the access module is executed.
Specifies the format of the TIME data type to be used for communication between the program and the database when the access module is executed.
Specifies the version of COBOL with which COBOL statements generated by the precompiler must comply.
Option 1 directs the precompiler to generate statements that comply with any of the following:
Versions of VS COBOL that precede VS COBOL II for z/OS, or z/VSE operating systems all CBOL compiler versions for BS2000 operating systems
Option 2, the default, directs the precompiler to generate statements that comply with VS COBOL II or LE-compliant COBOL compilers.
Option 85 directs the precompiler to comply with COBOL85, the version of COBOL required for the Fujitsu and Hitachi compilers.
If YES is specified then SR1 and SR7 will be emitted in SUBSCHEMA-RECNAMES. NO is the default.
Note: For more information about SQL-related parameter options, see the SQL Programming Guide.
Site-specific Parameters
The following sample IDMSPPRM source will change the default for the COBOL parameter from COBOL=2 to COBOL=1 and will direct the precompiler not to produce a listing of the source program.
EDBPPARM CSECT DC C'COBOL=1,NOLIST' DC X'00' END
Copyright © 2014 CA.
All rights reserved.
|
|