| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is not an easy change to make because it breaks the
validity of existing URLs in the wild which point to specific
sections of the TXR manual.
Some of my recent changes to capitalization of numerous
headings have already broken many URLs, so we might as well
bite the bullet and do this now.
The problem with the current scheme is that entire section
titles are hashed: all the words of a title, not just the
names of functions. Whenever we add a new function, macro or
variable which is documented together with related functions
in the same paragraph under the same heading, the heading
changes, and the hash changes. For instance, the hash for
the hash-map identifier is actually the hash of the string
"Function <tt>hash-map</tt>".
Under the new scheme, section titles are hashed in a more
complicated way that is robust against most edits. If a
title contains any symbols marked up with <tt>, then the
leftmost such symbol is taken as the title. Otherwise,
the whole title is mapped to lower case.
There is no longer a stdlib/doc-syms.tl file, and the
special disambiguated "D-<HEX>" codes are also gone.
Symbols are no longer associated with section hashes or
disambiguation section codes. The hash of a symbol is
a 32 bit CRC-32 checksum, expressed as S-<HEX> where
<HEX> is 8 hex digits. A section which defines symbols
has not only a <a name="..."> for its own hash but also
additional <a name="...>" elements for each of the symbols
that it defines.
If a section defines an ambiguous symbol (one that is also
defined with a different meaning in a different section),
then that symbol is not linked to either section; it is
mapped to the generated disambiguating section.
* genman.txr (dupes): Renamed to dupe-hashes for clarity.
(tagnum): Hash removed.
(direct): New hash. Tracks the assocation between sections
hashes and hashes of symbols that are defined only in
those symbols (no ambiguity) and thus the symbol hashes
can navigate directly to the sections. Serves as a
complement to the disamb hash.
(colli): There are no collisions now, so
initialize this to empty.
(hash-str): Function removed.
(hash-title): This function becomes more complicated.
If a title has at least one <tt>..</tt> item, then
that is taken in its place. Either way, the title
is transformed and enumerated against duplication and
hashed with crc32 instead of the original custom hashing
function.
(enumerate): Function removed: enumeration of titles is
done inside hash-title.
All manipulations of symhash using material from HTML now
use html-decode, so that we hash the original symbol
name like "str<" and not "str<".
When filtering the BODY, we have a new case: whenever
we see a <a name="...">, we now check the new direct
hash to see if there is a list of symbol hashes for
the given section. If so, we generate additional
<a name="..."> definitions for all the symbol hashes.
At the end of the file, the "missing from image"
processing is condensed, and the generation of the
stdlib/doc-syms.tl file is removed.
* stdlib/doc-syms.tl: Removed.
* stdlib/doc-lookup.tl: Don't load doc-syms. Use crc32
plus formatting to conver a symbol to the hash that is
used in the document and try the lookup with that.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* 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.
|
|
|
|
|
|
|
|
|
| |
* stdlib/doc-lookup.tl (open-url): Treat empty BROWSER variable
as if it were unset (i.e., ignore it). Otherwise the doc
function silently fails rather than falling back to alternative
URL-opening methods.
* txr.1: Documented.
|
|
|
|
|
| |
* stdlib/doc-lookup.tl (os-symbol): Add case for OpenBSD.
(open-url): Same.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* genman.txr (dupes, tagnum): Replace defvar with defvarl.
* stdlib/doc-lookup.tl (os-symbol): Same.
* tests/011/macros-3.tl (x): Same.
* tests/011/mandel.txr (x-centre, y-centre, width, i-max, j-max, n)
(r-max, pixel-size, x-offset, y-offset): Same.
(file, colour-max): Delete (unused) variables.
* tests/012/circ.tl (x): Replace defvar with defvarl.
* tests/012/stack.tl (stack-limited): Same.
* tests/012/struct.tl (s): Same.
* tests/013/maze.tl (vi, pa, sc): Delete variables. Use
function arguments instead.
(usage): Fix typo.
* tests/014/dgram-stream.tl (family): Rename to...
(*family*): ...this.
* tests/014/socket-basic.tl (socktype): Rename to...
(*socktype*): ...this.
(%iters%): Replace defvar with defvarl.
|
|
|
|
|
|
|
|
|
| |
* stdlib/doc-lookup.tl (open-url): On non-Windows platforms,
search for a program specified by the BROWSER variable,
then by the URL-opening utility, and finally thorugh a
fallback list of browsers.
* txr.1: Documentation updated.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
It is common for web browsers like firefox not to fork
themselves into the background when initially run from the
command line. Only when an additional instance is executed
does that instance terminate immediately, passing the URL to
the existing instance. (Which also does not constitute forking
into the background, but does have the effect of an immediate
exit.)
User Paul A. Patience reports that some installations of
xdg-open have the isssue of not handling this situation; these
versions of xdg-open wait for the browser to terminate, which
causes xdg-open to hang until the browser is closed if it is
the initial instance.
* stdlib/doc-lookup.tl (detached-run): New function. Like run,
but forks into the background, running the process in a
detached grandchild whose parent terminates, so that it
becomes an orphan parented to the init daemon. We redirect
*stdout* to *stdnull* because the first instance of the
browser can spit ugly, meaningless diagnostics when it
terminates.
(open-url): Use detached-run instad of run. Don't check the
return value for zero; there is no integer exit status.
|
|
|
|
|
| |
* stdlib/doc-lookup.tl (*doc-url*): Define with defvar,
not defvarl. Problem reported by Paul A. Patience.
|
|
This affects run-time also. Txr installations where the
executable is not in directory ending in ${bindir}
will look for stdlib rather than share/txr/stdlib,
relative to the determined installation directory.
* txr.c (sysroot_init): If we detect relative to the short
name, or fall back on the program directory, use stdlib
rather than share/txr/stdlib as the stdlib_path.
* INSTALL: Update some installation notes not to refer to
share/txr/stdlib but stdlib.
* Makefile (STDLIB_SRCS): Refer to stdlib, not
share/txr/stdlib.
(clean): In unconfigured mode, remove the old share/txr/stdlib
entirely. Remove .tlo files from stdlib.
(install): Install lib materials from stdlib.
* txr.1: Updated documentation under Deployment Directory Structure.
* share/txr/stdlib/{asm,awk,build,cadr}.tl:
Renamed to stdlib/{asm,awk,build,cadr}.tl.
* share/txr/stdlib/{compiler,conv,copy-file,debugger}.tl:
Renamed to stdlib/{compiler,conv,copy-file,debugger}.tl.
* share/txr/stdlib/{defset,doc-lookup,doc-syms,doloop}.tl:
Renamed to stdlib/{defset,doc-lookup,doc-syms,doloop}.tl.
* share/txr/stdlib/{each-prod,error,except,ffi}.tl:
Renamed to stdlib/{each-prod,error,except,ffi}.tl.
* share/txr/stdlib/{getopts,getput,hash,ifa}.tl:
Renamed to stdlib/{getopts,getput,hash,ifa}.tl.
* share/txr/stdlib/{keyparams,match,op,optimize}.tl:
Renamed to stdlib/{keyparams,match,op,optimize}.tl.
* share/txr/stdlib/{package,param,path-test,pic}.tl:
Renamed to stdlib/{package,param,path-test,pic}.tl.
* share/txr/stdlib/{place,pmac,quips,save-exe}.tl:
Renamed to stdlib/{place,pmac,quips,save-exe}.tl.
* share/txr/stdlib/{socket,stream-wrap,struct,tagbody}.tl:
Renamed to stdlib/{socket,stream-wrap,struct,tagbody}.tl.
* share/txr/stdlib/{termios,trace,txr-case,type}.tl:
Renamed to stdlib/{termios,trace,txr-case,type}.tl.
* share/txr/stdlib/{ver,vm-param,with-resources,with-stream}.tl:
Renamed to stdlib/{ver,vm-param,with-resources,with-stream}.tl.
* share/txr/stdlib/yield.tl: Renamed to stdlib/yield.tl.
* share/txr/stdlib/{txr-case,ver}.txr:
Renamed to stdlib/{txr-case,ver}.txr.
* gencadr.txr: Update to stdlib/place.tl.
* genman.txr: Update to stdlib/cadr.tl.
|