| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (compile-file-conditionally): When evaluation
of a compiled top-level form is not suppressed, there is a risk
that it can terminate non-locally, via throwing an exception or
performing a block return. The compilation of the file is then
aborted. We can do better: using an unwind-protect, we can catch
all non-local control transfers out of the form and just ignore
them. The motivation for this is that it lets us compile files
which call (return-from load ...), without requiring that it be
written as (compile-only (return-from load ...)). Other things will
work, like compiling a (load "foo") where foo doesn't exist or
aborts due to errors.
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (compiler comp-fun-form): Recognize
the pattern (subtypep (typeof x) y) and rewrite it to
(typep x y).
* stdlib/match.tl (compile-struct-match): Don't generate
the (subtype (typeof x) y) pattern, but (typeof x y).
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (dump-to-tlo): To ensure numbers are
externalized in such a way that they will be loaded back
exactly, we need to set a few special variables. For integers,
we want *print-base* to be 10. Numbers printed in other bases
cannot be read back correctly. Octal, hex and binary could be,
but they would need to be printed with the correct prefixes.
For floating-point values, we want to switch to the default
print format, and use flo-max-dig for the precision. That one
s not not the default value; the default is flo-dig.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When functions are optimized away due to constant folding,
instead of replacing them with a nil, we now compact the
table to close the gaps and renumber the references in the
code.
* stdlib/compiler.tl (compiler null-stab): Method removed.
(compiler compact-dregs): Renamed to compact-dregs-and-syms.
Now compacts the symbol table also. This is combined with
D-reg compacting because it makes just two passes through
the instruction: a pass to identify the used D registers
and symbol indices, and then another pass to edit the
instructions with the renamed D registers and renumbered
symbol indices.
(compiler optimize): Remove the call to the null-unused-data
on the basic-blocks object; nulling out D regs and symbol
table entries is no longer required. Fllow the rename of
compact-dregs to compact-dregs-and-syms which is called
the same way otherwise.
* stdlib/optimize.tl (basic-blocks null-unused-data):
No longer used method removed.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We now have some constant folding in the optimizer too, not
just in the front end compiler pass. This is leaving behind
dead D registers that are not referenced in the code.
Let's compact the D register table to close the gap.
* stdlib/compiler.tl (compiler get-dreg): In this function
we no longer check that we have allocated too many D
registers. We let the counter blow past %lev-size%.
Because this creates the fighting chance that the compaction
of D regs will reduce their number to %lev-size% or less.
By doing this, we allow code to be compilable that otherwise
would not be: code that allocates too many D regs which
are then optimized away.
(compiler compact-dregs): New function. Does all the work.
(compiler optimize): Compact the D regs at optimization
level 5 or higher.
(compile-toplevel): Check for an overflowing D reg count
here, after optimization.
* stdlib/optimize.tl (basic-blocks null-unused-data):
Here, we no longer have to do anything with the D registers.
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (compiler get-dreg): Fix
indentation proble.
* stdlib/optimize.tl (basic-block fill-treg-compacting-map):
Likewise.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (%effect-free-funs%, %effect-free%,
%functional-funs%, %functional%): Move variables
into stdlib/constfun.tl
* stdlib/constfun.tl %effect-free-funs%, %effect-free%,
%functional-funs%, %functional%): Moved here.
* stdlib/optimize.tl: Use load-for to express dependency
on constfun module; don't depend on the compiler having
loaded it.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The compiler handles trivial constant folding over the
source code, as a source to source transformation.
However, there are more opportunities for constant folding
after data flow optimizations of the VM code.
Early constant folding will not fold, for instance,
(let ((a 2) (b 3)) (* a b))
but we can reduce this to an end instruction that returns
the value of a D register that holds 6. Data flow optimizations
will propagate the D registers for 2 and 3 into the gcall
instruction. We can then recognize that we have a gcall with
nothing but D register operands, calling a constant-foldable
function. We can allocate a new D register to hold the result
of that calculation and just move that D register's value
into the target register of the original gcall.
* stdlib/compiler.tl (compiler get-dreg): When allocating
a new D reg, we must invalidate the datavec slot which is
calculated from the data hash. This didn't matter before,
because until now, get-datavec was called after compilation,
at which point no new D regs will exist. That is changing;
the optimizer can allocate D regs.
(compiler null-dregs, compiler null-stab): New methods.
(compiler optimize): Pass self to constructor for basic-blocks.
basic-blocks now references back to the compiler.
At optimization level 5 or higher, constant folding can
now happen, so we call the new method in the optimizer to
null the unused data. This overwrites unused D registers
and unused parts of the symbol vector with nil.
* stdlib/optimize (basic-blocks): Boa constructor now takes
a new leftmost param, the compiler.
(basic-blocks do-peephole-block): New optimization case:
gcall instruction invoking const-foldable function, with
all arguments being dregs.
(basic-blocks null-unused-data): New method.
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (clean-file): Under a log-level
of 1 or more, report clean-file removes a file.
(compile-update-file): Under a log level of 1 or more,
report when a compiled file was skipped due to being
up-to-date.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
With log-level, we can obtain trace messages about
what file is being compiled and individual forms
within that file.
* autoload.c (compiler_set_entries): Intern the slot
symbol log-level.
* stdlib/compiler.tl (compile-opts): New slot, log-level.
(%warning-syms%): Add log-level to %warning-syms%.
Probably we need to rename this variable.
(compile-file-conditionally): Implement the two log
level messages.
(with-compile-opts): Allow/recognize integer option values.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This function simplifies cleaning, by allowing a file to
be cleaned to be identified in much the same way as an input
file to load or compile-file.
* autoload.c (compiler_set_entries): The clean-file symbol
is interned and becomes an autoload trigger for the
compiler module.
* stdlib/compiler.tl (clean-file): New function.
* txr.1: Documented.
* stdlib/doc-syms.tl: Updated.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The file compiler combines compiled forms into a single
list as much as possible so that objects in the list can
share structure (e.g. merged string literals). However,
when package-manipulating forms occur, like defpackage,
it has to spit these lists, since the package manipulations
of an earlier form affect the processing of a later form,
such as whether symbols in that form are valid.
This splitting does not take care of the case that an
empty piece may result when the very last form is a package
manipulation form. A nil gets written to the .tlo file,
which the load function does not like; load thinks that since
this is not a valid list of compiled forms, it must be the
version number field of a catenated .tlo file, and proceeds
to find it an invalid, incompatible version.
* stdlib/compiler.tl (dump-to-tlo): Use partition* rather than
split*. partition* doesn't leave empty pieces.
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (comp-fbind): When after removing unused
functions we are left with an empty list (or the list of
functions was empty to begin with), let's only emit the body
fragment without any frame wrapping. We can't just return
bfrag because that was compiled in the environment which
matches the frame. Instead of the expense of compiling the
code again, we rely on eliminate-frame to move all v registers
up one level.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The with-compile-opts macro is rewritten such that
it cad occur inside code that is being compiled, and
change compiler options for individual subexpressions.
It continues to work as before in scripted build steps
such as when calls to (compile-file ...) are wrapped
in it. However, for the time being, that now only works
in interpreted code, because with this change, when
a with-compile-opts form is compiled, it no longer
arranges for the binding of *compile-opts* to be visible
to the subforms; the binding affects the compiler's
own environment.
* stdlib/compiler.tl (with-compile-opts): Rewrite.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* eval.c (compiler_let_s): New symbol variable.
(op_let): Recognize compiler-let for sequential
binding.
(do_expand): Traverse and diagnose compiler-let
form.
(eval_init): Initialize compiler_let_s and register
the interpreted version of the operator.
* stdlib/compiler.tl (compiler compile): Handle
compiler-let form.
(compiler comp-compiler-let): New method.
(no-dvbind-eval): New function.
* autoload.c (compiler-set-entries): Intern the
compiler-let symbol in the user package.
* txr.1: Documented.
* stdlib/doc-syms.tl: Updated.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Adding a progv operator, similar to the Common Lisp one.
* eval.c (progv_s): New symbol variable.
(op_progv): New static function.
(do_expand): Recognize and traverse the progv form.
(rt_progv): New static function: run-time support
for compiled progv.
(eval_init): Initialize progv_s, and register the the
op_progv operator interpreting function.
* stdlib/compilert (compiler compile): Handle progv
operator ...
(compiler comp-progv): ... via this new method.
* tests/019/progv.tl: New file.
* txr.1: Documented.
* stdlib/doc-syms.tl: Updated.
|
|
|
|
|
| |
* stdlib/compiler.tl (with-compile-opts): Remove stray
character from "uncrecognized".
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When a defmacro form is compiled, the entire form is retained
as a literal in the output. This is wasteful and gives away
the source code. In spite of that, errors in using the
macro are incorrectly reported against defmacro, because
that is the first symbol in the form. These issues arise with
what arguments are passed as the first two parameters of the
compiler's expand-bind-mac-params function, and what exactly
it does with them. We make a tweak to that, as well as some
tweaks to all the calls.
* stdlib/compiler.tl (expand-bind-mac-params): There is
a mix-up here in that both the ctx-form and err-form
arguments are ending up in the compiled output. Let's
have only the first agument, ctx-form going into the
compiled output. Thus that is what is inserted into
the sys:bind-mach-check call that is generated.
Secondly, ctx-form should not be passed to the constructor
for mac-param-parser. ctx-form is a to-be-evaluated
expression which might just be a gensym; we cannot use
it at compile time for error reporting. Here we must
use the second argument. Thus the second argument is now
used only for two purposes: copying the source code info
to the output code, and for error reporting in
the mac-param-parser class. This second purpose is minor,
because the code has been passed through the macro expander
before being compiled, which has caught all the errors.
Thus the argument is changed to rlcp-form, reflecting its
principal use.
(comp-tree-bind, comp-tree-case): Calculate a simplified
version of the tree-bind or tree-case form for error reporting
and pass that as argument the ctx-form argument of
expand-bind-mac-params. Just pass form as the second argument.
(comp-mac-param-bind, comp-mac-env-param-bind):
Just pass form as the second argument of
expand-bind-mac-params.
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (compiler comp-call-impl): We can no longer
free the temporary registers as-we-go based on whether the
argument expression frag uses them as the output register
frag. Let's just put them all into the aoregs list to be freed
afterward.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Instead of the conservative strategy in compiler comp-var of
loading variables into t-registers, and relying on optimization
to remove them, let's just go back to the old way: variables
are just registers. For function calls, we can detect mutated
variables and generate the conservative code.
* stdlib/compiler.tl (frag): New slots vbin and alt-oreg.
When a variable access is compiled, the binding is recorded
in vbin, and the desired output register in alt-oreg.
(simplify-var-spy): New struct type, used for detecting
mutated lexical variables when we compile a function argument
list.
(compiler comp-var): Revert to the old compilation strategy
for lexicals: the code fragment is empty, and the output
register is just the v-reg. However, we record the variable
binding and remember the caller's desired register in the
new frag fields.
(compiler comp-setq): Also revert the strategy here.
Here we get our frag from a recursive compilation, so
we just annotate it.
(compiler comp-call-impl): Use the simplify-var-spy to
obtain a list of the lexical variables that were mutated.
This is used for rewriting the frags, if necessary.
(handle-mutated-var-args): New function. If the mutated-vars
list is non-empty, it rewrites the frag list. Every element
in the frag which is a compiled reference to a lexical
variable which is mutated over the evaluation of the arg list
is substituted with a conservative frag which loads the
variable into a temporary register. That register thus
samples the value of the variable at the correct point in the
left-to-right evaluation, so the function is called with
the correct values.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We have the following problem: when function call argument
expressions mutate some of the variables that are being
passed as arguments, the left-to-right semantics isn't
obeyed. The problem is that the funcction call simply refers
to the registers that hold the variables, rather than to
the evaluated values. For instance (fun a (inc a)) will
translate to something like (gcall <n> (v 3) (v 3))
which is incorrect: both argument positions refer to the
current value of a, whereas we need the left argument
to refer to the value before the increment.
* stdlib/compiler.tl (compiler comp-var): Do not assert the
variable as the output register, with null code. Indicate
that the value is in the caller's output register, and
if necessary generate the move.
(compiler comp-setq): When compiling the right-hand-side,
use the original output register, so that we don't end
up reporting the variable as the result location.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (compiler): Remove discards slot.
(compile-in-toplevel, compile-with-fresh-tregs):
Do not save and restore discards.
(compiler maybe-mov): Method removed. It doesn't
require the compiler object so it can just be a function.
(maybe-mov): New function.
(compiler alloc-discard-treg): Method removed.
(compiler free-treg): No need to do anything with discards.
(compiler maybe-alloc-treg): No need to check discards.
(compiler (comp-setq, comp-if, comp-ift, comp-switch,
comp-block, comp-catch, comp-let, comp-fbind,
comp-lambda-impl, comp-or, comp-tree-case,
comp-load-time-lit): Use maybe-mov function instead of method.
(compiler comp-progn): Use alloc-treg rather than
alloc-discard-treg, and use maybe-mov function.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/optimize.tl (basic-blocks num-blocks): New
method.
* stdlib/compiler.tl (compiler optimize): At optimization
level 6, instead of performing one extra pass of
jump threading, dead-code elimintation and peephole
optimizations, keep iterating on these until the number
of basic blocks stays the same.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/optimize.tl (basic-blocks peephole-block): Drop the
code argument, and operate on bl.insns, which is stored
back. Perform the renames in the rename list after the
peephole pass.
(basic-blocks rename): New method.
(basic-blocks do-peephole-block): Implementation of
peephole-block, under a new name. The local function called
rename is removed; calls to it go to the new rename method.
(basic-blocks peephole): Simplify code around calls to
peephole-block; we no longer have to pass bl.insns to it,
capture the return value and store it back into bl.insns.
* stdlib/compiler.tl (*opt-level*): Initial
value changes from 6 to 7.
(compiler optimize): At optimization level 6,
we now do another jump threading pass, and
peephole, like at levels 4 and 5. The peephole
optimizations at level 5 make it possible
to coalesce some basic blocks in some cases,
and that opens up the possibility for more
reductions. The previously level 6 optimizations
are moved to level 7.
* txr.1: Updated documentation of optimization levels,
and default value of *opt-level*.
* stdlib/doc-syms.tl: Updated.
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (sys:env shadow-fun): Also diagnose
if a global macro is shadowed.
* txr.1: Documented compiler-opts structure, *compiler-opts*
variable and with-compiler-opts macro.
* stdlib/doc-syms.tl: Updated.
|
|
|
|
| |
* stdlib/compiler.tl (expand-dohash): Add missing rlcp.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (expand-defun): Sprinkling of rlcp
to pass source location info to the generated lambda,
and to the sys:define-method call.
(expand-defmacro): bugfix here: in with-gensyms we
shadowed the form parameter, and then passed that as both
form arguments to expand-bind-mac-params. We rename
the gensym to mform, and then for the error-form,
we pass the original form, quoted as necessary and with
source location info. Thus, now source location info
flows from the original defmacro form to the generated
let* which binds the destructured parameters.
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (compiler (comp-atom, comp-dwim),
safe-const-reduce, igno-notfound): Use ignore
rather than use for marking unused variable.
* stdlib/copy-file.tl (copy-files, copy-path-rec,
remove-path-rec, chmod-rec, chown-rec): Likewise.
* stdlib/optimize.tl (basic-block print): Likewise.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We want the ignore function to go away; but if variables
are mentioned, to suppress unused warnings on them.
* stdlib/compiler.tl (%functional-funs%): Remove nilf
from list since we are handling it specially.
(compiler comp-fun-form): Recognize (ignore ...)
and (nilf ...) forms, transforming
them into (progn .... nil). In the case of ignore,
walk the arguments: if any look like variables, mark
them used.
Also, add the use function to the pattern which handles
identity, since it is a synonym.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Now that we have the t convention in macro parameters,
we can use it to suppress many cases of unused variables
in the compiler.
* stdlib/compiler.tl (compiler (comp-setq, comp-lisp1-setq,
comp-setqf, comp-cond, comp-ift, comp-switch,
comp-unwind-protect, comp-return, comp-handler-bind,
comp-catch, eliminate-frame, comp-lambda-impl,
comp-fun, comp-or, comp-prog1, comp-arith-form,
comp-arith-neg-form, comp-fun-form, comp-apply-call,
comp-for, comp-tree-bind, comp-mac-param-bind,
comp-mac-env-param-bind, comp-tree-case, comp-lisp1-value,
comp-dwim, comp-prof, comp-load-time-lit), expand-quasi-mods,
expand-dohash, expand-each, expand-defvar, expand-defun,
expand-defmacro, expand-defsymacro, lambda-apply-transform,
usr:compile): Fix unused variable warnings mostly by using
the t mechanism in tree-case or mac-param-bind. In
some cases, (use var) is used where it would be detrimental
to diagnostic quality to replace identifiers in the
pattern with t. A few unused "else" variables were renamed
and used.
(safe-const-reduce, ign-notfound): Fix unused exception
clause unused parameters using (use param).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* eval.c (expand_params_rec, bind_macro_params): Handle t
specially everywhere a parameter can occur. Expansion
allows the syntax through without extending the
environment with a t variable; binding walks over
the structure without binding a variable.
* stdlib/compiler.tl (expand-bind-mac-params): Likewise,
handle occurrences of t, suppressing the generation of
and assignment to variables, while ensuring that
initializing expressions are evaluated.
* tests/011/tree-bind.tl: New file.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We fix numerous unused variable situations uncovered
by the new diagnostic. Most of those occurring inside
tree-bind or mac-param-bind forms remain unfixed.
These are caused by the idiom of binding a dummy variable
as a placeholder in the structure. I am instead going to
introduce a mechanism into tree-bind/mac-param-bind
for indicating an ignored piece of structure.
* stdlib/compiler.tl (compiler (comp-if, eliminate-frame,
comp-lambda-impl, comp-typep, comp-fun-form, expand-and,
reduce-or, compiler-emit-warnings, usr:compile
with-compile-opts): Eliminate unused variables in structural
pattern matches in various ways: eliminating predicate
argument variables, replacing place holder variables by
@nil, or just using the variables when possible.
(compiler compile-in-toplevel): Remove unused saved-nlev variable.
(compiler comp-atom): Use (use oreg) form to suppress
unused parameter warning.
(compiler comp-return-form): Eliminate unused binfo variable.
The lookup-block method is called for the side effect of
marking the block used, so we keep that call.
(compiler comp-let): Unused variable specials is gone.
(compiler comp-or): Unused variable lastfrag is gone,
as is the assignment to it. There is a reason assignment
isn't use!
(compiler comp-inline-lambda): Get rid of the two variables
called dummy by folding the associated calculation into
an adjacent initform using progn and prog1.
(comp-tree-case): Remove unused ncases, lerrtest and lnext
variables.
(safe-const-eval): Remove unused reduced-form variable,
and simplify code, eliminating another local.
|
|
|
|
|
| |
* stdlib/compiler.tl (opt-controlled-diag): If a the compiler
option's value is t, treat it as :warn.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Unused variables in tree-bind forms are not generating
diagnostics with source location info. We are missing
some rlcp calls.
* stdlib/compiler.tl (compiler comp-catch): The generated
lambda here ends up transformed to a let by the
lambda-apply-transfom function. We must propagate source
info to it, otherwise unused catch clause parameters
get diagnosed without it.
(compiler (comp-for, comp-mac-param-bind,
comp-mac-env-param-bind, comp-tree-case): Confer source
location info onto the err-form argument of
expand-bind-mac-params.
(expand-bind-mac-params): Pass source location info
from err-form onto the generated let* form.
Thus, diagnostics related to variables in that let*
get reported against that form's location.
(lambda-apply-transform): Pass source location info
from the lambda expression to the generated let.
* stdlib/except.tl (usr:catch): Pass source loc info
from each clause source code to the transformed
clause. The transformed clause will turn into a lambda
which will turn into a let in comp-catch, and then
into a let in lambda-apply-transform.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* autoload.c (compiler_set_entries): Register slot symbol
"unused".
* stdlib/compiler.tl (compile-opts): New slot, unused.
(%warning-syms%): List unused symbol.
(env lookup-var): Support optional mark-used parameter,
just like lookup-fun.
(env unused-check): New method.
(compiler comp-var): Pass t to mark-used parameter of
lookup-var to register the use.
(compiler (comp-let, comp-var)): Call unused-check
method after sub-compilations are done to dump
diagnostics about unused variables.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Introducing a compiler options system, so we can
control diagnostics and such. We begin with
three options for diagnosing shadowing.
* autoload.c (compiler_set_entries): Register a
structure name compiler-opts, a with-compile-opts
function name, *compile-opts* variable name, and
slots shadow-fun, shadow-var and shadow-cross.
* stdlib/compiler.tl (compile-opts): New struct.
(%warning-syms%): New macro.
(*compile-opts*): New special variable.
(when-opt, with-compile-opts): New macros.
(opt-controlled-diag): New function.
(env extend-var): Call extend-var* method instead of
repeating code.
(env extend-var*): Implement shadow-var and shadow-cross
diagnostic options.
(env extend-fun): Implement shadow-fun and shadow-cross
diagnostic options.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* LICENSE, LICENSE-CYG, METALICENSE, Makefile, alloca.h,
args.c, args.h, arith.c, arith.h, autoload.c, autoload.h,
buf.c, buf.h, cadr.c, cadr.h, chksum.c, chksum.h,
chksums/crc32.c, chksums/crc32.h, combi.c, combi.h, configure,
debug.c, debug.h, eval.c, eval.h, ffi.c, ffi.h, filter.c,
filter.h, ftw.c, ftw.h, gc.c, gc.h, glob.c, glob.h, gzio.c,
gzio.h, hash.c, hash.h, itypes.c, itypes.h, jmp.S,
lex.yy.c.shipped, lib.c, lib.h, linenoise/linenoise.c,
linenoise/linenoise.h, match.c, match.h, parser.c, parser.h,
parser.l, parser.y, protsym.c, psquare.h, rand.c, rand.h,
regex.c, regex.h, signal.c, signal.h, socket.c, socket.h,
stdlib/arith-each.tl, stdlib/asm.tl, stdlib/awk.tl,
stdlib/build.tl, stdlib/cadr.tl, stdlib/compiler.tl,
stdlib/constfun.tl, stdlib/conv.tl, stdlib/copy-file.tl,
stdlib/debugger.tl, stdlib/defset.tl, stdlib/doloop.tl,
stdlib/each-prod.tl, stdlib/error.tl, stdlib/except.tl,
stdlib/ffi.tl, stdlib/getopts.tl, stdlib/getput.tl,
stdlib/hash.tl, stdlib/ifa.tl, stdlib/keyparams.tl,
stdlib/match.tl, stdlib/op.tl, stdlib/optimize.tl,
stdlib/package.tl, stdlib/param.tl, stdlib/path-test.tl,
stdlib/pic.tl, stdlib/place.tl, stdlib/pmac.tl,
stdlib/quips.tl, stdlib/save-exe.tl, stdlib/socket.tl,
stdlib/stream-wrap.tl, stdlib/struct.tl, stdlib/tagbody.tl,
stdlib/termios.tl, stdlib/trace.tl, stdlib/txr-case.tl,
stdlib/type.tl, stdlib/vm-param.tl, stdlib/with-resources.tl,
stdlib/with-stream.tl, stdlib/yield.tl, stream.c, stream.h,
struct.c, struct.h, strudel.c, strudel.h, sysif.c, sysif.h,
syslog.c, syslog.h, termios.c, termios.h, time.c, time.h,
tree.c, tree.h, txr.1, txr.c, txr.h, unwind.c, unwind.h,
utf8.c, utf8.h, vm.c, vm.h, vmop.h, win/cleansvg.txr,
y.tab.c.shipped: Copyright year bumped to 2023.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When an invalid call expression is constant folded, such
as (call 'abs 1 2), runaway recursion occurs. This is
because due to the wrong number of arguments being passed
to abs, the safe-const-reduce function returns the
expression unmodified. The comp-apply-call method then
passes it to compile, wrongly assuming a reduction had
taken place, and so everything repeats.
* stdlib/compiler.tl (comp-apply-call): Detect when
safe-const-reduce has hit a fixed point by returning
the input form. In that case, we don't call the compiler
top-level entry point, but the comp-fun-form method
directly; the wrong function call will be compiled without
constant folding and throw an error at run-time.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (comp-catch): Under an optimization level
of at least 1, if no symbols are being caught, or if the
try expression is a safe constant expression, then just
compile the try expression. Furthermore, if there is only one
exception symbol being caught, and a catch clause is for a
subtype of that symbol, we eliminate the run-time
exception-subtype-p test. This will always be true if the catch
macros are being used, because the list of symbols is derived
from the clauses. Lastly, if there is only one exception symbol
being caught, any clause which doesn't match that symbol is
now eliminated as dead code. That shouldn't happen unless
the sys:catch operator is used directly.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The bad situation reproduced as a miscompilation of some prof
forms at *opt-level* 5 or above.
The basic idea is that there is a situation like this
prof t2
... profiled code here producing value in t8
mov t2 t8
end t2
end t2
The code block produces a value in t8, which is copied into
t2, and executes the end instruction. This instruction does not
fall through to the next one but passes control back to the
prof instruction. The prof instruction then stores the result
value, which came from t2, back into the t2 register and
resumes the program at the end t2.
The first bad thing that happens is that the end instructions
get merged together into one basic block. The optimizer then
treats them without regard for the prof instruction, as if
they were a linear sequence. It looks like the register move
mov t2 t8
is wasteful and so it eliminates it, rewriting the end instruction
to:
end t8
end t8
Of course, the second instruction is now wrong because prof is
still producing the result in t2.
To fix this without changing the instruction set, I'm introducing
another pseudo-op that represents end, called xend. This is
similar to jend, except that jend is regarded as an unconditional
branch whereas xend isn't. The special thing about xend is
that a basic block in which it occcurs is marked as non-joinable.
It will not be joined with the following basic block.
* stdlib/asm.tl (xend): New alias opcode for end.
* stdlib/compiler.tl (comp-prof): Use xend to end prof fragment,
rather than plain end.
* stdlib/optimize.tl (basic-block): New slot, nojoin.
If true, block cannot be joined with next one.
(basic-blocks jump-ops): Add xend to list of jump ops,
so that a basic block will terminate on xend.
(basic-blocks link-graph): Set the nojoin flag on a
basic block which contains (and thus ends with) xend.
(basic-blocks local-liveness): Add xend to the case
in def-ref that handles end.
(basic-blocks (peephole, join-blocks)): Refuse to join
blocks marked nojoin.
* tests/019/comp-bugs.tl: New file with miscompiled
test case that was returning 42 instead of (42 0 0 0)
as a result of the wrong register's value being returned.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The scoping is not behind handled correctly for optional
variables. The init-forms are being evaluated in a scope
in which all the variables are already visible, instead
of sequentially. Thus, for instance, variable rebinding
doesn't work, as in (lambda (: (x x)) ...). When the
argument is missing, x ends up with the value : because
the expression refers to the new x, rather than the
outer x.
* stdlib/compiler.tl (compiler comp-lambda-impl):
Perform the compilation of the init-forms earlier.
Use the same new trick that is used for let*:
the target for the code fragment is a locaton obtained
from get-loc, which is then attached to a variable
afterward. The spec-sub helper is extended with a loc
parameter to help with this case.
* tests/012/lambda.tl: New test case that fails without
this fix.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (env rename-var): Method removed.
(compiler comp-let): Instead of initially creating
a let* variable as a gensym, and then renaming it
after compiling the init expression, we now just
obtain the location not bound to a variable, use the
location when compiling the init form, and bind
the location to a variable right after. This is
cleaner since the only thing we are mutating now is
the environment, and we are not wastefully allocating
a gensym. The real motivation is that this is building
up to a bugfix in compiling optional variables in
lambda: stay tuned!
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (env get-loc): New method for
allocating v-reg, split out of extend-var and
extend-var*. Now there is a check for the v-cntr
overflow.
(env (extend-var, extend-var*)): Taken an optional
loc parameter, so the caller can optionally allocate
a v-reg location using get-loc, and then specify
that location when creating a variable. If the
argument is omitted, use get-loc.
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (env (extend-var, extend-var*)):
Return the variable binding rather than the alist
containing it.
(compiler (comp-catch, comp-let, comp-tree-case)):
Drop use of cdar on return value of extend-var
to ferret out the binding from the alist.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The compile-file function must only try a different
path, such as with a suffix, if a given path fails
to open due to non-existence. If the failure is for
another reason, like permissions. In that case we want
to propagate the failure.
* stdlib/compiler.tl (ign-notfound): New macro.
This lets through all errors, catching only path-not-found,
converting that to a nil result.
(open-compile-streams): Use ign-notfound instead of
ignerr when trying to open an input file for reading.
Also, we lose the ignerr wrapping around the open-file.
We let any error whatsoever just bubble out so that the user
is better informed about what went wrong. The requirement
to close the input stream is handled by the obvious
unwind-protect.
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (translate-hash-bang): New function.
(compile-file-conditionally): Use translate-hash-bang to
treat hash bang line.
* txr.1: Revised hash bang treatment by file compiler
documented.
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (open-compile-streams): If the in-path
is unsuffixed, try opening it without adding any suffix first.
If that fails, then try .tl in that order.
* txr.1: Documented.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* stdlib/compiler.tl (compile-file-conditionally): Recognize a
potential package-manipulating form not checking whether its
main operator is in %pakage-manip% list, but whether any
global functions that its compiled image references are in
that list. This is the same approach that is used in
dump-compiled-objects. This fix is needed for correctly
recognizing defpackage as a package-manipulating form.
defpackage macro-expands to a let form which contains a call
to make-package. Testing whether let is in %package-manip% is
useless; of course it isn't, and the test overlooks
make-package.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* eval.c (eval_init): Register isecp intrinsic.
* lib.c (isecp): New function.
* lib.h (isecp): Declared.
* stdlib/compiler.tl (lambda-apply-transform,
dump-compiled-objects): Use isecp instead of isec, since the
actual intersection of symbols isn't needed, only whether it
exists.
* txr.1: Documented.
* stdlib/doc-syms.tl: Updated.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Commit 93edcde038209335122964432bd35dee0c2ecb04, made in
August 2021, accidentally removed the blank line after the
copyright header in most stdlib files.
stdlib{asm.tl, awk.tl, build.tl, compiler.tl, copy-file.tl,
debugger.tl, doloop.tl, each-prod.tl, error.tl, except.tl,
ffi.tl, getopts.tl, getput.tl, hash.tl, ifa.tl, match.tl,
op.tl, package.tl, param.tl, path-test.tl, pic.tl, place.tl,
pmac.tl, quips.tl, save-exe.tl, socket.tl, stream-wrap.tl,
tagbody.tl, termios.tl, trace.tl, txr-case.tl, type.tl,
vm-param.tl, with-resources.tl, with-stream.tl, yield.tl}:
Ensure there is a blank line after the copyright header.
|