diff options
author | Kaz Kylheku <kaz@kylheku.com> | 2023-03-22 23:57:38 -0700 |
---|---|---|
committer | Kaz Kylheku <kaz@kylheku.com> | 2023-03-22 23:57:38 -0700 |
commit | 502c6b4d4a1e29c51c80a39a6eaef27a3f5c0d89 (patch) | |
tree | 2dabede4707e240329405b6f008da043766dc657 /stdlib/place.tl | |
parent | df0ade89277738dea89abfaa226e91a30025bf60 (diff) | |
download | txr-502c6b4d4a1e29c51c80a39a6eaef27a3f5c0d89.tar.gz txr-502c6b4d4a1e29c51c80a39a6eaef27a3f5c0d89.tar.bz2 txr-502c6b4d4a1e29c51c80a39a6eaef27a3f5c0d89.zip |
lib: address remaining unused variable warnings.
* stdlib/arith-each.tl (sys-arith-each): Remove :form param.
* stdlib/awk.tl (awk-state :fini): Suppress unused warning
in dohash form by using an uninterned symbol for this
variable. This is a useful technique worth documenting.
(awk-expander): Remove unused varaible in a predicate
pattern.
(awk-code-move-check): Lose the unused awc and aws-sym.
(awk-mac-let): Don't pass the unused parameters to
awk-code-move-check.
* stdlib/conv.tl (conv-expand): Remove unused gensym.
* stdlib/debugger.tl (fcall-frame loc,
fcall-frame print-trace, expand-frame print-trace):
Mark unused parameters ignored.
* stdlib/defset.tl (defset-expander-simple): Remove
unused parameter.
(defset): Drop argument from defset-expander-simple
call, and also fix unused warning in tree-case form.
* stdlib/doc-lookup.tl (detached-run): Remove unused
variable from a pattern matching predicate.
It's not in the rightmost position so we have to
revers the comparison. I will enhance the pattern
matcher to support @nil in a predicate.
(toplevel): Ignore a parameter of the not-implemented
version of the open-url function.
* stdlib/doloop.tl (expand-dooloop): Replace unused
variable in a tree binding pattern with the t
symbol.
* stdlib/each-prod.tl (expand-each-prod*): Remove
unused let variable.
* stdlib/except.tl (expand-handle): Put else variable
in tree bind pattern to use.
* stdlib/getopts.tl (opt-desc (basic-type-p, cumul-type-p)):
Replace unused catch-all variable in tree bind pattern
with t symbol.
(opt-processor parse-opts): Remove unused args argument.
The object holds the args, prepared at construction time.
(getopts, option-base getopts): Don't pass args to parse-opts.
(define-option-struct): Replace unused treee pattern
variable with t.
* stdlib/ifa.tl (if-to-cond): Put catch-all else variable
to use.
* stdlib/keyparams.tl (param-expander): Mark unused parameter
ignored. Replace unused variables in tree-case with t.
* stdlib/match.tl (compile-struct-match, compile-predicate-match,
compile-require-match, compile-as-match, compile-with-match,
compile-or-match, compile-and-match, compile-not-match,
compile-hash-match, compile-scan-match, compile-exprs-match):
Address unused variables in mac-param-bind and tree-bind
patterns.
(match-case): Likewise, and also remove unused let variables.
(while-match-case, while-true-match-case): Remove unused
:env parameter.
(expand-lambda-match): Remove unused let variable.
(defun-match): Remove unused variable in tree-bind.
(define-param-expander): Mark menv parameter ignored.
Unused variables in tree-bind.
(defmatch): Replace lambda variable with a gensym.
(loosen, pat-len): Remove unused parameter.
(sme, end): Fix calls to loosen and pat-len.
(non-triv-pat-p): Mark parameter ignored in the
temporary version of this function.
(expand-quasi-match): Address unused variables in patterns,
and remove unused gensyms.
* stdlib/op.tl (op-rec-p): Unused variable in tree-case.
(op-alpha-rename): Remove f parameter.
(op-ignerr): Mark catch handler parameter ignored.
(op-expand): Remove argument from calls to op-alpha-rename.
* stdlib/path.test (if-windows, if-native-windows): The
compiler complains here about the unused variable
due to constant folding. We use the use function
to indicate that the variable is not ignored, but used.
* stdlib/pic.tl (expand-pic-num): Remove unused let variable.
(pic): Remove unused :env parameter.
* stdlib/place.tl (macroexpand-1-place): Ignore unused
env parameter.
(pset): Ignore some tree-bind variables. Not replacing
them with t because their names help code readability.
Lots of tricky code in place.tl.
(shift): Replace unused variable with t in tree-case.
(vecref, chr-str, ref, sub): Deal with unused expander
parameters.
(gethash): Deal with unused place parameter.
(dwim): Remove unused env parameter, and deal with
unused place parameters.
(get-fun-getter-setter): Unused variables in tree-bind.
(read-once, define-modify-macro): Remove unused gensyms.
(placelet-1): Mark ignored a parameter of an update
expander lambda.
* stdlib/pmac.tl (macroexpand-params): Fix unused
catch-all in tree-case.
* stdlib/struct.tl (prune-missing-inits): Mark
tree-bind unused variable ignored.
(defstruct): Unused tree-case variable.
(qref): Unused tree-case catch-all variables.
(rslot): Unused parameter removed.
(:delegate): Unused tree-case variables.
* stdlib/tagbody.tl (tagbody): Drop unused :env param.
Mark ignored the threaded-2 let variable, which cannot
be removed because its init-form performs a needed
side effect.
* stdlib/trace.tl (trace-leave): Remove unused param.
(trace): Don't pass argument to unused param of trace-leave.
(untrace): Use gensym in dohash to suppress unused
variable warning.
* stdlib/type.tl (typecase-expander): Unused variable
in tree-case.
* stdlib/with-resources.tl (with-resources): Likewise.
* stdlib/yield.tl (hlet-expand): Remove two unused locals.
* tests/012/lambda.tl: Fix test cases that break the
tests due to unused variable warnings.
* tests/016/arith.tl: Add test case for each-prod*.
At first I thought a bug was found in it but it turned
out that the init-forms variable that was removed
was really superfluous.
Diffstat (limited to 'stdlib/place.tl')
-rw-r--r-- | stdlib/place.tl | 40 |
1 files changed, 27 insertions, 13 deletions
diff --git a/stdlib/place.tl b/stdlib/place.tl index dd79a4b3..13b9bb18 100644 --- a/stdlib/place.tl +++ b/stdlib/place.tl @@ -79,7 +79,8 @@ (return-from macroexpand-place place)) (sys:setq unex-place place)))) -(defun macroexpand-1-place (unex-place : env-unused) +(defun macroexpand-1-place (unex-place : env) + (ignore env) (let ((pm-expander (if (consp unex-place) (sys:get-place-macro (car unex-place))))) (if pm-expander @@ -215,13 +216,15 @@ (list a b (gensym) (gensym) (gensym))) (tuples 2 place-value-pairs))) (ls (reduce-left (tb ((lets stores) (place value temp getter setter)) - (list ^((,temp ,value) ,*lets) - ^((,setter ,temp) ,*stores))) + (ignore place getter) + (list ^((,temp ,value) ,*lets) + ^((,setter ,temp) ,*stores))) pvtgs '(nil nil))) (lets (first ls)) (stores (second ls)) (body-form ^(rlet (,*lets) ,*stores))) (reduce-left (tb (accum-form (place value temp getter setter)) + (ignore place value temp) (call-update-expander getter setter place env accum-form)) pvtgs body-form)))))) @@ -307,7 +310,7 @@ (defmacro shift (:form f :env env . places) (tree-case places (() (compile-error f "need at least two arguments")) - ((place) (compile-error f "need at least two arguments")) + ((t) (compile-error f "need at least two arguments")) ((place newvalue) (with-update-expander (getter setter) place env ^(prog1 (,getter) (,setter ,newvalue)))) @@ -530,6 +533,7 @@ (defplace (vecref vector index :whole args) body (getter setter (with-gensyms (vec-sym ind-sym) + (ignore args) ^(alet ((,vec-sym ,vector) (,ind-sym ,index)) (macrolet ((,getter () ^(vecref ,',vec-sym ,',ind-sym)) @@ -537,9 +541,11 @@ ,body)))) (ssetter ^(macrolet ((,ssetter (val) ^(refset ,*',args ,val))) + ,(ignore vector index) ,body)) (deleter (with-gensyms (vec-sym ind-sym) + (ignore args) ^(alet ((,vec-sym ,vector) (,ind-sym ,index)) (macrolet ((,deleter () @@ -551,6 +557,7 @@ (defplace (chr-str string index :whole args) body (getter setter (with-gensyms (str-sym ind-sym) + (ignore args) ^(alet ((,str-sym ,string) (,ind-sym ,index)) (macrolet ((,getter () ^(chr-str ,',str-sym ,',ind-sym)) @@ -558,9 +565,11 @@ ,body)))) (ssetter ^(macrolet ((,ssetter (val) ^(chr-str-set ,*',args ,val))) + ,(ignore string index) ,body)) (deleter (with-gensyms (str-sym ind-sym) + (ignore args) ^(alet ((,str-sym ,string) (,ind-sym ,index)) (macrolet ((,deleter () @@ -572,6 +581,7 @@ (defplace (ref seq index :whole args) body (getter setter (with-gensyms (seq-sym ind-sym) + (ignore args) ^(alet ((,seq-sym ,seq) (,ind-sym ,index)) (macrolet ((,getter () ^(ref ,',seq-sym ,',ind-sym)) @@ -579,9 +589,11 @@ ,body)))) (ssetter ^(macrolet ((,ssetter (val) ^(refset ,*',args ,val))) + ,(ignore seq index) ,body)) (deleter (with-gensyms (seq-sym ind-sym) + (ignore args) ^(alet ((,seq-sym ,seq) (,ind-sym ,index)) (macrolet ((,deleter () @@ -590,7 +602,7 @@ ,',ind-sym (succ ,',ind-sym))))) ,body))))) -(defplace (sub seq :whole args : (from 0) (to t)) body +(defplace (sub seq : (from 0) (to t)) body (getter setter (with-gensyms (seq-sym from-sym to-sym v-sym) (with-update-expander (seq-getter seq-setter) seq sys:*pl-env* @@ -632,6 +644,7 @@ (defplace (gethash hash key : (default nil have-default-p)) body (getter setter (with-gensyms (entry-sym) + (ignore have-default-p) ^(let ((,entry-sym (inhash ,hash ,key ,default))) (macrolet ((,getter () ^(cdr ,',entry-sym)) (,setter (val) ^(sys:rplacd ,',entry-sym ,val))) @@ -662,9 +675,9 @@ ^(set-hash-userdata ,',hash ,val))) ,body))) -(defplace (dwim obj-place :env env . args) body +(defplace (dwim obj-place . args) body (getter setter - (with-gensyms (ogetter-sym osetter-sym obj-sym newval-sym) + (with-gensyms (obj-sym newval-sym) (let ((arg-syms (mapcar (ret (gensym)) args))) (if (place-form-p obj-place sys:*pl-env*) (with-update-expander (ogetter-sym osetter-sym) @@ -691,7 +704,7 @@ ,',newval-sym))) ,body)))))) (ssetter - (with-gensyms (osetter-sym ogetter-sym obj-sym newval-sym) + (with-gensyms (obj-sym newval-sym) (let ((arg-syms (mapcar (ret (gensym)) args))) (if (place-form-p obj-place sys:*pl-env*) (with-update-expander (ogetter-sym osetter-sym) @@ -719,7 +732,7 @@ ,body))))) (deleter - (with-gensyms (osetter-sym ogetter-sym obj-sym oldval-sym) + (with-gensyms (obj-sym oldval-sym) (let ((arg-syms (mapcar (ret (gensym)) args))) (if (place-form-p obj-place sys:*pl-env*) (with-update-expander (ogetter-sym osetter-sym) @@ -805,13 +818,13 @@ (cons (op cdr) (op sys:rplacd cell))) :)) - ((op . rest) + ((op . t) (if (eq op 'lambda) (compile-error f "cannot assign to lambda") (compile-error f "invalid function syntax ~s" sym))) (else (let ((cell (or (gethash sys:top-fb sym) - (sethash sys:top-fb sym (cons sym nil))))) + (sethash sys:top-fb sym (cons else nil))))) (cons (op cdr) (op sys:rplacd cell)))))) @@ -875,7 +888,7 @@ (defplace (read-once place) body (getter setter - (with-gensyms (cache-var pgetter psetter) + (with-gensyms (cache-var) (with-update-expander (pgetter psetter) place sys:*pl-env* ^(slet ((,cache-var (,pgetter))) (macrolet ((,getter () ',cache-var) @@ -885,7 +898,7 @@ (defmacro define-modify-macro (name lambda-list function) (let ((cleaned-lambda-list (mapcar [iffi consp car] (remql : lambda-list)))) - (with-gensyms (place-sym args-sym) + (with-gensyms (place-sym) ^(defmacro ,name (:env env ,place-sym ,*lambda-list) (with-update-expander (getter setter) ,place-sym env ^(,setter (,',function (,getter) ,,*cleaned-lambda-list))))))) @@ -908,6 +921,7 @@ ;; uses of sym as a place will fail due to get-foo not being a place. (sethash *place-update-expander* tmp-place (lambda (tmp-getter tmp-setter tmp-place tmp-body) + (ignore tmp-place) ^(macrolet ((,tmp-getter () ^(,',pl-getter)) (,tmp-setter (val) ^(,',pl-setter ,val))) ,tmp-body))) |