This chapter lists the structures you can use to customize APS.
Use in conditional or looping statement blocks to control the number of columns that APS moves the blocks during processing. The number of columns that % BEGIN is indented from a conditional or looping construct is the same number of columns that APS moves the subordinate block to the left. For example, if % BEGIN is indented four columns from an IF statement, all lines subordinate to % BEGIN move four columns to the left during processing. Any text at the same or lesser indentation than % BEGIN stops the effect of % BEGIN, and default processing resumes. Default processing moves the block to the starting column of the controlling conditional or looping construct.
% BEGIN
Do not use the Customization Facility function &columnnumber+source with % BEGIN.
Override default processing to shift the IF statement's subordinate statement block to start at column 12. Default processing shifts the block instead to the starting column of the IF statement--column 8--as shown below:
Input:
Column: 8...12..16
% IF &TYPE = 'NEW'
01 INV-ITEM.
05 PART-CLASS.
10 PART-NUMBER PIC X(5).
Default output:
Column: 8...12..16
01 INV-ITEM.
05 PART-CLASS.
10 PART-NUMBER PIC X(5).
Use % BEGIN to force the statement block to start at column 12:
Input:
Column: 8...12..16
% IF &TYPE = 'NEW'
% BEGIN
01 INV-ITEM.
05 PART-CLASS.
10 PART-NUMBER PIC X(5).
Output:
Column: 8...12..16
01 INV-ITEM.
05 PART-CLASS.
10 PART-NUMBER PIC X(5).
|
See... |
For more
information about... |
|---|---|
|
Specifying the column number to place source code in the output |
|
|
Placement of looping structure output |
Document Customization Facility source code with Comments.
%* comment text
% DEFINE $SAMPLE-MACRO( ARG1, ARG2) %* comment text %* more comment text
|
See... |
For more
information about... |
|---|---|
|
APS Reference |
Documenting APS source with Comments |
Continue Customization Facility statements on additional lines.
|
Statement |
Continuation
Method |
|---|---|
|
Macro definition |
Break the line after any comma in the argument list; skip to the next line and code a percent symbol, space, ellipsis, and at least one space (% ... ). |
|
Macro call |
Break the line after any comma in the argument list; skip to the next line and code an ellipsis and at least one space (... ). |
|
Literal string in a variable assignment statement |
Break the line anywhere in the string by coding a hyphen; skip to the next line and code a percent symbol, space, ellipsis, and at least one space (% ... ). |
|
All other statements |
Break the line after a blank space by coding a hyphen; skip to the next line and code a percent symbol, space, ellipsis, and at least one space (% ... ). |
Continue a macro definition.
% DEFINE $SAMPLE-MACRO( &ARG1, &ARG2, &ARG3, % ... &ARG4)
Continue a macro call.
$TABLE-MAKER( 3, 4, 'ENTRY', 'ITEM', ... 'X(4) VALUE SPACES')
Continue a literal string variable value by coding a hyphen anywhere in the string.
% &VARIABLE = 'THIS WORKS- % ... FINE' % &VARIABLE = 'THIS WORKS FI- % ... NE TOO'
Continue other statements where a space occurs.
% REPEAT VARYING &IM-TARG FROM - % ... 1 TO 20 % IF &APS-IDENT < 8 - % ... OR &APS-INDENT > 11
|
See... |
For more
information about... |
|---|---|
|
APS Reference: |
Continuing APS statements |
Define a % DECLARE table made of variable assignments that can be referenced either directly (after assigning values to its subscripts), or by searching with the % LOOKUP structure. Help access a loaded table made of variable assignments.
% DECLARE &fieldname(&subscript1)[...(&subscriptN)]
[ % &declarepart1 [Xn|Nn|REDEFINES]
.
.
.
% &declarepartN [Xn|Nn|REDEFINES]]
[% END]
|
&declarepart |
Subscript-part of &fieldname. Indentation indicates subordination. Note the following:
|
|
&fieldname |
Name-assignment statement with zero or more subscripts and up to 78 &declareparts in each structure level. |
|
&subscript |
Set members of single- or multi-dimensional arrays. Values are numbers or strings (maximum 12 characters). For numeric values, the counter starts at 1 and increments until the end of the numeric value. The maximum number of &subscripts per program is 300. |
% DECLARE &(&FILE)-KEY-(&KEY)-A
% &FILE-KEY-NAME X30
% &FILE-KEY-TYPE X
% &FILE-KEY-LEN N4
% DECLARE &(&FILE)-KEY-1-A
% &FILE-KEY-1-NAME X30
% &FILE-KEY-1-TYPE X
% &FILE-KEY-1-LEN N4
.
.
.
% DECLARE &(&SCX-SCR)-XFLD-(&SCX-FLD)
% &SCP-FLD-NAME X16
% &SCP-REP-CNT N3
% &SCP-REP-COL N3
% &SCP-FLD-SHORT X8
% &SCP-FLD-FI
% &SCP-FLD-LEN N3
% &SCP-FLD-ROW N3
% &SCP-FLD-COL N3
% &SCP-FLD-ATTRS
% &SCP-FLD-PROT X
% &SCP-FLD-INTENS-FLG X
% &SCP-FLD-MDT-FLG X
% &SCP-FLD-NUM-FLG X
% &SCP-FLD-EXT-ATTRS
% &SCP-FLD-RVID-FLG X
% &SCP-FLD-BLINK-FLG X
% &SCP-FLD-UNDER-FLG X
% &SCP-FLD-COLOR X2
% &SCP-FLD-DET-FLG X
% &SCP-FLD-EDIT-FLG N
% &SCP-FLD-IM-MOD X
% &DMOL-XFLD-1 = "PART-NBR 0 08 8 6 19UNTFFFF F1F" % &DMOL-XFLD-2 = "SHORT-DESC 0 0 13 8 19PNTFFFF F0F" % &DMOL-XFLD-3 = "LOCATION 5 3 12 12 5PNTFFFF F0F" . . .
% DECLARE &VS-(&VSX-FILE)-KEY-(&VSX-KEY)-B
% &VSP-FILE-KEY-VOL X8
% &VSP-FILE-KEY-SPACE X20
% &VSP-FILE-KEY-CICZ X20
.
.
.
% &VSX-FILE = "FILE3"
% &VSX-KEY = 2
.
.
.
% &VOL = &VSP-FILE-KEY-VOL
% DECLARE &IMS-PCB-(&PCBX)-SEG-(&SEGX)
% &IMS-PCB-SEG-NAME X30
% &IMS-PCB-SEG-IMSNAME X8
% &IMS-PCB-SEG-PROCOPTS
% &IMS-PCB-SEG-PROCOPT-GET N
% &IMS-PCB-SEG-PROCOPT-ISRT N
% &IMS-PCB-SEG-PROCOPT-REPL N
% &IMS-PCB-SEG-PROCOPT-DLET N
% &IMS-PCB-SEG-LEN N6
.
.
.
% LOOKUP &IMS-PCB-SEG-NAME = &THE-SEG-NAME-YOU-WANT FROM 1 1
.
.
.
% ELSE
.
.
.
% DECLARE &OPERATOR-(&OPR)
% &OPERATOR X2
% &OPERATOR-SYMBOL X
% &OPERATOR-1 = "EQ="
% &OPERATOR-2 = "LT<"
% &OPERATOR-3 = "GT>"
% &OPERATOR-4 = "MI-"
% &OPERATOR-5 = "PL+"
% &OPERATOR-6 = "TIX"
% &OPERATOR-7 = "DI/"
% DECLARE &VS-OPT-(&VSX-OPT)
% &VS-FILE-OPT
% REPEAT VARYING &VSX-OPT FROM 1
% WHILE &DEFINED(&SCR-OPTS-<&VSX-OPT>)
% &VS-FILE-OPT = &DEFVAL
|
See... |
For more
information about... |
|---|---|
|
Referencing a % DECLARE table |
Specify the name and formal arguments when defining a macro in a USERMACS file or APS program.
% DEFINE $macroname [(&formalarg1[, &formalarg2, % ... &formalarg3, ..., &formalarg1000])] statementblock [% END]
Define a macro with three formal arguments whose values are supplied by a call that invokes the macro.
% DEFINE $ITEM-MAKER( &MM, &DATANAME, &TAIL) . . . % END
Macro call:
$ITEM-MAKER( 12, 'TEST-ITEM', 'S9(9) COMP SYNC VALUE -1')
|
See... |
For more
information about... |
|---|---|
|
Calling macros |
All targets
APS writes error messages to a temporary file, passes them to the APS Precompiler, and displays them in the final APS message report of the compile.
Send your own messages to the report, classified with a severity level, by coding one of the following SET statements:
% SET FATAL messagetext % SET ERROR messagetext % SET WARNING messagetext % SET INFO messagetext
% SET FATAL ends all translation. Enclose variables in the message text within evaluation brackets.
% SET TRACE ERROR is an error trace mechanism that appears by default in the APS CNTL file APSDBDC. The trace identifies:
The severity codes of errors traced are: F(atal), E(rror), W(arning), and I(nformation). To exclude Information messages, append the keyword NOINFO to the % SET TRACE ERROR statement. To trace a selected section of your macro or program, code % SET TRACE ERROR and the beginning of the section, and % SET NOTRACE at the end.
% SET WRITE-CONTROL prints all Customization Facility input source in the output source, enabling you to view both the input and output source together, in context. It prints all error messages immediately below the source lines in error; they appear as COBOL Comments. This feature is especially helpful when examining complicated evaluation bracket processing.
|
See... |
For more
information about... |
|---|---|
|
Coding other % SET statements |
|
|
Processing with evaluation brackets |
Stop processing the remaining lines of a macro and resume processing with the line immediately following the macro call.
% ESCAPE
|
See... |
For more
information about... |
|---|---|
|
APS Reference: |
Terminating APS programs |
|
APS Reference: |
Calling or linking to other programs or subprograms |
Specify the order in which the Customization Facility evaluates variable values.
Format 1:
... <% source> [...]
Format 2:
... <source> [...]
|
source |
Can include:
|
|
Evaluation bracket: |
<source> |
|
Greater-than operator: |
source > source |
|
Less-than operator: |
source < source |
|
Greater-than or equal to operator: |
source >= source |
|
Less-than or equal to operator: |
source <= source |
Before Customization Facility processing:
% &VAR = 6
% &XVAR = 7
.
.
.
... <% &VAR + 3 + &XVAR>
.
.
.
... <&VAR + 3 + &XVAR>
After Customization Facility processing:
The Customization Facility processor replaces the variables in the first set of brackets with their values, but does not calculate the result because the source is a Customization Facility statement, as indicated by the % symbol inside the brackets. At the next processing step--APS generation--the APS generator calculates the result.
The Customization Facility processor replaces the variables in the second set of brackets with their values and calculates the result, because the source is not a Customization Facility statement.
.
.
.
... <6 + 3 + 7>
.
.
.
... <16>
Before Customization Facility processing:
% &ITEM-COUNT = 75 % &PKG-COUNT = <&ITEM-COUNT + 50> / 50
After Customization Facility processing:
The Customization Facility adds 75 to 50 and divides the result by 50; assigns the result--2--as the value of &PKG-COUNT.
|
See... |
For more
information about... |
|---|---|
|
Defining evaluation bracket characters |
|
|
Using evaluation brackets to code in-line macros |
Perform predefined processes in a Customization Facility macro or APS program.
&APS-EPILOGUE
&APS-FULL
&APS-HALF
&APS-INDENT
&APS-PROGRAM-ID
&APS-PSB-NAME
&columnnumber+source
&COMPILETIME
&DEFINED( $macroname|&variablename)
&DEFVAL
&INDEX( 'wholestring', 'characterstring')
&LENGTH( string)
&NUMERIC( &variablename)
"literalstring"
&PARSE( &string[, &variable ])
number
&SUBSTR( string, startcolumn[, length])
&dataname+-suffix
|
&APS-EPILOGUE |
Returns the last macro call in the EPILOGUE queue. For information about calling macros with % SET EPILOGUE, see % SET Statements. |
|
&APS-FULL |
Returns a full-word binary PIC, a string containing a 4-byte (full-word) binary picture specification: PIC S9(9) COMP. |
|
&APS-HALF |
Returns a half-word binary PIC, a string containing a 2-byte (half-word) binary picture specification: PIC S9(4) COMP. |
|
&APS-INDENT |
Returns the indentation level for the current macro. Contains the column position of the $ of the invoking macro; otherwise, contains the column position of the left margin (usually column 7 for COBOL). |
|
&APS-PROGRAM-ID |
Returns the PROGRAM-ID name from the Identification Division. |
|
&APS-PSB-NAME |
Returns the user-specified PSB or subschema name for your program. |
|
&columnnumber+source |
Specifies the column number at which to place source code in the output. |
|
&COMPILETIME |
Returns
the date and time of the compile: |
|
&DEFINED |
Determines whether a specific macro or variable has a defined value. Returns a true value (1) if defined, and a false value (0) if not defined. |
|
&DEFVAL |
Returns the string or number value of the last &DEFINED variable, the string or number in &variablename. |
|
&INDEX |
Searches a string left to right for the first occurrence of a character-string. Returns a number identifying its character position; return 0 if no character string. Delimiting quotes are not included in the character position. (See also &SUBSTR below.) |
|
&LENGTH |
Returns a number specifying the length of the argument string. Leading and trailing blanks are included as part of a string; delimiting quotation marks are not. |
|
&NUMERIC |
Determines whether a variable is numeric. Returns a true value (1) if numeric and a false value (0) if non-numeric. |
|
&PARSE |
Parses a Customization Facility text string. &String must be a variable with a string value. The second argument can be either a literal text string, a variable with a string value, or a number (the number turns into a string). The second argument is matched against the first argument (the string value of &string). The part of the &string value following the match is stored back into &string with the leading and trailing spaces eliminated. Then, the part of the &string value preceding the match returns as the value of the parsing function, again with no leading and trailing spaces. In matching the second string inside the first string, the match does not begin within a string that is embedded (quoted) within the first string. |
|
&SUBSTR |
Extracts a substring from a string, starting with startcolumn and continuing for substringlength. String can be an alphanumeric literal string delimited with quotation marks, or a variable with a string value. Startcolumn and substringlength can be a number or variable; if substringlength is omitted, the substring includes all characters from startcolumn onward. Note the following:
|
|
&dataname+suffix |
Appends a literal suffix to a variable data name by coding a plus symbol (+) in the space between them. During processing, the plus symbol disappears (it is not replaced with a space), and the suffix appends onto the resolved variable value. |
% DEFINE $TP-ENTRY
% IF &APS-INDENT < 8 OR &APS-INDENT > 11
% SET ERROR $TP-ENTRY MUST BE INVOKED
% ... IN AREA A
CLOSE &FILE-1
% IF &DEFINED( &FILE-2)
... &FILE-2
% IF &DEFINED( &FILE-3)
... &FILE-3
% REPEAT VARYING &SC-I FROM 1
% WHILE &DEFINED( &<&SCR>-FLD-<&SC-I>)
% &VAR = &<&SCR>-FLD-<&SC-I>
% END
% REPEAT VARYING &SC-I FROM 1
% WHILE &DEFINED( &<&SCR>-FLD-<&SC-I>)
% &VAR= &DEFVAL
% END
&INDEX( 'THIS IS AN EXAMPLE', 'IS')
% &II = 1
% IF &NUMERIC( &II)
/* YOU WILL GET THIS TEXT
.
.
.
% END
% &SCOPE = 'CALC' PERFORM &SCOPE+-ROUTINE
PERFORM CALC-ROUTINE
Extract a substring from the string value of &PREFIX, starting with column 1 and continuing for 23 characters.
% &PREFIX = &SUBSTR( &PREFIX, 1, 23)
Extract substring values from the values of &RANDOM and &STUFF, and assign the result to MY-LANGUAGE. Note that &QT defines the delimiter character as the apostrophe; the quotation marks delimiting the string values are not considered part of the string and are stripped from the output.
Input source:
% &QT = "'" % &RANDOM = &SUBSTR( "MEANINGLESS", 1, 4) % &STUFF = &SUBSTR( "EXAMPLE", 3, 5) MY-LANGUAGE = &QT&RANDOM&STUFF&QT
Output source:
MY-LANGUAGE = 'MEANAMPLE'
|
See... |
For more
information about... |
|---|---|
|
Associative memory structures |
|
|
Calling EPILOGUE macros |
|
|
Examples: of functions |
% IF condition1 statementblock % ELSE-IF condition2 statementblock % ELSE-IF conditionN statementblock % ELSE statementblock [% END]
|
condition |
Can be a: Number, literal enclosed in apostrophes or quotation marks, or variable; followed by a space and a relational operator; followed by a space and a value. To specify multiple conditions, use the Boolean operators AND or OR with no parentheses. Relational operator can be: =, NOT =, <, >, NOT <, NOT >, <=, >=. Value can be a number, a literal enclosed in apostrophes or quotation marks, or a variable. |
Test a variable for a numeric condition.
% IF &LEN = 80 % IF &APS-INDENT < 8
Test a variable for multiple conditions.
% IF &APS-INDENT < 8 OR &APS-INDENT > 11
Test a variable for a true condition, represented by the value 1.
% &EMPLOYEE-TYPE-A = 0
% &EMPLOYEE-TYPE-B = 1
% IF &EMPLOYEE-TYPE-B
statementblock
% IF condition1
statementblock1
% IF condition2
% IF condition3
statementblock2
% ELSE-IF condition4
% ELSE-IF condition5
statementblock3
% ELSE
statementblock4
% ELSE
statementblock5
% IF condition6
% IF condition7
statementblock6
statementblock7
|
See... |
For more
information about... |
|---|---|
|
Conditional processing |
|
|
Examples: of conditional processing |
Open, read, and process a user-defined macro, copybook, or other file in an APS program.
% INCLUDE ddname[(membername)] [submember]
|
ddname |
Data set containing the file to include. Can be a partitioned data set, sequential file, or instream data set. |
|
membername |
Member of ddname |
|
submember |
Submember of membername |
-KYWD- 12-*----20---*----30---*----40---*----50---*----60 SYM1 % INCLUDE USERMACS(MY-MACRO)
-KYWD- 12-*----20---*----30---*----40---*----50---*----60 SYBT % INCLUDE USERMACS(MY-MACRO)
-KYWD- 12-*----20---*----30---*----40---*----50---*----60 SYWS % INCLUDE COPYLIB(MY-COPYBOOK)
-KYWD- 12-*----20---*----30---*----40---*----50---*----60 SYLK % INCLUDE COPYLIB(MY-COPYBOOK)
|
See... |
For more
information about... |
|---|---|
|
Specifying in an APS program the location where the Customization Facility places source code |
APS enforces the following size and programming limitations.
| Item |
Max |
|---|---|
|
Indents |
50 |
|
Nested macros |
139 |
|
Macro call arguments |
1000 |
|
Nested % INCLUDEs |
10 |
|
% DECLARE statements: |
|
|
Subscripts |
300 |
|
Length of subscript |
12 |
|
Tables |
200 |
|
Parts per table |
1000 |
|
Length of a table part |
78 |
|
System limits: |
|
|
Work files (beginning with WORK4) |
8 |
|
LRECL of INCLUDE library |
80 |
|
LRECL of extended INCLUDE library |
140 |
|
See... |
For more
information about... |
|---|---|
|
APS Reference: |
APS limits |
% LOOKUP &declarepart oper searchval
[FROM value [valueN ...]]
statementblock
[% ELSE-IF condition
statementblock
.
.
.
[% ELSE
statementblock
[% END]
|
&declarepart |
Name of variable assignment in % DECLARE table |
|
condition |
Condition can be a number or variable, followed by a space and a relational operator, followed by a space and a value. To specify multiple conditions, use the Boolean operators AND or OR with no parentheses. Relational operator can be: =, NOT =, <, >, NOT <, NOT >, <=, >=. Value can be a number, a literal enclosed in apostrophes or quotation marks, or a variable. |
|
oper |
Valid operator: =, NOT =, <, >, NOT <, NOT >, <=, >=. |
|
searchval |
Customization Facility term. |
|
value |
Starting value(s) of the low-order &subscript of the &fieldname associated with the &declarepart. |
% DECLARE &IMS-PCB-(&PCBX)-SEG-(&SEGX)
% &IMS-PCB-SEG-NAME X30
% &IMS-PCB-SEG-IMSNAME X8
% &IMS-PCB-SEG-PROCOPTS
% &IMS-PCB-SEG-PROCOPT-GET N
% &IMS-PCB-SEG-PROCOPT-ISRT N
% &IMS-PCB-SEG-PROCOPT-REPL N
% &IMS-PCB-SEG-PROCOPT-DLET N
% &IMS-PCB-SEG-LEN N6
.
.
% LOOKUP &IMS-PCB-SEG-NAME = &THE-SEG-NAME-YOU-WANT FROM 1 1
do this if found
% ELSE
do this if found
% DECLARE &VS-(&VSX-FILE)-KEY-(&VSX-KEY)-B
% &VSP-FILE-KEY-VOL X8
% &VSP-FILE-KEY-SPACE X20
% &VSP-FILE-KEY-CICZ X20
% DECLARE &VS-(&VSX-FILE)-KEY-(&VSX-KEY)-ALIAS-(&VSX-ALIAS)
% &VSP-FILE-KEY-ALIAS X30
.
.
&ALIAS = &PARSE(&ALIAS)
.
.
% LOOKUP &VSP-FILE-KEY-ALIAS = &ALIAS FROM 1 1 1
% &VOL = &VSP-FILE-KEY-VOL
|
See... |
For more
information about... |
|---|---|
|
Defining % DECLARE tables |
$macroname [(actualarg1[, actualarg2, % ... actualarg3, ..., actualarg1000])]
sourcecode <$macroname( actualarg1, ... actualarg1000)> [... sourcecode]
|
actualarg |
Actual argument list that corresponds to the formal argument list in the called macro's % DEFINE statement. Actual arguments pass values to their corresponding formal arguments. Actual arguments are positional; if you omit any argument but the last one, code a comma in its place. Omitted arguments are called empty arguments. Actualarg is a local variable and retains the values passed to it only from the time it is invoked until it ends. Note: A variable defined outside the scope of a macro definition is global in scope. An actual argument can be a:
|
|
$macroname |
Macro to be invoked; the macro must be defined in the USERMACS PDS or data set in your Project and Group |
Pass the actual argument value 1 to the formal argument variable &ARG1 in the macro, and the actual argument value 3 to &ARG3. In the macro, give &ARG2 a default value of 0. Note that the extra comma between the actual arguments 1 and the 3 is a placeholder, indicating that the call does not pass an actual argument to &ARG2; it is an undefined, or empty argument. Rather than leave the empty argument undefined, assign to it the default value 0. Also note that the call does not pass an actual argument to &ARG4. It, however, needs no placeholder because it is the last argument in the list; the macro assumes it is undefined.
% DEFINE $SAMPLE-MACRO( &ARG1, &ARG2, &ARG3,
... &ARG4)
% IF NOT &DEFINED( &ARG2)
% &ARG2 = "0"
% END
.
.
.
% END
$SAMPLE-MACRO( 1,, 3)
Note: Another way to assign a default value to an empty argument is to hard-code a variable assignment statement in the formal argument list as follows:
% DEFINE $SAMPLE-MACRO( &ARG1, &ARG2 = defaultvalue, % ... &ARG3, &ARG4)
Pass a new value to &NEXT-VALUE each time that the in-line macro $CNTR is called.
% &CNTR = 0
% DEFINE $CNTR
% &CNTR = &CNTR + 1
% END
.
.
% &VALUE-<$CNTR> = &NEXT-VALUE
.
.
% &VALUE-<$CNTR> = &NEXT-VALUE
|
See... |
For more
information about... |
|---|---|
|
Writing a macro % DEFINE statement |
Establish a loop and test a condition.
% REPEAT statementblock % UNTIL|WHILE condition [ statementblock] [% END]
% REPEAT VARYING|R-V &variable % ... [FROM &variable|literal|arithmeticexpr] % ... [BY &variable|literal|arithmeticexpr] statementblock % ... UNTIL|WHILE condition [ statementblock] [% END]
% REPEAT VARYING|R-V &variable % ... [FROM &variable|literal|arithmeticexpr] % ... [BY &variable|literal|arithmeticexpr] % ... THRU|TO &variable|literal|arithmeticexpr [% ... OR THRU|TO &variable|literal|arithmeticexpr] [% ... OR THRU|TO &variable|literal|arithmeticexpr] [% ... OR THRU|TO &variable|literal|arithmeticexpr] statementblock [% END]
|
condition |
Condition can be a number or variable, followed by a space and a relational operator, followed by a space and a value. To specify multiple conditions, use the Boolean operators AND or OR with no parentheses. Relational operator can be: =, NOT =, <, >, NOT <, NOT >, <=, >=. Value can be a number, a literal enclosed in apostrophes or quotation marks, or a variable. |
|
statementblock |
Can contain any Customization Facility, COBOL or COBOL/2, or S-COBOL statements. |
|
variable |
Customization Facility variable with valid COBOL name. |
|
See... |
For more
information about... |
|---|---|
|
Testing % REPEAT loops |
|
|
Specifying the order in which the Customization Facility evaluates variable values |
|
|
Examples: of looping |
% SET COMMUNICATION [SECTION] % SET DATA [DIVISION] % SET END-WORKING-STORAGE % SET FILE-CONTROL % SET FILE [SECTION] % SET LINKAGE [SECTION] % SET PROCEDURE % SET SPECIAL-NAMES % SET WORKING-STORAGE
% SET AUXILIARY-OUTPUT % SET NORMAL-OUTPUT % SET BLANK % SET NOBLANK % SET CONVERT-LOWER-CASE % SET PRESERVE-LOWER-CASE % SET DELIMITERS-OPTIONAL % SET DELIMITERS-REQUIRED % SET EPILOGUE [$macroname] % SET EVAL-BRACKETS 'leftright' % SET EVAL-BRACKETS-AUX 'leftright' % SET LEFT-MARGIN column % SET RIGHT-MARGIN column % SET ERROR message text % SET FATAL message text % SET INFO message text % SET WARNING message text % SET LOOP-LIMIT SET TRACE ERROR [NOINFO] SET NOTRACE % SET WRITE-CONTROL[-LIMIT number] % SET NOWRITE-CONTROL
Store three macro calls in the EPILOGUE queue, but invoke just $MACRO-1.
% SET EPILOGUE $MACRO-1
% SET EPILOGUE $MACRO-2
% SET EPILOGUE $MACRO-3
%* Current value of &APS-EPILOGUE is $MACRO-3.
.
.
.
% SET EPILOGUE
%* $MACRO-3 (the current value of &APS-EPILOGUE) is
%* elminated from the EPILOGUE queue;
%* the new current value of &APS-EPILOGUE is $MACRO-2.
.
.
.
% SET EPILOGUE
%* $MACRO-2 (the current value of &APS-EPILOGUE) is
%* eliminated from the EPILOGUE queue;
%* the new current value of &APS-EPILOGUE is $MACRO-1.
%* $MACRO-1 (the current value of &APS-EPILOGUE) is
%* invoked.
|
See... |
For more
information about... |
|---|---|
|
Specifying in an APS program the location where the Customization Facility places source code |
|
|
Specifying the order in which the Customization Facility evaluates variable values |
|
|
Examples: of program location statements |
Specify in an APS program the location where the Customization Facility places source code.
-KYWD- 12-*----20---*----30---*----40---*----50---*----60 SYBT macrocode SYEN macrocode SYDD macrocode SYFD macrocode SYIO macrocode SYLT macrocode SYLK macrocode SYM1 macrocode SYM2 macrocode SYRP macrocode SYWS macrocode
|
SYM1 |
At the beginning of the program, before macro libraries that you include at the beginning of the program |
|
SYM2 |
After macro libraries that you include at the beginning of the program |
|
SYEN |
In the Environment Division, after the Special-Names paragraph |
|
SYIO |
In the Input-Output Section, after macro libraries that you include at the beginning of the Input-Output Section |
|
SYDD |
At the beginning of the Data Division |
|
SYFD |
In the File Section, after macro libraries that you include at the beginning of the File Section |
|
SYWS |
In the Working-Storage Section, after macro libraries and data structures that you include in Working-Storage |
|
SYLT |
In the Linkage Section, after macro libraries and data structures that you include at the beginning of Linkage |
|
SYLK |
In the Linkage Section, after source code that you include with the SYLT keyword |
|
SYRP |
In the Report Section, after any macro libraries that you include at the beginning of the Report Section |
|
SYBT |
At the end of the program |
-KYWD- 12-*----20---*----30---*----40---*----50---*----60 SYM1 % INCLUDE USERMACS(MY-MACRO)
-KYWD- 12-*----20---*----30---*----40---*----50---*----60 SYBT % INCLUDE USERMACS(MY-MACRO)
-KYWD- 12-*----20---*----30---*----40---*----50---*----60 SYM1 &TP-USER-LEN = 49
-KYWD- 12-*----20---*----30---*----40---*----50---*----60 SYWS % INCLUDE COPYLIB(MY-COPYBOOK)
-KYWD- 12-*----20---*----30---*----40---*----50---*----60 SYLK % INCLUDE COPYLIB(MY-COPYBOOK)
|
See... |
For more
information about... |
|---|---|
|
Specifying the program location where the Customization Facility places source code |
|
|
Including macros or copybooks in a macro |
|
|
APS Reference: |
Other APS keywords |
Establish a loop and test a condition to execute a subordinate statement block either until or while a single or compound condition is satisfied.
% UNTIL|WHILE condition statementblock [% END]
|
condition |
Valid values:
AND or OR may connect multiple logical terms. Do not use parentheses. |
|
See... |
For more
information about... |
|---|---|
|
Using % UNTIL or % WHILE with a % REPEAT loop |
|
|
Examples: of looping |
Assign a value to a Customization Facility variable.
% &variable = stringterm|numericterm
|
numericterm |
Numeric term can be one or a combination of:
|
|
variable |
Valid COBOL name |
|
stringterm |
String term can be:
|
% &TEST-CHR = 'SPACE'
% &A = &SUBSTR( &B, 3, 5)
% &REC-LEN = 121
% &B = 100 % &A = &B
% &EMPLOYEE-TYPE-A = 0 % &EMPLOYEE-TYPE-B = 1 % IF &EMPLOYEE-TYPE-B
% &A = &B + &C
% &COL = &LINELENGTH / 2 - &NN / 2
% &SQ = "'" % &B = 'CON' % &C = 'CAT' % &A = <% &SQ&B&C&SQ>
|
See... |
For more
information about... |
|---|---|
|
Using Customization Facility functions |
Copyright © 2002 Micro Focus International Limited. All rights reserved.
This document and the proprietary marks and names
used herein are protected by international law.