*PPid
- A global constant holding the process-id of the parent picolisp process, or
NIL
if the current process is a top level process.
: (println *PPid *Pid)
NIL 5286
: (unless (fork) (println *PPid *Pid) (bye))
5286 5522
*Pid
- A global constant holding the current process-id.
: *Pid
-> 6386
: (call "ps") # Show processes
PID TTY TIME CMD
.... ... ........ .....
6386 pts/1 00:00:00 pil # <- current process
6388 pts/1 00:00:00 ps
-> T
*Prompt
- Global variable holding a (possibly empty)
prg
body, which is
executed - and the result prin
ted -
every time before a prompt is output to the console in the
"read-eval-print-loop" (REPL).
: (de *Prompt (pack "[" (stamp) "]"))
# *Prompt redefined
-> *Prompt
[2011-10-11 16:50:05]: (+ 1 2 3)
-> 6
[2011-10-11 16:50:11]:
(pack 'any ..) -> sym
- Returns a transient symbol whose name is concatenated from all arguments
any
. A NIL
arguments contributes nothing to the result
string, a number is converted to a digit string, a symbol supplies the
characters of its name, and for a list its elements are taken. See also text
and glue
.
: (pack 'car " is " 1 '(" symbol " name))
-> "car is 1 symbol name"
(pad 'cnt 'any) -> sym
- Returns a transient symbol with
any
pack
ed with leading '0' characters, up to a
field width of cnt
. See also format
and align
.
: (pad 5 1)
-> "00001"
: (pad 5 123456789)
-> "123456789"
(pair 'any) -> any
- Returns
any
when the argument is a cons pair. See also atom
, num?
, sym?
and lst?
.
: (pair NIL)
-> NIL
: (pair (1 . 2))
-> (1 . 2)
: (pair (1 2 3))
-> (1 2 3)
part/3
- Pilog predicate that succeeds if the first
argument, after
fold
ing it to a
canonical form, is a substring of the folded string representation of the
result of applying the get
algorithm to
the following arguments. Typically used as filter predicate in select/3
database queries. See also
sub?
, isa/2
, same/3
, bool/3
, range/3
, head/3
, fold/3
and tolr/3
.
: (?
@Nr (1 . 5)
@Nm "part"
(select (@Item)
((nr +Item @Nr) (nm +Item @Nm))
(range @Nr @Item nr)
(part @Nm @Item nm) ) )
@Nr=(1 . 5) @Nm="part" @Item={B1}
@Nr=(1 . 5) @Nm="part" @Item={B2}
-> NIL
(pass 'fun ['any ..]) -> any
- Passes to
fun
all arguments any
, and all remaining
variable arguments (@
) as they would be returned by rest
. (pass 'fun 'any)
is
equivalent to (apply 'fun (rest) 'any)
. See also apply
.
: (de bar (A B . @)
(println 'bar A B (rest)) )
-> bar
: (de foo (A B . @)
(println 'foo A B)
(pass bar 1)
(pass bar 2) )
-> foo
: (foo 'a 'b 'c 'd 'e 'f)
foo a b
bar 1 c (d e f)
bar 2 c (d e f)
-> (d e f)
(pat? 'any) -> pat | NIL
- Returns
any
when the argument any
is a symbol
whose name starts with an at-mark "@
", otherwise NIL
.
: (pat? '@)
-> @
: (pat? "@Abc")
-> "@Abc"
: (pat? "ABC")
-> NIL
: (pat? 123)
-> NIL
(patch 'lst 'any . prg) -> any
- Destructively replaces all sub-expressions of
lst
, that
match
the pattern any
,
by the result of the execution of prg
. See also daemon
and redef
.
: (pp 'hello)
(de hello NIL
(prinl "Hello world!") )
-> hello
: (patch hello 'prinl 'println)
-> NIL
: (pp 'hello)
(de hello NIL
(println "Hello world!") )
-> hello
: (patch hello '(prinl @S) (fill '(println "We said: " . @S)))
-> NIL
: (hello)
We said: Hello world!
-> "Hello world!"
(path 'any) -> sym
- Substitutes any leading "
@
" or "~
" character in
the any
argument with the PicoLisp or User Home
Directory respectively, as they were remembered during interpreter startup.
Optionally, the name may be preceded by a "+
" character (as used by
in
and out
). This mechanism is used internally by all
I/O functions. See also Invocation, basename
and dirname
.
$ /usr/bin/picolisp /usr/lib/picolisp/lib.l
: (path "a/b/c")
-> "a/b/c"
: (path "@a/b/c")
-> "/usr/lib/picolisp/a/b/c"
: (path "+@a/b/c")
-> "+/usr/lib/picolisp/a/b/c"
(peek) -> sym
- Single character look-ahead: Returns the same character as the next call to
char
would return. Note that the
look-ahead covers only the next byte, so a multi-byte character might
still block. See also skip
.
$ cat a
# Comment
abcd
$ pil +
: (in "a" (list (peek) (char)))
-> ("#" "#")
permute/2
- Pilog predicate that succeeds if the second
argument is a permutation of the list in the second argument. See also
append/3
.
: (? (permute (a b c) @X))
@X=(a b c)
@X=(a c b)
@X=(b a c)
@X=(b c a)
@X=(c a b)
@X=(c b a)
-> NIL
(pick 'fun 'lst ..) -> any
- Applies
fun
to successive elements of lst
until
non-NIL
is returned. Returns that value, or NIL
if
fun
did not return non-NIL
for any element of
lst
. When additional lst
arguments are given, their
elements are also passed to fun
. (pick 'fun 'lst)
is
equivalent to (fun (find 'fun 'lst))
. See also seek
, find
and extract
.
: (setq A NIL B 1 C NIL D 2 E NIL F 3)
-> 3
: (find val '(A B C D E))
-> B
: (pick val '(A B C D E))
-> 1
pico
- A global constant holding the initial (default) namespace of internal
symbols. Its value is two cons pairs of the symbol
~
(as a marker)
and two 'idx
' trees, one for symbols
with short names and one for symbols with long names (more than 7 bytes in the
name). See also symbols
, nsp
, import
and intern
.
: (symbols)
-> (pico)
: (cdr pico)
-> (rollback (*NoTrace (*CtryCode (+IdxFold) genStrKey) basename ...
(pilog 'lst . prg) -> any
- Evaluates a Pilog query, and executes
prg
for each result set with all Pilog variables bound to their
matching values. See also solve
,
?
, goal
and prove
.
: (pilog '((append @X @Y (a b c))) (println @X '- @Y))
NIL - (a b c)
(a) - (b c)
(a b) - (c)
(a b c) - NIL
-> NIL
(pipe exe) -> cnt
(pipe exe . prg) -> any
- Executes
exe
in a fork
'ed child process (which terminates
thereafter). In the first form, pipe
just returns a file descriptor
to write to the standard input and read from the standard output of that
process. In the second form, it opens the standard output of that process as
input channel during the execution of prg
. The current input
channel will be saved and restored appropriately, and the (system dependent)
exit status code of the child process is stored in the global variable @@
. See also later
, ipid
, in
and out
.
: (pipe # equivalent to 'any'
(prinl "(a b # Comment\nc d)") # Child
(read) ) # Parent
-> (a b c d)
: (pipe # pipe through an external program
(out '(tr "[a-z]" "[A-Z]") # Child
(prinl "abc def ghi") )
(line T) ) # Parent
-> "ABC DEF GHI"
: (setq P
(pipe
(in NIL # Child: Read stdin
(while (line T)
(prinl (uppc @)) # and write to stdout
(flush) ) ) ) )
-> 3
: (out P (prinl "abc def")) # Parent: Send line to child
-> "abc def"
: (in P (line)) # Parent: Read reply
-> ("A" "B" "C" " " "D" "E" "F")
(place 'cnt 'lst 'any) -> lst
- Places
any
into lst
at position cnt
.
This is a non-destructive operation. See also insert
, remove
, append
, delete
and replace
.
: (place 3 '(a b c d e) 777)
-> (a b 777 d e)
: (place 1 '(a b c d e) 777)
-> (777 b c d e)
: (place 9 '(a b c d e) 777)
-> (a b c d e 777)
(plio 'num) -> any
(plio 'num 'cnt 'any) -> cnt
- The first form returns one item stored in PLIO format at the memory location
pointed to by
num
. The second form stores an item any
in a buffer of size cnt
. See also byte
and struct
.
: (buf P 64
(plio P 64 (1 a (2 b c) d)) # Store expression
(plio P) ) # Fetch it
-> (1 a (2 b c) d)
(poll 'cnt) -> cnt | NIL
- Checks for the availability of data for reading on the file descriptor
cnt
. See also open
,
in
and close
.
: (and (poll *Fd) (in @ (read))) # Prevent blocking
(pool ['sym1 ['lst] ['sym2] ['sym3]]) -> T
- Opens the file
sym1
as a database file in read/write mode. If
the file does not exist, it is created. A currently open database is closed.
lst
is a list of block size scale factors (i.e. numbers),
defaulting to (2) (for a single file with a 256 byte block size). If
lst
is given, an individual database file is opened for each item.
If sym2
is non-NIL
, it is opened in append-mode as an
asynchronous replication journal. If sym3
is non-NIL
,
it is opened for reading and appending, to be used as a synchronous transaction
log during commit
s. Calling
(pool)
without arguments just closes the current database. See also
dbs
, *Dbs
and journal
.
: *Dbs
-> (1 2 2 4)
: (pool "dbFile" *Dbs)
-> T
$ ls -l dbFile*
-rw-r--r-- 1 abu abu 256 Jul 3 08:30 dbFile@
-rw-r--r-- 1 abu abu 256 Jul 3 08:30 dbFileA
-rw-r--r-- 1 abu abu 256 Jul 3 08:30 dbFileB
-rw-r--r-- 1 abu abu 1024 Jul 3 08:30 dbFileC
# DB directly on a device
: (pool "/dev/hda2")
-> T
(pool2 'sym . prg)
-> any
- Temporary switches to another database specified by
sym
. This
database must be a multi-file DB with exactly the same *Dbs
structure as the currently open one. The
current database is not closed - I/O is just redirected to the new one. All
files are opened before prg
runs, and are closed thereafter. The
result of prg
is returned. No replication journal or transaction
log is written. Also, possibly cached objects of the current DB remain in the
heap, so an explicit call to rollback
may be necessary. See also
blk
.
(pool2 "db2/" # Update a read-only DB
(journal "file.jnl") )
(rollback)
(pool2 "db2/" # Access object(s)
(show *DB) )
(rollback)
(pop 'var) -> any
- Pops the first element (CAR) from the stack in
var
. See also
push
, ++
, shift
, queue
, cut
, del
and fifo
.
: (setq S '((a b c) (1 2 3)))
-> ((a b c) (1 2 3))
: (pop S)
-> a
: (pop (cdr S))
-> 1
: (pop 'S)
-> (b c)
: S
-> ((2 3))
(port ['T] 'cnt|(cnt . cnt) ['var]) -> cnt
- Opens a TCP-Port
cnt
(or a UDP-Port if the first argument is
T
), and returns a socket descriptor suitable as an argument for
listen
or accept
(or udp
, respectively). If cnt
is zero,
some free port number is allocated. If a pair of cnt
s is given
instead, it should be a range of numbers which are tried in turn. When
var
is given, it is bound to the port number.
: (port 0 'A) # Allocate free port
-> 4
: A
-> 1034 # Got 1034
: (port (4000 . 4008) 'A) # Try one of these ports
-> 5
: A
-> 4002
(pp 'sym) -> sym
(pp 'sym 'cls) -> sym
(pp '(sym . cls)) -> sym
- Pretty-prints the function or method definition of
sym
. The
output format would regenerate that same definition when read and executed. See
also pretty
, debug
and vi
.
: (pp 'tab)
(de tab (Lst . @)
(for N Lst
(let V (next)
(and (gt0 N) (space (- N (length V))))
(prin V)
(and
(lt0 N)
(space (- 0 N (length V))) ) ) )
(prinl) )
-> tab
: (pp 'has> '+Entity)
(dm has> (Var Val)
(or
(nor Val (get This Var))
(has> (meta This Var) Val (get This Var)) ) )
-> has>
: (more (can 'has>) pp)
(dm (has> . +relation) (Val X)
(and (= Val X) X) )
(dm (has> . +Fold) (Val X)
(extra
Val
(if (= Val (fold Val)) (fold X) X) ) )
(dm (has> . +Entity) (Var Val)
(or
(nor Val (get This Var))
(has> (meta This Var) Val (get This Var)) ) )
(dm (has> . +List) (Val X)
(and
Val
(or
(extra Val X)
(find '((X) (extra Val X)) X) ) ) )
(dm (has> . +Bag) (Val X)
(and
Val
(or (super Val X) (car (member Val X))) ) )
(pr 'any ..) -> any
- Binary print: Prints all
any
arguments to the current output
channel in encoded binary format. See also rd
, bytes
, tell
, hear
and wr
.
: (out "x" (pr 7 "abc" (1 2 3) 'a)) # Print to "x"
-> a
: (hd "x")
00000000 04 0E 0E 61 62 63 01 04 02 04 04 04 06 03 05 61 ...abc.........a
-> NIL
(prBase64 'cnt ['str]) -> NIL
- Multiline base64 printing. Echoes bytes from the current input channel to
the current output channel in Base64 format. A newline is inserted after every
cnt
byte-triples (character-quadruples). If str
is
given (typically a carriage return), it is output before the newline. See also
echo
mail
.
: (in "image.png" (prBase64 18)) # Print 72 columns
(prEval 'prg ['cnt]) -> any
- Executes
prg
, similar to run
, by evaluating all expressions in
prg
(within the binding environment given by cnt-1
).
As a side effect, all atomic expressions will be printed with prinl
. See also eval
.
: (let Prg 567
(prEval
'("abc" (prinl (+ 1 2 3)) Prg 987) ) )
abc
6
567
987
-> 987
(pre? 'any1 'any2) -> any2 | NIL
- Returns
any2
when the string representation of
any1
is a prefix of the string representation of any2
.
See also sub?
and head
.
: (pre? "abc" "abcdefg")
-> "abcdef"
: (pre? "def" "abcdefg")
-> NIL
: (pre? (+ 3 4) "7fach")
-> "7fach"
: (pre? NIL "abcdefg")
-> "abcdefg"
: (pre? "abc" '(a b c d e f g))
-> "abcdefg"
: (pre? '(a b c) "abcdefg")
-> "abcdefg"
(pretty 'any 'cnt)
- Pretty-prints
any
. If any
is an atom, or a list
with a size
not greater than 12, it is
print
ed as is. Otherwise, only the
opening parenthesis and the CAR of the list is printed, all other elements are
pretty-printed recursively indented by three spaces, followed by a space and the
corresponding closing parenthesis. The initial indentation level
cnt
defaults to zero. See also pp
.
: (pretty '(a (b c d) (e (f (g) (h) (i)) (j (k) (l) (m))) (n o p) q))
(a
(b c d)
(e
(f (g) (h) (i))
(j (k) (l) (m)) )
(n o p)
q )-> ")"
(prin 'any ..) -> any
- Prints the string representation of all
any
arguments to the
current output channel. No space or newline is printed between individual items,
or after the last item. For lists, all elements are prin
'ted
recursively. See also prinl
.
: (prin 'abc 123 '(a 1 b 2))
abc123a1b2-> (a 1 b 2)
(prinl 'any ..) -> any
- Prints the string representation of all
any
arguments to the
current output channel, followed by a newline. No space or newline is printed
between individual items. For lists, all elements are prin
'ted
recursively. See also prin
.
: (prinl 'abc 123 '(a 1 b 2))
abc123a1b2
-> (a 1 b 2)
(print 'any ..) -> any
- Prints all
any
arguments to the current output channel. If
there is more than one argument, a space is printed between successive
arguments. No space or newline is printed after the last item. See also println
, printsp
, sym
and str
: (print 123)
123-> 123
: (print 1 2 3)
1 2 3-> 3
: (print '(a b c) 'def)
(a b c) def-> def
(println 'any ..) -> any
- Prints all
any
arguments to the current output channel,
followed by a newline. If there is more than one argument, a space is printed
between successive arguments. See also print
, printsp
.
: (println '(a b c) 'def)
(a b c) def
-> def
(printsp 'any ..) -> any
- Prints all
any
arguments to the current output channel,
followed by a space. If there is more than one argument, a space is printed
between successive arguments. See also print
, println
.
: (printsp '(a b c) 'def)
(a b c) def -> def
(prior 'lst1 'lst2) -> lst | NIL
- Returns the cell in
lst2
which immediately precedes the cell
lst1
, or NIL
if lst1
is not found in
lst2
or is the very first cell. ==
is used for comparison (pointer equality). See
also offset
and memq
.
: (setq L (1 2 3 4 5 6))
-> (1 2 3 4 5 6)
: (setq X (cdddr L))
-> (4 5 6)
: (prior X L)
-> (3 4 5 6)
(private) sym|lst
- Intern symbols locally into an internal special namespace named
'
priv
'. This namespace is always searched first, but never gets new
symbols automatically interned. (private)
expects a single symbol
or a list of symbols immediately following in the current input stream. See also
pico
, symbols
, local
, export
, import
and intern
.
: (symbols 'myLib 'pico)
-> (pico)
myLib: (symbols)
-> (myLib pico)
myLib: (private) (foo bar) # Intern 'foo' and 'bar' in 'priv'
myLib: (symbols)
-> (myLib pico)
myLib: (all 'priv)
-> (priv~foo priv~bar)
(proc 'sym ..) -> T
- (Debug mode on Linux only) Shows a list of processes with command names
given by the
sym
arguments, using the system ps
utility. See also kids
, kill
and hd
.
: (proc 'pil)
PID PPID STARTED SIZE %CPU WCHAN CMD
16993 3267 12:38:21 1516 0.5 - /usr/bin/picolisp /usr/lib/picolisp/lib.l /usr/bin/pil +
15731 1834 12:36:35 2544 0.1 - /usr/bin/picolisp /usr/lib/picolisp/lib.l /usr/bin/pil app/main.l -main -go +
15823 15731 12:36:44 2548 0.0 - /usr/bin/picolisp /usr/lib/picolisp/lib.l /usr/bin/pil app/main.l -main -go +
-> T
(prog . prg) -> any
- Executes
prg
, and returns the result of the last expression.
See also nil
, t
, prog1
and prog2
.
: (prog (print 1) (print 2) (print 3))
123-> 3
(prog1 'any1 . prg) -> any1
- Executes all arguments, and returns the result of the first expression
any1
. See also nil
,
t
, prog
and prog2
.
: (prog1 (print 1) (print 2) (print 3))
123-> 1
(prog2 'any1 'any2 . prg) -> any2
- Executes all arguments, and returns the result of the second expression
any2
. See also nil
,
t
, prog
and prog1
.
: (prog2 (print 1) (print 2) (print 3))
123-> 2
(prompt 'any . prg) -> any
- Sets the prompt for non-REPL
readline(3)
calls to
any
during the execution of prg. See also tty
.
: (prompt "== " (line))
== abc
-> ("a" "b" "c")
(prop 'sym1|lst ['sym2|cnt ..] 'sym) -> var
- Fetches a property for a property key
sym
from a symbol. That
symbol is sym1
(if no other arguments are given), or a symbol found
by applying the get
algorithm to
sym1|lst
and the following arguments. The property (the cons pair,
not just its value) is returned, suitable for direct (destructive) manipulations
with functions expecting a var
argument. See also ::
.
: (put 'X 'cnt 0)
-> 0
: (prop 'X 'cnt)
-> (0 . cnt)
: (inc (prop 'X 'cnt)) # Directly manipulate the property value
-> 1
: (get 'X 'cnt)
-> 1
(protect . prg) -> any
- Executes
prg
, and returns the result of the last expression. If
a signal is received during that time, its handling will be delayed until the
execution of prg
is completed. See also alarm
, *Hup, *Sig[12] and kill
.
: (protect (journal "db1.log" "db2.log"))
-> T
(prove 'lst ['lst]) -> lst
- The Pilog interpreter. Tries to prove the query
list in the first argument, and returns an association list of symbol-value
pairs, or
NIL
if not successful. The query list is modified as a
side effect, allowing subsequent calls to prove
for further
results. The optional second argument may contain a list of symbols; in that
case the successful matches of rules defined for these symbols will be traced.
See also goal
, ->
and unify
.
: (prove (goal '((equal 3 3))))
-> T
: (prove (goal '((equal 3 @X))))
-> ((@X . 3))
: (prove (goal '((equal 3 4))))
-> NIL
(prune ['cnt])
- Optimizes memory usage by pruning in-memory nodes of database trees.
Typically called repeatedly during bulk data imports. If
cnt
is
0
, the pruning process is initialized, and if it is
NIL
, further pruning will be disabled. Otherwise, all nodes which
have not been accessed (with fetch
or
store
) for cnt
calls to
prune
will be wipe
d. See
also lieu
.
(in File1
(prune 0)
(while (someData)
(new T '(+Cls1) ..)
(at (0 . 10000) (commit) (prune 100)) ) )
(in File2
(prune 0)
(while (moreData)
(new T '(+Cls2) ..)
(at (0 . 10000) (commit) (prune 100)) ) )
(commit)
(prune)
(push 'var 'any ..) -> any
- Implements a stack using a list in
var
. The any
arguments are cons'ed in front of the value list. See also push1
, push1q
, pop
, shift
, queue
and fifo
.
: (push 'S 3) # Use the VAL of 'S' as a stack
-> 3
: S
-> (3)
: (push 'S 2)
-> 2
: (push 'S 1)
-> 1
: S
-> (1 2 3)
: (push S 999) # Now use the CAR of the list in 'S'
-> 999
: (push S 888 777)
-> 777
: S
-> ((777 888 999 . 1) 2 3)
(push1 'var 'any ..) -> any
- Maintains a unique list in
var
. Each any
argument
is cons'ed in front of the value list only if it is not already a member
of that list. See also push
, push1q
, pop
and queue
.
: (push1 'S 1 2 3)
-> 3
: S
-> (3 2 1)
: (push1 'S 2 4)
-> 4
: S
-> (4 3 2 1)
(push1q 'var 'any ..) -> any
- Maintains a unique list in
var
. Each any
argument
is cons'ed in front of the value list only if it is not already memq
of that list (pointer equality). See also
push
, push1
, pop
and queue
.
: (push1q 'S 'a (1) 'b (2) 'c)
-> c
: S
-> (c (2) b (1) a)
: (push1q 'S 'b (1) 'd) # (1) is not pointer equal to the previous one
-> d
: S
-> (d (1) c (2) b (1) a) # (1) is twice in the list
(put 'sym1|lst ['sym2|cnt ..] 'any) -> any
- Stores a new value
any
for a property key (or in the symbol
value for zero) in a symbol, or in a list. That symbol is sym1
(if
no other arguments are given), or a symbol found by applying the get
algorithm to sym1|lst
and the
following arguments. If the final destination is a list, the value is stored in
the CDR of an asoq
ed element (if the
key argument is a symbol), or the n'th element (if the key is a number). See
also =:
.
: (put 'X 'a 1)
-> 1
: (get 'X 'a)
-> 1
: (prop 'X 'a)
-> (1 . a)
: (setq L '(A B C))
-> (A B C)
: (setq B 'D)
-> D
: (put L 2 0 'p 5) # Store '5' under the 'p' property of the value of 'B'
-> 5
: (getl 'D)
-> ((5 . p))
(put! 'obj 'sym 'any) -> any
- Transaction wrapper function for
put
. Note that for setting property values of
entities typically the put!>
message is used. See also
new!
, request!
, set!
and inc!
.
(put! Obj 'cnt 0) # Setting a property of a non-entity object
(putl 'sym1|lst1 ['sym2|cnt ..] 'lst) -> lst
- Stores a complete new property list
lst
in a symbol. That
symbol is sym1
(if no other arguments are given), or a symbol found
by applying the get
algorithm to
sym1|lst1
and the following arguments. All previously defined
properties for that symbol are lost. See also getl
and maps
.
: (putl 'X '((123 . a) flg ("Hello" . b)))
-> ((123 . a) flg ("Hello" . b))
: (get 'X 'a)
-> 123
: (get 'X 'b)
-> "Hello"
: (get 'X 'flg)
-> T
(pwd) -> sym
- Returns the path to the current working directory. See also
dir
and cd
.
: (pwd)
-> "/home/app"