Preprocessing, Compiling, and Linking |
Under OS/390 batch, you use the following
cataloged procedures to compile and link your program under CICS:
-
LCCCP
-
to preprocess
-
LCCCPC
-
to preprocess and compile
-
LCCCPCL
-
to preprocess, compile, and link.
The LCCCP cataloged procedure may be used to execute the translator.
The JCL contained in this procedure is similar to that shown in the following:
// EXEC LCCCP,PARM.CCP='options'
//SYSPUNCH DD DISP=SHR,DSN=your.translated.source(member)
//SYSIN DD DISP=SHR,DSN=your.source.library(member)
When you use LCCCP, you need to provide DD cards for
only SYSIN (your C source program containing EXEC CICS commands) and SYSPUNCH
(where the translated C source file is placed). The LCCCP procedure contains
the JCL shown in Expanded JCL for LCCCP.
Expanded JCL for LCCCP
//LCCCP PROC
//*
//CCP EXEC PGM=LCCCP0,REGION=1536K
//STEPLIB DD DSN=SASC.LINKLIB,DISP=SHR
// DD DSN=SASC.LOAD,DISP=SHR
//SYSTERM DD SYSOUT=A
//SYSPRINT DD SYSOUT=A,DCB=(RECFM=FBA,LRECL=121,BLKSIZE=1210)
//SYSPUNCH DD UNIT=SYSDA,DSN=&&CCPOUT,DISP=(,PASS),SPACE=(TRK,(5,5)),
// DCB=(RECFM=VB,LRECL=259)
You can use the LCCCPC procedure to preprocess and then
compile your C program. (Under TSO and CMS, preprocessing, compiling, and
linking are typically done separately.) Complete details about compiler options
and running the compiler in different environments are given in the
SAS/C Compiler and Library User's Guide.
Note:
CICS requires that all programs be compiled so that
they are re-entrant. You must specify the compiler options
rent
or
rentext
to cause the compiler to generate re-entrant code because the
compiler default for re-entrancy is
norent
. Static variables
cannot be modified if you compile with the rentext
option. ![[cautionend]](../common/images/cautend.gif)
The procedure LCCCPC for OS/390 batch runs the translator
in one step, followed by an invocation of the compiler. The JCL for preprocessing
and then compiling C programs using LCCCPC is as follows:
// EXEC LCCCPC, PARM.C='RENT'
//CCP.SYSIN DD DISP=SHR,DSN=your.source.library(member)
//C.SYSLIN DD DISP=SHR,DSN=your.object.library(member)
When you use LCCCPC, you need to provide DD statements
for only SYSIN (your C source program containing EXEC CICS commands) and SYSLIN
(your object data set). The LCCCPC procedure contains the JCL shown in Expanded JCL for LCCCPC.
Expanded JCL for LCCCPC
//LCCCPC PROC
//*
//CCP EXEC PGM=LCCCP0,REGION=1536K
//STEPLIB DD DSN=SAS.LINKLIB,
// DISP=SHR RUNTIME LIBRARY
// DD DSN=SASC.LOAD,
// DISP=SHR TRANSLATOR LIBRARY
//SYSTERM DD SYSOUT=*
//SYSPRINT DD SYSOUT=A,DCB=(RECFM=FBA,LRECL=121,BLKSIZE=1210)
//SYSPUNCH DD UNIT=SYSDA,DSN=&&CPPOUT,DISP=(NEW,PASS),
// SPACE=(TRK,(5,5)),DCB=(RECFM=VB,LRECL=259)
//C EXEC PGM=LC370B,PARM='RENT',COND=(8,LT,CCP)
//STEPLIB DD DSN=SASC.LINKLIB,
// DISP=SHR RUNTIME LIBRARY
// DD DSN=SASC.LOAD,
// DISP=SHR COMPILER LIBRARY
//SYSTERM DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSUT1 DD UNIT=SYSDA,SPACE=(TRK,(10,10))
//SYSUT2 DD UNIT=SYSDA,SPACE=(TRK,(10,10))
//SYSUT3 DD UNIT=SYSDA,SPACE=(TRK,(10,10))
//SYSLIN DD DSN=&&OBJECT,SPACE=(3200,(10,10)),DISP=(MOD,PASS),
// UNIT=SYSDA
//SYSLIB DD DSN=SASC.MACLIBC,
// DISP=SHR STANDARD MACRO LIBRARY
//SYSDBLIB DD DSN=&&DBGLIB,SPACE=(4080,(20,20,1)),DISP=(,PASS),
// UNIT=SYSDA,DCB=(RECFM=U,BLKSIZE=4080)
//SYSTMP01 DD UNIT=SYSDA,SPACE=(TRK,25) VS1 ONLY
//SYSTMP02 DD UNIT=SYSDA,SPACE=(TRK,25) VS1 ONLY
//SYSIN DD DSN=*.CCP.SYSPUNCH,DISP=(OLD,DELETE,DELETE),
// VOL=REF=*.CCP.SYSPUNCH
Two
cataloged procedures are provided for preprocessing, compiling, and linking,
or simply linking a C program for CICS: LCCCPCL and LCCCL. The LCCCPCL procedure
invokes the linkage editor; the LCCCL procedure invokes COOL before invoking
the linkage editor.
You must explicitly specify the entry point of the program
in a linkage-editor ENTRY control statement. When using either LCCCPCL or
LCCCL, you can specify (via the ENTRY parameter) an ENTRY control statement
to be added to the input automatically. Valid values of the ENTRY parameter
are as follows:
-
ENTRY=MAIN
-
links a program whose entry is a C main
program. MAIN is the default value.
-
ENTRY=CSPE
-
links CICS SPE applications. It specifies
the standard CICS start-up routine as the entry point.
-
ENTRY=DYN
-
links subordinate load modules (which are
dynamically loaded by some other module at run-time via the
loadm
function).
-
ENTRY=NONE
-
is used in any situation where a special
entry point is needed. This value inhibits the inclusion of an ENTRY control
statement. You must add an ENTRY control statement to the input that specifies
the correct entry point.
The ENV symbolic parameter may be
used to specify the
environment in which the program is to run. Valid values of the ENV parameter
are as follows:
-
ENV=CICS
-
specifies the default CICS environment.
-
ENV='CICS.SPE'
-
specifies that this application will run
in the CICS Systems Programming Environment.
-
ENV=VSE
-
specifies that this application should be
linked with code to enable it to run in a CICS/VSE environment. This parameter
is used only with the LCCCCL procedure. For further information, see Linking for VSE.
The ALLRES symbolic parameter may be used to
force the program
load module to contain a private copy of all the required transient library
routines. This is a special-use feature not normally specified by applications
developers. This parameter is used only with the LCCCCL procedure. For more
information, see Chapter 10, "All-Resident C Programs," in the
SAS/C Compiler and Library User's Guide. Valid
values of the ALLRES parameter are as follows:
-
ALLRES=NO
-
specifies that normally transient library
routines will not be included in the load module. This is the default.
-
ALLRES=YES
-
forces the transient library routines to
be included in the load module.
The procedure LCCCPCL invokes the translator and the compiler,
followed by the linkage editor. The following is the JCL for preprocessing,
compiling, and then linking C programs using LCCCPCL:
// EXEC LCCCPCL,PARM.CCP='options', PARM.C='RENT'
//CCP.SYSIN DD DISP=SHR,DSNAME=your.source.library(member)
//LKED.SYSLMOD DD DISP=SHR,DSNAME=your.cics.loadlib(member)
When you use LCCCPCL, you need to provide DD statements
for only SYSIN (your C source program) and SYSLMOD (your CICS application
load module library). See Using Cataloged Procedures to Compile and Link C Programs for a complete description of the ENV= and ENTRY= JCL parameters. The LCCCPCL
procedure contains the JCL shown in Expanded JCL for LCCCPCL.
Expanded JCL for LCCCPCL
//LCCCPCL PROC ENTRY=MAIN,ENV=CICS,
// CALLLIB='SASC.BASELIB',
// SYSLIB='SASC.BASELIB',
// CICSLIB='CICS17.LOADLIB'
//*
//**************************************************************
//* ENV=CICS: MODULE RUNS IN A CICS C ENVIRONMENT *
//* ENV='CICS.SPE': MODULE RUNS IN A CICS C SPE ENVIRONMENT *
//* ENTRY=MAIN: MODULE IS A NORMAL C MAIN PROGRAM *
//* ENTRY=DYN: MODULE IS DYNAMICALLY LOADABLE AND REENTRANT *
//* ENTRY=NONE: ENTRY POINT TO BE ASSIGNED BY USER *
//* ENTRY=CSPE: MODULE IS A CICS SPE APPLICATION *
//**************************************************************
//*
//CCP EXEC PGM=LCCCP0,REGION=1536K
//STEPLIB DD DSN=SASC.LINKLIB,
// DISP=SHR C RUNTIME LIBRARY
// DD DSN=SASC.LOAD,
// DISP=SHR C COMPILER LIBRARY
//SYSTERM DD SYSOUT=*
//SYSPRINT DD SYSOUT=*,
// DCB=(RECFM=FBA,LRECL=121,BLKSIZE=1210)
//SYSPUNCH DD UNIT=SYSDA,DSN=&&CPPOUT,DISP=(NEW,PASS),
// SPACE=(TRK,(5,5)),DCB=(RECFM=VB,LRECL=259)
//C EXEC PGM=LC370B,PARM='RENT',COND=(8,LT,CCP)
//STEPLIB DD DSN=SASC.LINKLIB,
// DISP=SHR C RUNTIME LIBRARY
// DD DSN=SASC.LOAD,
// DISP=SHR C COMPILER LIBRARY
//SYSTERM DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSUT1 DD UNIT=SYSDA,SPACE=(TRK,(10,10))
//SYSUT2 DD UNIT=SYSDA,SPACE=(TRK,(10,10))
//SYSUT3 DD UNIT=SYSDA,SPACE=(TRK,(10,10))
//SYSLIN DD DSN=&&OBJECT,SPACE=(3200,(10,10)),DISP=(MOD,PASS),
// UNIT=SYSDA
//SYSLIB DD DSN=SASC.MACLIBC,
// DISP=SHR STANDARD MACRO LIBRARY
//SYSDBLIB DD DSN=&&DBGLIB,SPACE=(4080,(20,20,1)),DISP=(,PASS),
// UNIT=SYSDA,DCB=(RECFM=U,BLKSIZE=4080)
//SYSTMP01 DD UNIT=SYSDA,SPACE=(TRK,25) VS1 ONLY
//SYSTMP02 DD UNIT=SYSDA,SPACE=(TRK,25) VS1 ONLY
//SYSIN DD DSN=*.CCP.SYSPUNCH,DISP=(OLD,DELETE,DELETE),
// VOL=REF=*.CCP.SYSPUNCH
//*
//LKED EXEC PGM=LINKEDIT,PARM='LIST,MAP,RENT',
// COND=((8,LT,C),(8,LT,CCP))
//SYSPRINT DD SYSOUT=*,DCB=(RECFM=FBA,LRECL=121,BLKSIZE=1210)
//SYSTERM DD SYSOUT=*
//SYSLIN DD DSN=*.C.SYSLIN,DISP=(OLD,PASS),VOL=REF=*.C.SYSLIN
// DD DSN=SASC.CICSOBJ(EP@&ENTRY),
// DISP=SHR
// DD DDNAME=SYSIN
//SYSLIB DD DSN=SASC.&ENV.LIB,
// DISP=SHR CICSLIB
// DD DSN=&SYSLIB,DISP=SHR COMMON RESIDENT LIBRARY
// DD DSN=&CALLLIB,DISP=SHR
//SYSUT1 DD DSN=&&SYSUT1,UNIT=SYSDA,DCB=BLKSIZE=1024,
// SPACE=(1024,(200,50))
//SYSLMOD DD DSN=&&LOADMOD(MAIN),DISP=(,PASS),UNIT=SYSDA,
// SPACE=(1024,(50,20,1))
//DFHLIB DD DSN=&CICSLIB,DISP=SHR CICS APPLICATION STUBS
LCCCL invokes COOL and the linkage editor.
Typical JCL for running this cataloged procedure is shown in the example that
follows. This example shows two separate process/compilation steps, followed
by the step to link the application together.
//STEP1 EXEC LCCCPC
//CCP.SYSIN DD DISP=SHR,DSN=your.source.library(mainpgm)
//C.SYSLIN DD DSIP=SHR,DSN=your.object.library(mainpgm)
.
.
.
//STEP2 EXEC LCCCPC
//CCP.SYSIN DD DISP=SHR,DSN=your.source.library(subpgm)
//C.SYSLIN DD DSIP=SHR,DSN=your.object.library(subpgm)
.
.
.
//LINKSTEP EXEC LCCCL
//SYSLMOD DD DSIP=SHR,DSN=your.cics.loadlib(applname)
//SYSIN DD DISP=SHR,DSN=your.object.library(mainpgm)
// DD DISP=SHR,DSN=your.object.library(subpgm)
The JCL steps (STEP1 and STEP2) shown must specify only
two DD statements: SYSIN (the C source program) and SYSLIN (the resulting
object code library). These steps can be run independently from any of the
others.
The LINKSTEP JCL step specifies the DD statements for
SYSLMOD (the CICS application load module library) and SYSIN (the collective
object code to be processed). This step lets the ENV= and ENTRY= parameters
take their default values (of CICS and MAIN, respectively).
The LCCCL procedure specifies the DD statement for SYSLKCTL.
This DD statement is used to pass input to the linkage editor from the COOL
batch monitor, CLK370B. The statement also contains linkage-editor control
statements needed by applications running under CICS. The LCCCL procedure
contains the JCL shown in Expanded JCL for LCCCL.
Expanded JCL for LCCCL
//LCCCL PROC ENV=CICS,ALLRES=NO,ENTRY=MAIN,
// CALLLIB='SASC.BASEOBJ',
// SYSLIB='SASC.BASEOBJ'
//*
//* ************************************************************
//* ENV=CICS: MODULE RUNS IN A CICS C ENVIRONMENT *
//* ENV=VSE: MODULE RUNS IN A CICS/VSE ENVIRONMENT *
//* ENV='CICS.SPE': MODULE RUNS IN A CICS C SPE ENVIRONMENT *
//* ENTRY=MAIN: MODULE IS A NORMAL C MAIN PROGRAM *
//* ENTRY=DYN: MODULE IS DYNAMICALLY LOADABLE *
//* ENTRY=CSPE: MODULE IS A CICS SPE APPLICATION *
//* ENTRY=NONE: ENTRY POINT TO BE ASSIGNED BY USER *
//* ************************************************************
//LKED EXEC PGM=CLK370B,PARM='LIST,MAP,RENT',REGION=1536K
//STEPLIB DD DSN=SASC.LOAD,
// DISP=SHR C COMPILER LIBRARY
// DD DSN=SASC.LINKLIB,
// DISP=SHR C RUNTIME LIBRARY
//SYSPRINT DD SYSOUT=*,DCB=(RECFM=FBA,LRECL=121,BLKSIZE=1210)
//SYSTERM DD SYSOUT=*
//SYSLIN DD UNIT=SYSDA,DSN=&&LKEDIN,SPACE=(3200,(20,20)),
// DCB=(RECFM=FB,LRECL=80,BLKSIZE=3200)
//SYSLKCTL DD DSN=SASC.CICSOBJ(EP@&ENTRY),
// DISP=SHR
// DD DSN=*.SYSLIN,VOL=REF=*.SYSLIN,
// DISP=(SHR,PASS)
//SYSLIB DD DDNAME=AR#&ALLRES ARESOBJ OR ENVIRONMENT OBJ FILE
// DD DSN=SASC.&ENV.OBJ,
// DISP=SHR ENVIRONMENT SPECIFIC OBJECT FILE
// DD DSN=&SYSLIB,DISP=SHR COMMON RESIDENT LIBRARY
// DD DSN=&CALLLIB,DISP=SHR
//SYSUT1 DD DSN=&&SYSUT1,UNIT=SYSDA,DCB=BLKSIZE=1024,
// SPACE=(1024,(200,50))
//SYSLMOD DD DSN=&&LOADMOD(MAIN),DISP=(,PASS),UNIT=SYSDA,
// SPACE=(1024,(50,20,1))
//AR#NO DD DSN=SASC.&ENV.OBJ,
// DISP=SHR
//AR#YES DD DSN=SASC.CICS.ARESOBJ,
// DISP=SHR
//DFHLIB DD DSN=CICS17.LOADLIB,
// DISP=SHR
Copyright © 2001
by SAS Institute Inc., Cary, NC, USA. All rights reserved.