tons of progress on macros
[pspp] / doc / flow-control.texi
index f0bf4fe10b77400ed999dd56672f9c1b84f93460..a3f39b6ccb8c40390b0b5126ec453e711fd9ddd4 100644 (file)
@@ -45,91 +45,142 @@ BREAK.
 @vindex DEFINE
 @cindex macro
 
+@subsection Overview
+
 @display
-DEFINE macro_name([argument[/argument]@dots{}])
-@dots{}body@dots{}
-!ENDDEFINE.
+@t{DEFINE} @i{macro_name}@t{(}@r{[}@i{argument}@r{[}@t{/}@i{argument}@r{]@dots{}]}@t{)}
+@dots{}@i{body}@dots{}
+@t{!ENDDEFINE.}
+@end display
 
-Each argument takes the following form:
-  @{!arg_name =,!POSITIONAL@} [!DEFAULT(default)] [!NOEXPAND]
-  @{!TOKENS(count),!CHAREND('token'),!ENCLOSE('start','end'),!CMDEND@}
+Each @i{argument} takes the following form:
+@display
+@r{@{}@i{!arg_name} @t{=},@t{!POSITIONAL}@r{@}}
+@r{[}@t{!DEFAULT(}@i{default}@t{)}@r{]}
+@r{[}@t{!NOEXPAND}@r{]}
+@r{@{}@t{!TOKENS(}@i{count}@t{)},@t{!CHAREND('}@i{token}@t{')},@t{!ENCLOSE('}@i{start}@t{','}@i{end}@t{')},@t{!CMDEND}@}
+@end display
 
-The following directives may be used within the body:
-  !OFFEXPAND
-  !ONEXPAND
+The following directives may be used within @i{body}:
+@example
+!OFFEXPAND
+!ONEXPAND
+@end example
 
 The following functions may be used within the body:
-  !BLANKS(count)
-  !CONCAT(arg@dots{})
-  !EVAL(arg)
-  !HEAD(arg)
-  !INDEX(haystack, needle)
-  !LENGTH(arg)
-  !NULL
-  !QUOTE(arg)
-  !SUBSTR(arg, start[, count])
-  !TAIL(arg)
-  !UNQUOTE(arg)
-  !UPCASE(arg)
+@display
+@t{!BLANKS(}@i{count}@t{)}
+@t{!CONCAT(}@i{arg}@dots{}@t{)}
+@t{!EVAL(}@i{arg}@t{)}
+@t{!HEAD(}@i{arg}@t{)}
+@t{!INDEX(}@i{haystack}@t{,} @i{needle}@t{)}
+@t{!LENGTH(}@i{arg}@t{)}
+@t{!NULL}
+@t{!QUOTE(}@i{arg}@t{)}
+@t{!SUBSTR(}@i{arg}@t{,} @i{start}[@t{,} @i{count}]@t{)}
+@t{!TAIL(}@i{arg}@t{)}
+@t{!UNQUOTE(}@i{arg}@t{)}
+@t{!UPCASE(}@i{arg}@t{)}
 @end display
 
-The DEFINE command defines a macro that can later be called any number
-of times within a syntax file.  Each time it is called, the macro's
-body is @dfn{expanded}, that is, substituted, as if the body had been
-written instead of the macro call.  A macro may accept arguments,
-whose values are specified at the point of invocation and expanded in
-the body where they are referenced.  Macro bodies may also use various
-directives and functions, which are also expanded when the macro is
-called.
+The body may also include the following constructs:
+@display
+@t{!IF (}@i{condition}@t{) !THEN} @i{true-expansion} @t{!ENDIF}
+@t{!IF (}@i{condition}@t{) !THEN} @i{true-expansion} @t{!ELSE} @i{false-expansion} @t{!ENDIF}
 
-Many identifiers associated with macros begin with @samp{!}, a
-character not normally allowed in identifiers.  These identifiers are
-reserved only for use with macros, which helps keep them from being
-confused with other kinds of identifiers.
+@t{!DO} @i{!var} @t{=} @i{start} @t{!TO} @i{end} [@t{!BY} @i{step}]
+  @i{body}
+@t{!DOEND}
+@t{!DO} @i{!var} @t{!IN} @t{(}@i{expression}@t{)}
+  @i{body}
+@t{!DOEND}
 
-@menu
-* Macro Basics::
-* Macro Arguments::
-* Controlling Macro Expansion::
-* Macro Functions::
-* Macro Settings::
-* Macro Notes::
-@end menu
+@t{!LET} @i{!var} @t{=} @i{expression}
+@end display
+
+@subsection Introduction
 
-@node Macro Basics
-@subsection Macro Basics
+The DEFINE command creates a @dfn{macro}, which is a name for a
+fragment of PSPP syntax called the macro's @dfn{body}.  Following the
+DEFINE command, syntax may @dfn{call} the macro by name any number of
+times.  Each call substitutes, or @dfn{expands}, the macro's body in
+place of the call, as if the body had been written in its place.
 
-The simplest macros have no arguments.  The following defines a macro
-named @code{!vars} that expands to the variable names @code{v1 v2 v3},
-along with a few example uses.  The macro's name begins with @samp{!},
-which is optional for macro names.  The @code{()} following the macro
-name are required:
+The following syntax defines a macro named @code{!vars} that expands
+to the variable names @code{v1 v2 v3}.  The macro's name begins with
+@samp{!}, which is optional for macro names.  The @code{()} following
+the macro name are required:
 
 @example
 DEFINE !vars()
 v1 v2 v3
 !ENDDEFINE.
+@end example
+
+Here are two ways that @code{!vars} might be called given the
+preceding definition:
 
+@example
 DESCRIPTIVES !vars.
 FREQUENCIES /VARIABLES=!vars.
 @end example
 
-Macros can also expand to entire commands.  For example, the following
-example performs the same analyses as the last one:
+With macro expansion, the above calls are equivalent to the following:
 
 @example
-DEFINE !commands()
 DESCRIPTIVES v1 v2 v3.
 FREQUENCIES /VARIABLES=v1 v2 v3.
-!ENDDEFINE.
-
-!commands
 @end example
 
-The body of a macro can call another macro.  For example, we could
-combine the two preceding examples, with @code{!commands} calling
-@code{!vars} to obtain the variables to analyze.  The following shows
-one way that could work:
+The @code{!vars} macro expands to a fixed body.  Macros may have more
+sophisticated contents:
+
+@itemize @bullet
+@item
+Macro @dfn{arguments} that are substituted into the body whenever they
+are named.  The values of a macro's arguments are specified each time
+it is called.  @xref{Macro Arguments}.
+
+@item
+Macro @dfn{functions}, expanded when the macro is called.  @xref{Macro
+Functions}.
+
+@item
+@code{!IF} constructs, for conditional expansion.  @xref{Macro
+Conditional Expansion}.
+
+@item
+Two forms of @code{!DO} construct, for looping over a numerical range
+or a collection of tokens.  @xref{Macro Loops}.
+
+@item
+@code{!LET} constructs, for assigning to macro variables.  @xref{Macro
+Variable Assignment}.
+@end itemize
+
+Many identifiers associated with macros begin with @samp{!}, a
+character not normally allowed in identifiers.  These identifiers are
+reserved only for use with macros, which helps keep them from being
+confused with other kinds of identifiers.
+
+The following sections provide more details on macro syntax and
+semantics.
+
+@node Macro Bodies
+@subsection Macro Bodies
+
+As previously shown, a macro body may contain a fragment of a PSPP
+command (such as a variable name).  A macro body may also contain full
+PSPP commands.  In the latter case, the macro body should also contain
+the command terminators.
+
+Most PSPP commands may occur within a macro.  The @code{DEFINE}
+command itself is one exception, because the inner @code{!ENDDEFINE}
+ends the outer macro definition.  For compatibility, @code{BEGIN
+DATA}@dots{}@code{END DATA.} should not be used within a macro.
+
+The body of a macro may call another macro.  The following shows one
+way that could work:
 
 @example
 DEFINE !commands()
@@ -152,10 +203,39 @@ The following section shows how to do that.
 @node Macro Arguments
 @subsection Macro Arguments
 
-Macros may take any number of arguments, which are specified within
-the parentheses in the DEFINE command.  Arguments come in two
-varieties based on how their values are specified when the macro is
-called:
+This section explains how to use macro arguments.  As an initial
+example, the following syntax defines a macro named @code{!analyze}
+that takes all the syntax up to the first command terminator as an
+argument:
+
+@example
+DEFINE !analyze(!POSITIONAL !CMDEND)
+DESCRIPTIVES !1.
+FREQUENCIES /VARIABLES=!1.
+!ENDDEFINE.
+@end example
+
+@noindent When @code{!analyze} is called, it expands to a pair of analysis
+commands with each @code{!1} in the body replaced by the argument.
+That is, these calls:
+
+@example
+!analyze v1 v2 v3.
+!analyze v4 v5.
+@end example
+
+@noindent act like the following:
+
+@example
+DESCRIPTIVES v1 v2 v3.
+FREQUENCIES /VARIABLES=v1 v2 v3.
+DESCRIPTIVES v4 v5.
+FREQUENCIES /VARIABLES=v4 v5.
+@end example
+
+Macros may take any number of arguments, described within the
+parentheses in the DEFINE command.  Arguments come in two varieties
+based on how their values are specified when the macro is called:
 
 @itemize @bullet
 @item
@@ -163,9 +243,13 @@ A @dfn{positional} argument has a required value that follows the
 macro's name.  Use the @code{!POSITIONAL} keyword to declare a
 positional argument.
 
+When a macro is called, every positional argument must be given a
+value in the same order as the defintion.
+
 References to a positional argument in a macro body are numbered:
 @code{!1} is the first positional argument, @code{!2} the second, and
-so on.
+so on.  In addition, @code{!*} expands to all of the positional
+arguments' values, separated by spaces.
 
 The following example uses a positional argument:
 
@@ -181,10 +265,10 @@ FREQUENCIES /VARIABLES=!1.
 
 @item
 A @dfn{keyword} argument has a name.  In the macro call, its value is
-specified with the syntax @code{@var{name}=@var{value}}.  Because of
-the names, keyword argument values may take any order in a macro call.
-If one is omitted, then a default value is used: either the value
-specified in @code{!DEFAULT(@var{value})}, or an empty value
+specified with the syntax @code{@i{name}=@i{value}}.  The names allow
+keyword argument values to take any order in the call, and even to be
+omitted.  When one is omitted, a default value is used: either the
+value specified in @code{!DEFAULT(@i{value})}, or an empty value
 otherwise.
 
 In declaration and calls, a keyword argument's name may not begin with
@@ -201,19 +285,10 @@ FREQUENCIES /VARIABLES=!vars.
 !ENDDEFINE.
 
 !analyze_kw vars=v1 v2 v3.  /* Analyze specified variables.
-!analyze_kw.                /* Analyze all variables.  
+!analyze_kw.                /* Analyze all variables.
 @end example
 @end itemize
 
-@example
-DEFINE !analyze_kw(vars=!CMDEND)
-DESCRIPTIVES !vars.
-FREQUENCIES /VARIABLES=!vars.
-!ENDDEFINE.
-
-!analyze_kw vars=v1 v2 v3.
-@end example
-
 If a macro has both positional and keyword arguments, then the
 positional arguments must come first in the DEFINE command, and their
 values also come first in macro calls.
@@ -221,7 +296,7 @@ values also come first in macro calls.
 Each argument declaration specifies the form of its value:
 
 @table @code
-@item !TOKENS(@var{count})
+@item !TOKENS(@i{count})
 Exactly @var{count} tokens, e.g.@: @code{!TOKENS(1)} for a single
 token.  Each identifier, number, quoted string, operator, or
 punctuator is a token.  @xref{Tokens}, for a complete definition.
@@ -243,6 +318,18 @@ Any number of tokens up to @var{token}, which should be an operator or
 punctuator token such as @samp{/} or @samp{+}.  The @var{token} does
 not become part of the value.
 
+With the following variant of @code{!analyze_kw}, the variables must
+be following by @samp{/}:
+
+@example
+DEFINE !analyze_parens(vars=!CHARNED('/'))
+DESCRIPTIVES !vars.
+FREQUENCIES /VARIABLES=!vars.
+!ENDDEFINE.
+
+!analyze_parens vars=v1 v2 v3/.
+@end example
+
 @item !ENCLOSE('@var{start}','@var{end}')
 Any number of tokens enclosed between @var{start} and @var{end}, which
 should each be operator or punctuator tokens.  For example, use
@@ -267,12 +354,24 @@ FREQUENCIES /VARIABLES=!vars.
 Any number of tokens up to the end of the command.  This should be
 used only for the last positional parameter, since it consumes all of
 the tokens in the command calling the macro.
+
+The following variant of @code{!analyze_kw} takes all the variable
+names up to the end of the command as its argument:
+
+@example
+DEFINE !analyze_kw(vars=!CMDEND)
+DESCRIPTIVES !vars.
+FREQUENCIES /VARIABLES=!vars.
+!ENDDEFINE.
+
+!analyze_kw vars=v1 v2 v3.
+@end example
 @end table
 
 By default, when an argument's value contains a macro call, the call
 is expanded each time the argument appears in the macro's body.  The
 @code{!NOEXPAND} keyword in an argument declaration suppresses this
-expansion.
+expansion.  @xref{Controlling Macro Expansion}.
 
 @node Controlling Macro Expansion
 @subsection Controlling Macro Expansion
@@ -287,20 +386,20 @@ If a macro body contains @code{!OFFEXPAND} or @code{!ONEXPAND}
 directives, then @code{!OFFEXPAND} disables expansion of macro calls
 until the following @code{!ONEXPAND}.
 
-A macro argument's value may contain a macro call.  By default, these
-macro calls are expanded.  If the argument was declared with the
-@code{!NOEXPAND} keyword, they are not expanded.
+A macro argument's value may contain a macro call.  These macro calls
+are expanded, unless the argument was declared with the
+@code{!NOEXPAND} keyword.
 
 The argument to a macro function is a special context that does not
 expand macro calls.  For example, if @code{!vars} is the name of a
 macro, then @code{!LENGTH(!vars)} expands to 5, as does
 @code{!LENGTH(!1)} if positional argument 1 has value @code{!vars}.
-In these cases, use the @code{!EVAL} macro function to expand macros,
+To expand macros in these cases, use the @code{!EVAL} macro function,
 e.g.@: @code{!LENGTH(!EVAL(!vars))} or @code{!LENGTH(!EVAL(!1))}.
 @xref{Macro Functions}, for details.
 
-These rules apply to macro calls.  Uses of macro functions and macro
-arguments within a macro body are always expanded.
+These rules apply to macro calls, not to uses of macro functions and
+macro arguments within a macro body, which are always expanded.
 
 @node Macro Functions
 @subsection Macro Functions
@@ -311,9 +410,15 @@ characters.
 
 The arguments to macro functions have a restricted form.  They may
 only be a single token (such as an identifier or a string), a macro
-argument, or a call to a macro function.  Thus, @code{x}, @code{5.0},
-@code{x}, @code{!1}, @code{"5 + 6"}, and @code{!CONCAT(x,y)} are valid
-macro arguments, but @code{x y} and @code{5 + 6} are not.
+argument, or a call to a macro function.  Thus, the following are
+valid macro arguments:
+@example
+x    5.0    x    !1    "5 + 6"    !CONCAT(x,y)
+@end example
+@noindent and the following are not:
+@example
+x y    5+6
+@end example
 
 Macro functions expand to sequences of characters.  When these
 character strings are processed further as character strings, e.g.@:
@@ -351,7 +456,8 @@ results visible.
 @deffn {Macro Function} !CONCAT (arg@dots{})
 Expands to the concatenation of all of the arguments.  Before
 concatenation, each quoted string argument is unquoted, as if
-@code{!UNQUOTE} were applied.
+@code{!UNQUOTE} were applied.  This allows for ``token pasting'',
+combining two (or more) tokens into a single one:
 
 @c Keep these examples in sync with the test for !CONCAT in
 @c tests/language/control/define.at:
@@ -361,12 +467,36 @@ concatenation, each quoted string argument is unquoted, as if
 !CONCAT(12, 34)              @expansion{} 1234
 !CONCAT(!NULL, 123)          @expansion{} 123
 @end example
+
+@code{!CONCAT} is often used for constructing a series of similar
+variable names from a prefix followed by a number and perhaps a
+suffix.  For example:
+
+@c Keep these examples in sync with the test for !CONCAT in
+@c tests/language/control/define.at:
+@example
+!CONCAT(x, 0)                @expansion{} x0
+!CONCAT(x, 0, y)             @expansion{} x0y
+@end example
+
+An identifier token must begin with a letter (or @samp{#} or
+@samp{@@}), which means that attempting to use a number as the first
+part of an identifier will produce a pair of distinct tokens rather
+than a single one.  For example:
+
+@c Keep these examples in sync with the test for !CONCAT in
+@c tests/language/control/define.at:
+@example
+!CONCAT(0, x)                @expansion{} 0 x
+!CONCAT(0, x, y)             @expansion{} 0 xy
+@end example
 @end deffn
 
 @deffn {Macro Function} !EVAL (arg)
 Expands macro calls in @var{arg}.  This is especially useful if
 @var{arg} is the name of a macro or a macro argument that expands to
-one, because arguments to macro functions are not expanded by default.
+one, because arguments to macro functions are not expanded by default
+(@pxref{Controlling Macro Expansion}).
 
 The following examples assume that @code{!vars} is a macro that
 expands to @code{a b c}:
@@ -514,6 +644,123 @@ to uppercase.
 @end example
 @end deffn
 
+@node Macro Expressions
+@subsection Macro Expressions
+
+Macro expressions are used in conditional expansion and loops, which
+are described in the following sections.  A macro expression may use
+the following operators, listed in descending order of operator
+precedence:
+
+@table @code
+@item ()
+Parentheses override the default operator precedence.
+
+@item !EQ !NE !GT !LT !GE !LE = ~= <> > < >= <=
+Relational operators compare their operands and yield a Boolean
+result, either @samp{0} for false or @samp{1} for true.
+
+These operators always compare their operands as strings.  This can be
+surprising when the strings are numbers because, e.g.,@: @code{1 <
+1.0} and @code{10 < 2} both evaluate to @samp{1} (true).
+
+Comparisons are case sensitive, so that @code{a = A} evaluates to
+@samp{0} (false).
+
+@item !NOT ~
+@itemx !AND &
+@itemx !OR |
+Logical operators interpret their operands as Boolean values, where
+quoted or unquoted @samp{0} is false and anything else is true, and
+yield a Boolean result, either @samp{0} for false or @samp{1} for
+true.
+@end table
+
+Macro expressions do not include any arithmetic operators.
+
+An operand in an expression may be a single token (including a macro
+argument name) or a macro function invocation.  Either way, the
+expression evaluator unquotes the operand, so that @code{1 = '1'} is
+true.
+
+@node Macro Conditional Expansion
+@subsection Macro Conditional Expansion
+
+The @code{!IF} construct may be used inside a macro body to allow for
+conditional expansion.  It takes the following forms:
+
+@example
+!IF (@var{expression}) !THEN @var{true-expansion} !IFEND
+!IF (@var{expression}) !THEN @var{true-expansion} !ELSE @var{false-expansion} !IFEND
+@end example
+
+When @var{expression} evaluates to true, the macro processor expands
+@var{true-expansion}; otherwise, it expands @var{false-expansion}, if
+it is present.  The macro processor considers quoted or unquoted
+@samp{0} to be false, and anything else to be true.
+
+@node Macro Loops
+@subsection Macro Loops
+
+The body of a macro may include two forms of loops: loops over
+numerical ranges and loops over tokens.  Both forms expand a @dfn{loop
+body} multiple times, each time setting a named @dfn{loop variable} to
+a different value.  The loop body typically expands the loop variable
+at least once.
+
+The MITERATE setting (@pxref{SET MITERATE}) limits the number of
+iterations in a loop.  This is a safety measure to ensure that macro
+expansion terminates.  PSPP issues a warning when the MITERATE limit
+is exceeded.
+
+@subsubheading Loops Over Ranges
+
+@example
+!DO @var{!var} = @var{start} !TO @var{end} [!BY @var{step}]
+  @var{body}
+!DOEND
+@end example
+
+A loop over a numerical range has the form shown above.  @var{start},
+@var{end}, and @var{step} (if included) must be expressions with
+numeric values.  The macro processor accepts both integers and real
+numbers.  The macro processor expands @var{body} for each numeric
+value from @var{start} to @var{end}, inclusive.
+
+The default value for @var{step} is 1.  If @var{step} is positive and
+@math{@var{first} > @var{last}}, or if @var{step} is negative and
+@math{@var{first} < @var{last}}, then the macro processor doesn't
+expand the body at all.  @var{step} may not be zero.
+
+@subsubheading Loops Over Tokens
+
+@example
+!DO @var{!var} !IN (@var{expression})
+  @var{body}
+!DOEND
+@end example
+
+A loop over tokens takes the form shown above.  The macro processor
+evaluates @var{expression} and expands @var{body} once per token in
+the result, substituting the token for @var{!var} each time it
+appears.
+
+@node Macro Variable Assignment
+@subsection Macro Variable Assignment
+
+The @code{!LET} construct evaluates an expression and assigns the
+result to a macro variable.  It may create a new macro variable or
+change the value of one created by a previous @code{!LET} or
+@code{!DO}, but it may not change the value of a macro argument.
+@code{!LET} has the following form:
+
+@example
+!LET @var{!var} = @var{expression}
+@end example
+
+If @var{expression} is more than one token, it must be enclosed in
+parentheses.
+
 @node Macro Settings
 @subsection Macro Settings
 
@@ -535,9 +782,12 @@ of each macro in the input.  This feature can be useful for debugging
 macro definitions.
 
 MNEST (@pxref{SET MNEST}) limits the depth of expansion of macro
-calls, that is, the nesting level of macro expansion.
+calls, that is, the nesting level of macro expansion.  The default is
+50.  This is mainly useful to avoid infinite expansion in the case of
+a macro that calls itself.
 
-MITERATE
+MITERATE (@pxref{SET MITERATE}) limits the number of iterations in a
+@code{!DO} construct.  The default is 1000.
 
 PRESERVE...RESTORE
 
@@ -546,12 +796,12 @@ SET MEXPAND, etc. doesn't work inside macro bodies.
 @node Macro Notes
 @subsection Extra Notes
 
-@code{!*} expands to all the positional arguments.
-
 Macros in comments.
 
 Macros in titles.
 
+Define ``unquote.''
+
 @node DO IF
 @section DO IF
 @vindex DO IF