| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
| |
* stdlib/infix.tl (funp): Do not recognize list
forms as functions, such as lambda expressions
or (meth ...) syntax. It causes surprisingly
wrong transformations.
|
|
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (toplevel): New ~ operator,
prefix at level 35, tied to lognot function.
* tests/012/infix.tl: New tests.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The problem is that (parse-infix '(x < y < z)) and
(parse-infix '(x < (< y z)) produce exactly the same
parse and will be treated the same way. But we would
like (< y z) to be left alone. The fix is to annotate
all compound terms such that finish-infix will
not recurse into them.
* stdlib/infix.tl (parse-infix): When an operand is
seen that is a compound expression X it is turned
into @X, in other words (sys:expr X).
(finish-infix): Recognize (sys:expr X) and convert
it into X without recursing into it.
* tests/012/infix.tl: Update a number of test cases.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (infix-expand-hook): Do not process
the interior of square bracket forms; jsut pass
them through. Of course, square brackets continue to
denote postfix array indexing.
* txr.1: Updated and revised.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
It is undesirable to translate (1 fun) into (fun 1).
Only cases similar to these patterns, using list
as an example:
(1 list 2) -> (list 1 2)
(1 list 2 3) -> (list 1 2 3)
(1 list 2 + 3) -> (list 1 (+ 2 3))
(list 2 3) -> (list 2 3)
(list 2 + 3) -> (list (+ 2 3))
* stdlib/infix.tl (infix-expand-hook): Restrict the phony
infix case to three or more elements.
* txr.1: Update phony infix case 1 as requiring three
or more elements. Also add (1 list) example emphasizing
that it's not recognized.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit extends infix with a post-processing step
applied to the output of parse-infix which improves
the code, and also implements math-like semantics for
relational operators, which I'm calling superfix.
Improving the code means that expressions like a + b + c,
which turn into (+ (+ a b) c) are cleaned up into
(+ a b c). This is done for all n-ary operators.
superfix means that clumps of certain operators
behave as a compound. For instance a < b <= c
means (and (< a b) (<= b c)), where b is evaluated
only once.
Some relational operators are n-ary; for those we
generate the n-ary expression, so that
a = b = c < d becomes (and (= a b c) (< c d)).
* stdlib/infix.tl (*ifx-env*): New special variable.
We use this for communicating the macro environment
down into the new finish-infix function, without
having to pass a parameter through all the recursion.
(eq, eql, equal, neq, neql, nequal, /=, <, >, <=, >=,
less, greater, lequal, gequal): These operators
become right associative, and are merged into a single
precedence level.
(finish-infix): New function which coalesces compounds
of n-ary operations and converts the postfix chains
of relational operators into the correct translation
of superfix semantics.
(infix-expand-hook): Call finish-infix on the output
of parse-infix, taking care to bind the *ifx-env*
variable to the environment we are given.
* tests/012/infix.tl: New tests.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
| |
* stdlib.tl (detect-infix): Do not detect a prefix
operator followed by argument, followed by anything whatsoever
as being infix. The pair must be followed by nothing, or
by a non-argument.
* txr.1: Documented.
|
|
|
|
|
|
| |
* stdlib/infix.tl (infix-expand-hook): In the phony
prefix case, require rest to be a cons, rather
than non-nil in order to invoke cdr.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (infix-expand-hook): In addition to the
phony infix rule which swaps a function from second to
first place, and then transforms the arguments, if possible,
we add a case which is essentially like the above, but with
the leading argument before the function being absent:
the expression begins with a function and has two or more
arguments. If those arguments transform as infix, we take
the result as one argument. Otherwise if no transformation
takes place, we return the original expression.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* infix.tl (ifx-oper): New slot, power. When we detect a
prefix operator that is followed by a power symbol and
operand, we clone the operator and store the operand here.
(parse-infix): If the operator has the power slot, the
add-local function, add an extra node for the exponentiation
operation over the function result.
When about to add a prefix operator to the operator stack,
we check whether it is a function, and whether it is
followed by ** and an operand. If so, we clone the operator
and store the operand into the power slot then remoe
those two arguments from the rest of the input; effectively,
we recognize this as a phrase structure.
(detect-infix): We need a couple of rules here to
detect infix expressions which use function power operators.
* txr.1: Document function power operators as well
as the new auto-detection rules.
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (funp): New macro.
(detect-infix): Take environment argument and test with
funp rather than fboundp.
(infix-expand-hook): Pass environment to detect-infix.
Also use funp in the phony infix argument test.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (detect-infix): Redesign.
New algorithm looks only at the first two or three
elements. Arguments that are not operators are
only considered operands if they don't have
function bindings. This is important because sometimes
the logic is applied to the arguments in a DWIM
bracket form, like [apply / args], which we don't
want to treat as (/ apply args).
* tests/012/infix.tl: New test.
* txr.1: Redocumented.
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (infix-expand-hook): In the phony infix
logic that swaps the first two arguments, we also try the
remaining arguments as a stand-alone expression, passing that
through the hook. If the hook recognizes and transforms them
as infix, we keep the result as one argument. Otherwise,
we just take the original arguments. I already committed
some test cases for this which are failing.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (parse-infix): Change how we treat fn (arg ...)
and elem [arg ...] forms. These now translate to (fn (arg ...))
and [elem (arg ...)] rather than (fn arg ...) and [elem arg ...].
(detect-infix): detect certain op [arg ...] forms as infix.
(infix-expand-hook): Revise detection logic to handle bracket
expression forms, and parenthesized single terms.
The latter are needed to reduce [elem (atom)] to [elem atom].
* tests/012/infix.tl: Fix up some tests.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* autoload.c (infix_set_entries): Intern new symbols
||, &&, !, !=, &=, |=, &&=, ||=, >>=, <<=, ~=, %=,
*=, %=, <<, >>, &, |, ~, % and //.
* stdlib/infix.tl: revise precedence of calculating
assignment operators. Add shifts, bitwise operators,
modulo, C-like synonyms for some operators,
numerous new calculating assignments.
(sys:mod-set, sys:and-set, sys:or-set, sys:logand-set,
sys:logxor-set, sys:logior-set, sys:ash-set,
sys:asr-set, sys:asr): New macros to provide
the implementation of operation combinations that
will only be available via infix.
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (parse-infix): We don't need to
recognize consecutive [...][...], because the
rule which reduces any element followed by [...]
does the job.
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (parse-infix): Drop usr: package
prefix; autoload.c interns this symbol in the usr
package.
(detect-infix): New function, whose single
responsibility is determining whether the argument
expression should be treated via parse-infix.
(infix-expand-hook): Simplified by using detect-infix
function.
|
|
|
|
|
| |
* stdlib/infix.tl (infix-error): Remove
trailing whitespace.
|
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (toplevel): New prefix operator =
at 0 precedence. This is useful for specifying an
infix formula that is not being autodetected by ifx
nicely. For instance an expression containing
only array references can be obtained as (= a[i][j]).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We implement a dynamic precedence algorithm whereby
when an infix operator is immediately followed by
a clump of one or more consecutive prefix operators,
the infix operator's precedence is lowered to one
less than the lowest one of the prefix operators.
This creates nice handling for situations like
(sqrt x + y - sqrt z + w) whose visual symmetry
parses into (- (sqrt (+ x y)) (sqrt (+ z w)))
rather than subordinating the second sqrt to the
first one.
* stdlib/infix.tl (parse-infix): Before processing
an infix operator, calculate the prefix of the rest
of the input that consists of nothing but consecutive
prefix operators, and if it is nonempty, then use it
to adjust the effective precedence used for the infix
operator. This algorithm must only ever lower the
precedence, never raise it.
|
|
|
|
|
|
| |
* stdlib/infix.tl (toplevel): The := operator must
be assoc :right so a := b := c becomes (set a (set b c))
and not (set (set a b) c).
|
|
|
|
|
|
|
|
|
| |
* stdlib/infix.tl (parse-infix): The operator expected
diagnostic can occur not just before an an operand,
but before an prefix operator. For instance "a cos b".
An operator is expected between a and cos.
We don't want to say "before operand cos" because
cos is an operator.
|
|
The infix module provides a macro called ifx. Forms
(evaluated expressions) enclosed inside ifx at any nesting
level, which are not special operator or macro forms, are
subject to automatic detection of an infix notation, which is
transformed into regular Lisp. The notation is based on Lisp
atoms; no read syntax is introduced. Infix may be freely mixed
with ordinary Lisp.
* autoload.c (infix_set_entries, infix_instantiate):
New static functions.
(autoload_init): Register new infix module for autoload.
* stdlib/infix.tl: New file.
|