*Adr
listen
and accept
.
: *Adr -> "127.0.0.1"
(adr 'var) -> num
(adr 'num) -> var
var
(a symbol or a cons
pair) into num
(actually an encoded pointer). This pointer can be
passed to native
or struct
. The second form converts a pointer
back into the original var
. Note that this original
var
may be garbage collected if it is not referred from other data,
giving unpredictable results. See also byte
.
: (setq X (box 7)) -> $370237372176 : (adr X) -> 533244889064 : (adr @) -> $370237372176 : (val @) -> 7 : (struct (adr X) 'N) -> 114 $: (struct (adr X) T) -> 7
*Allow
NIL
, it should contain a list where the CAR is an idx
tree of allowed items, and the CDR a list of
prefix strings. See also allow
,
allowed
and pre?
.
: (allowed ("app/") # Initialize "!start" "!stop" "lib.css" "!psh" ) -> NIL : (allow "!myFoo") # additional item -> "!myFoo" : (allow "myDir/" T) # additional prefix -> "myDir/" : *Allow -> (("!start" ("!psh" ("!myFoo")) "!stop" NIL "lib.css") "app/" "myDir/") : (idx *Allow) # items -> ("!myFoo" "!psh" "!start" "!stop" "lib.css") : (cdr *Allow) # prefixes -> ("app/" "myDir/")
+Alt
+relation
. This allows indexes or other
side effects to be maintained in a class different from the current one. See
also Database.
(class +EuOrd +Ord) # EU-specific order subclass (rel nr (+Alt +Key +Number) +XyOrd) # Maintain the key in the +XyOrd index
+Any
+relation
. Objects of that class accept
and maintain any type of Lisp data. Used often when there is no other suitable
relation class available. See also Database.
In the following example +Any
is used simply for the reason that
there is no direct way to specify dotted pairs:
(rel loc (+Any)) # Locale, e.g. ("DE" . "de")
+Aux
+relation
s, in addition to +Ref
or +Idx
indexes. Expects a list of auxiliary
attributes of the same object, and combines all keys in that order into a single
index key. See also +UB
, aux
and Database.
(rel nr (+Ref +Number)) # Normal, non-unique index (rel nm (+Aux +Ref +String) (nr txt)) # Combined name/number/text index (rel txt (+Aux +Sn +Idx +String) (nr)) # Text/number plus tolerant text index
(abort 'cnt . prg) -> any
prg
if it takes longer than
cnt
seconds, and returns NIL
. Otherwise, the result of
prg
is returned. alarm
is used internally, so care must be taken not to interfer with other calls to
alarm
.
: (abort 20 (in Sock (rd))) # Wait maximally 20 seconds for socket data
(abs 'num) -> num
num
argument.
: (abs -7) -> 7 : (abs 7) -> 7
(accept 'cnt) -> cnt | NIL
cnt
(as received by port
), and returns the new socket descriptor
cnt
. The global variable *Adr
is set to the IP address
of the client. See also listen
,
connect
and *Adr
.
: (setq *Socket (accept (port 6789)) ) # Accept connection at port 6789 -> 4
(accu 'var 'any 'num)
num
into a sum, using the key any
in
an association list stored in var
. See also assoc
.
: (off Sum) -> NIL : (accu 'Sum 'a 1) -> (a . 1) : (accu 'Sum 'a 5) -> 6 : (accu 'Sum 22 100) -> (22 . 100) : Sum -> ((22 . 100) (a . 6))
(acquire 'sym) -> flg
sym
, by
obtaining an exclusive lock on that file with ctl
, and then trying to write the PID of the
current process into that file. It fails if the file already holds the PID of
some other existing process. See also release
, *Pid
and rc
.
: (acquire "sema1") -> 28255
(alarm 'cnt . prg) -> cnt
prg
to be executed after
cnt
seconds, and returns the number of seconds remaining until any
previously scheduled alarm was due to be delivered. Calling (alarm
0)
will cancel an alarm. See also abort
, sigio
, *Hup
, *Winch
, *Sig[12]
, *TStp[12]
and *Term
.
: (prinl (tim$ (time) T)) (alarm 10 (prinl (tim$ (time) T))) 16:36:14 -> 0 : 16:36:24 : (alarm 10 (bye 0)) -> 0 $
(align 'cnt 'any) -> sym
(align 'lst 'any ..) -> sym
any
arguments pack
ed in an aligned format. In the first form,
any
will be left-aligned if cnt
is negative, otherwise
right-aligned. In the second form, all any
arguments are packed
according to the numbers in lst
. See also tab
, center
and wrap
.
: (align 4 "a") -> " a" : (align -4 12) -> "12 " : (align (4 4 4) "a" 12 "b") -> " a 12 b"
(all ['T | '0 | 'sym]) -> lst
NIL
), all current transient
symbols (if the argument is T
), all external symbols (if the argument is zero), or all
symbols of the given namespace sym
. See also symbols
and all*
.
: (all) # All internal symbols -> (inc> leaf nil inc! accept ... # Find all symbols starting with an underscore character : (filter '((X) (= "_" (car (chop X)))) (all)) -> (_put _nacs _oct _lintq _lst _map _iter _dbg2 _getLine _led ...
(all* 'any ['flg]) -> lst
any
. If flg
is
T
, only symbols, and if it is 0
, only path names are
returned. Typically used in TAB-completion routines. See also all
, symbols
and intern
.
: (all* "map") -> ("map" "map/3" "mapc" "mapcan" "mapcar" "mapcon" "maplist" "maps") : (all* "llvm~BLK") -> ("llvm~BLK" "llvm~BLKMASK" "llvm~BLKSIZE" "llvm~BLKTAG")
(allow 'sym ['flg]) -> sym
*Allow
. If the value of
*Allow
is non-NIL
, sym
is added to the
idx
tree in the CAR of
*Allow
(if flg
is NIL
), or to the list of
prefix strings (if flg
is non-NIL
). See also allowed
.
: *Allow -> (("!start" ("!psh") "!stop" NIL "lib.css") "app/") : (allow "!myFoo") # additionally allowed item -> "!myFoo" : (allow "myDir/" T) # additionally allowed prefix -> "myDir/"
(allowed lst [sym ..])
*Allow
. lst
should
consist of prefix strings (to be checked at runtime with pre?
), and the sym
arguments
should specify the initially allowed items. See also allow
.
: (allowed ("app/") # allowed prefixes "!start" "!stop" "lib.css" "!psh" ) # allowed items -> NIL
(and 'any ..) -> any
any
are evaluated from left to
right. If NIL
is encountered, NIL
is returned
immediately. Else the result of the last expression is returned. See also
nand
, or
and when
.
: (and (= 3 3) (read)) abc # User input -> abc : (and (= 3 4) (read)) -> NIL
(any 'any) -> any
any
from the argument. This is the reverse operation of
sym
. See also str
, (any 'sym)
is equivalent to
(car (str 'sym))
.
: (any "(a b # Comment\nc d)") -> (a b c d) : (any "\"A String\"") -> "A String"
(append 'lst ..) -> lst
conc
, insert
, delete
and remove
.
: (append '(a b c) (1 2 3)) -> (a b c 1 2 3) : (append (1) (2) (3) 4) -> (1 2 3 . 4)
append/3
append
and member/2
.
: (? (append @X @Y (a b c))) @X=NIL @Y=(a b c) @X=(a) @Y=(b c) @X=(a b) @Y=(c) @X=(a b c) @Y=NIL -> NIL
(apply 'fun 'lst ['any ..]) -> any
fun
to lst
. If additional any
arguments are given, they are applied as leading elements of lst
.
(apply 'fun 'lst 'any1 'any2)
is equivalent to (apply 'fun
(cons 'any1 'any2 'lst))
.
: (apply + (1 2 3)) -> 6 : (apply * (5 6) 3 4) -> 360 : (apply '((X Y Z) (* X (+ Y Z))) (3 4 5)) -> 27 : (apply println (3 4) 1 2) 1 2 3 4 -> 4
(arg 'cnt) -> any
@
). Returns the cnt
'th remaining argument. See also
next
, args
, rest
and pass
.
: (de foo @ (println (arg 1) (arg 2)) (println (next)) (println (arg 1) (arg 2)) ) -> foo : (foo 'a 'b 'c) a b a b c -> c
(args) -> flg
@
). Returns T
when there are more arguments to be
fetched from the internal list. See also next
, arg
, rest
and pass
.
: (de foo @ (println (args))) # Test for arguments -> foo : (foo) # No arguments NIL -> NIL : (foo NIL) # One argument T -> T : (foo 123) # One argument T -> T
(argv [var ..] [. sym]) -> lst|sym
argv
returns a list of strings
containing all remaining command line arguments. Otherwise, the
var/sym
arguments are subsequently bound to the command line
arguments. A hyphen "-
" can be used to inhibit the automatic
load
ing further arguments. See also cmd
, Invocation and
opt
.
$ pil -"println 'OK" - abc 123 + OK : (argv) -> ("abc" "123") : (argv A B) -> "123" : A -> "abc" : B -> "123" : (argv . Lst) -> ("abc" "123") : Lst -> ("abc" "123")
(as 'any1 . any2) -> any2 | NIL
any2
unevaluated when any1
evaluates to
non-NIL
. Otherwise NIL
is returned. (as Flg A B
C)
is equivalent to (and Flg '(A B C))
. as
is
typically used in read-macros to conditionally
exclude sub-expressions. See also quote
.
: (as (= 3 3) A B C) -> (A B C) (de foo () (doSomething) ~(as (someConditio) (doThis) (doThat) ) (doMore) )
(asoq 'any 'lst) -> lst
lst
with any
as its CAR, or NIL
if no
match is found. ==
is used for
comparison (pointer equality). See also assoc
, rasoq
, get
, push1q
, delq
, memq
, mmeq
and Comparing.
: (asoq 'a '((999 1 2 3) (b . 7) ("ok" "Hello"))) -> NIL : (asoq 'b '((999 1 2 3) (b . 7) ("ok" "Hello"))) -> (b . 7)
(assert exe ..) -> prg | NIL
*Dbg
is
non-NIL
), assert
returns a prg
list which
tests all exe
conditions, and issues an error via quit
if one of the results evaluates to
NIL
. Otherwise, NIL
is returned. Used typically in
combination with the ~
tilde read-macro
to insert the test code only when
in debug mode. See also test
.
# Start in debug mode $ pil + : (de foo (N) ~(assert (>= 90 N 10)) (bar N) ) -> foo : (pp 'foo) # Pretty-print 'foo' (de foo (N) (unless (>= 90 N 10) # Assertion code exists (quit "'assert' failed" '(>= 90 N 10)) ) (bar N) ) -> foo : (foo 7) # Try it (>= 90 N 10) -- Assertion failed ? # Start in non-debug mode $ pil : (de foo (N) ~(assert (>= 90 N 10)) (bar N) ) -> foo : (pp 'foo) # Pretty-print 'foo' (de foo (N) (bar N) ) # Assertion code does not exist -> foo
(asserta 'lst) -> lst
be
, clause
, assertz
and retract
.
: (be a (2)) # Define two facts -> a : (be a (3)) -> a : (asserta '(a (1))) # Insert new fact in front -> ((1)) : (? (a @N)) # Query @N=1 @N=2 @N=3 -> NIL
asserta/1
asserta
, assertz/1
and retract/1
.
: (? (asserta (a (2)))) -> T : (? (asserta (a (1)))) -> T : (rules 'a) 1 (be a (1)) 2 (be a (2)) -> a
(assertz 'lst) -> lst
be
, clause
, asserta
and retract
.
: (be a (1)) # Define two facts -> a : (be a (2)) -> a : (assertz '(a (3))) # Append new fact at the end -> ((3)) : (? (a @N)) # Query @N=1 @N=2 @N=3 -> NIL
assertz/1
assertz
, asserta/1
and retract/1
.
: (? (assertz (a (1)))) -> T : (? (assertz (a (2)))) -> T : (rules 'a) 1 (be a (1)) 2 (be a (2)) -> a
(assoc 'any 'lst) -> lst
lst
with its CAR equal to any
, or NIL
if
no match is found. See also asoq
and
rassoc
.
: (assoc "b" '((999 1 2 3) ("b" . 7) ("ok" "Hello"))) -> ("b" . 7) : (assoc 999 '((999 1 2 3) ("b" . 7) ("ok" "Hello"))) -> (999 1 2 3) : (assoc 'u '((999 1 2 3) ("b" . 7) ("ok" "Hello"))) -> NIL
(at '(cnt1 . cnt2|NIL) . prg) -> any
cnt1
(destructively), and returns NIL
when it is less than cnt2
. Both cnt1
and
cnt2
should be positive. Otherwise, cnt1
is reset to
zero and prg
is executed. Returns the result of prg
.
If cnt2
is NIL
, nothing is done, and NIL
is returned immediately.
: (do 11 (prin ".") (at (0 . 3) (prin "!"))) ...!...!...!..-> NIL
(atom 'any) -> flg
T
when the argument any
is an atom (a
number or a symbol). See also num?
,
sym?
and pair
.
: (atom 123) -> T : (atom 'a) -> T : (atom NIL) -> T : (atom (123)) -> NIL
(aux 'sym 'cls ['hook] 'any ..) -> sym
cls
, where the value for
sym
corresponds to any
and the following arguments.
sym
, cls
and hook
should specify a
tree
for cls
or one of
its superclasses, for a relation with auxiliary keys. For multi-key accesses,
aux
is similar to - but faster than - db
, because it
can use a single tree access. See also db
, collect
, fetch
, init
, step
and +Aux
.
(class +PS +Entity) (rel par (+Dep +Joint) (sup) ps (+Part)) # Part (rel sup (+Aux +Ref +Link) (par) NIL (+Supp)) # Supplier ... (aux 'sup '+PS # Access PS object (db 'nr '+Supp 1234) (db 'nr '+Part 5678) )