ac.scm
. On top of this the core of the language is implemented
in the Arc language itself in arc.arc
. Finally, various libraries
are implemented on top of the core. This page provides some documentation
of the functionality in the foundation.
In one sense, the foundation can be considered the "axioms", and the full language is created out of these axioms. However, in my view, the current foundation both contains too much and too little to be considered an axiomatic base. For example, it contains enough networking functionality to implement a web server, but not enough to fetch a web page. The math functions include square root and exponentiation, but not trigonometry. Nonetheless, the foundation provides the basis for a very interesting language. For more information on how the foundation is implemented, see my article Arc Internals.
Arc was used to generate this document. I created a large Arc data structure holding the functions, arguments, description, headings, and test examples. I wrote a program in Arc that processes this data structure to generate the HTML file for this page. The functions are linked to the Arc Cross Reference website. The examples on the right, for the most part, show actual output from running the embedded code while generating the page. This ensures that the examples show actual behavior of the arc2 release. (A few commands, such as quit and the socket operations, are not suitable for execution in this way and their output was "faked".)
The documentation below is based on my exploration of the language. Undoubtedly this document contains many errors. In addition, the language is undergoing active modification. This documentation is based on the "arc1" release.
numbers
Arc includes integers (fixed size and arbitrarily large),
floats, fractions, and complex numbers. It also has positive and negative infinities
and "Not a Number". Arc supports escapes for hex, decimal, octal, or
binary numbers: #x, #d, #o, and #b. Numbers are of type 'int or 'num.
|
>42 42 >5.0 5.0 >2.0-3.0i 2.0-3.0i >+inf.0 +inf.0 >(+ #x10 #d10 #o10 #b10) 36 >1/2+3/4i 1/2+3/4i >1e3 1000.0 >1/2e3 500.0 >(type 5.0) int >(type 1+2i) num |
characters
Arc supports Unicode characters, and a variety of
escapes.
|
>(prn #\a #\102 #\newline #\null #\u5a #\u4e9c #\U12031 #\日) aB Z亜𒀱日 #\a >(type #\a) char |
strings
Arc supports Unicode strings, and a variety of escapes. The
escape sequences are not the same as the character escape sequences.
|
>(prn "a \102 \n \x00 \x5a \U4e9c 日") a B Z 亜 日 "a B \n \u0000 Z 亜 日" >(type "a") string |
symbols
By quoting a symbol, it will not be evaluated.
|
>'a a >'b b >(type 'c) sym |
lists
Lists are built up of cons cells. They are terminated with nil,
in contrast to Scheme, where they are terminated with '().
|
>'(1 2 3) (1 2 3) >(type '(1)) cons |
procedures
Procedures are created by fn or def.
|
>(fn (x) (+ x 1)) #<procedure> >(def foo (x) (+ x 1)) #<procedure: foo> >(type (fn (x) (+ x 1))) fn |
macros
Macros are created by mac.
|
>(mac bar (x) `(+ ,x 1)) #3(tagged mac #<procedure>) >(type (mac baz (x) `(+ ,x 1))) mac |
tagged
Arc supports arbitrary tagged types.
|
>(annotate 'mytype 'x) #3(tagged mytype x) >(type (annotate 'mytype 'x)) mytype |
table
Arc supports hash tables. Tables can be used as
functions; they look up the key.
|
>(table) #hash() >(let x (table) (= (x 'key) 'value) (x 'key)) value >(type (table)) table |
input
Input ports can be from files, sockets, or strings.
|
>(type (stdin)) input |
output
Output ports can be from files, sockets, or strings.
|
>(type (outfile "/tmp/junk")) output |
exception
A thread can throw an exception if an error occurs, or
generate an exception with err.
|
>(on-err (fn (ex) (prn ex) (prn (details ex)) (type ex)) (fn () (car 1))) #<struct:exn:fail> Can't take car of 1 exception |
socket
A TCP socket is created with open-socket. Arc's socket
support is limited to incoming TCP connections.
|
>(type (open-socket 8080)) Error: tcp-listen: listen on 8080 failed (Address already in use; errno=98) |
threads
Threads are created with new-thread.
|
>(type (new-thread (fn x))) thread |
nil
nil represents false. it is equivalent to '()
|
>(is nil '()) t >(type nil) sym |
t
t represents true. Any non-nil value will evaluate as true in a
conditional, including 0 and the empty string.
|
>(no t) nil >(type t) sym |
coerce obj type [args]
Coerces object to a new type. A char can be
coerced to int, string, or sym. A number can be coerced to int, char, or string
(of specified base). A string can be coerced to sym, cons (char list), or int (of
specified base). A list of characters can be coerced to a string. A symbol
can be coerced to a string.
|
>(coerce "a" 'sym) a >(coerce 65 'char) #\A >(coerce 65 'int 2) 65 >(coerce "abc" 'cons) (#\a #\b #\c) |
type object
Returns the type of an object (as a symbol).
Possibilities are cons, sym, fn, char, string, int, num, table, output,
input, socket, exception, or mac.
|
>(type 1) int >(type car) fn |
fn args [body ...]
fn is used to create lambda functions. The args can be a variable (which
will pick up all the arguments as a list), a list of variables, or a dotted list of
variables (the last will pick up the remainder as a list ).
|
>((fn (x y) (+ x y)) 1 2) 3 >((fn all (len all)) 1 2 3) 3 >((fn (arg1 arg2 . rest) rest) 1 2 3 4) (3 4) |
if [test expr] ... [else-expr]
Arc is the basic conditional operation.
It takes a sequence of tests and expressions. The expression corresponding
to the first true test is returned. Other expressions are not evaluated.
|
>(if nil "Nil is true" 0 "0 is true" "What is true?") "0 is true" |
quasiquote arg
The backquote ` is shorthand for quasiquote, e.g. `(+
1 2) is the same as (quasiquote (1 2)). Inside quasiquote, the unquote
operator will cause the contents to be evaluated instead of quoated. The
unquote-splicing operator will cause contents to be evaluated and spliced
into the result. , is shorthand for unquote, and ,@ is shorthand for
unquote-splicing.
|
>`((+ 1 2) ,(+ 3 4) ,@(list 5 6)) ((+ 1 2) 7 5 6) |
quote arg
The single quote ' is shorthand for quote, e.g. 'x is the same as (quote x)
|
>'(1 2 3) (1 2 3) |
set variable val
set is used to set a variable to a value.
|
>(set x 10) 10 |
< arg arg [...]
Less than comparison. Applies to numbers, strings, symbols, or
chars. If multiple arguments are given, the sequence must be monotonically
increasing.
|
>(< 1 2) t >(< 1 2 3) t >(< 1 3 2) nil >(< "a" "b") t >(< 'a 'b) t >(< #\a #\b) t |
> arg arg [...]
Greater than comparison. Applies to numbers, strings, symbols, or
chars. If multiple arguments are given, the sequence must be monotonically
decreasing.
|
>(> 1 2) nil >(> 3 1 2) nil >(> "a" "b") nil >(> 'a 'b) nil >(> #\a #\b) nil |
bound symbol
Tests is a symbol is bound.
|
>(bound 'foobar) nil >(do (set y 1) (bound 'y)) t |
exact value
Tests if the value is an exact integer.
|
>(exact 3) t >(exact 3.14) nil |
is val [val ...]
Tests equality with eqv?
|
>(is 1 2) nil >(is "a" "a") t >(is '(1) '(1)) nil >(is 1 1 1 1) t >(is nil '()) t |
car list
First element of list
|
>(car '(1 2 3)) 1 |
cdr list
Remainder of list.
|
>(cdr '(1 2 3)) (2 3) |
cons element list
Prepends element to list.
|
>(cons 1 '(2 3)) (1 2 3) |
newstring length [char]
Creates a string of the given length.
|
>(newstring 5 #\a) "aaaaa" |
scar list value
Sets car of list to new value. If applied to a
string, sets the first character of the string, which must have length at
least one.
|
>(do (= x "abc") (scar x #\d) x) "dbc" >(do (= x '(1 2 3)) (scar x #\d) x) (#\d 2 3) |
scdr list value
Sets cdr of a list.
|
>(do (= x '(1 2 3)) (scdr x '(4)) x) (1 4) |
sref object value index
Sets indexed entry in a list, string, or hash table to
the given value.
|
>(do (= x "abc") (sref x #\d 1) x) "adc" >(do (= x '(1 2 3)) (sref x #\d 1) x) (1 #\d 3) |
len obj
Computes the length of a list, string, or hash table.
|
>(len "abc") 3 >(len '(1 2 3)) 3 |
* args
Multiplication.
|
>(* 2 3) 6 |
+ args
Addition. This operator also performs string and list
concatenation.
|
>(+ 1 2 3) 6 >(+ "ab" "c" "de") "abcde" >(+ '(1 2) '(3 4) '(5)) (1 2 3 4 5) |
- args
Subtraction.
|
>(- 3 2) 1 |
/ args
Division
|
>(/ 1 2) 1/2 >(/ 1.0 2) 0.5 |
expt base exponent
Exponentiation.
|
>(expt 2 3) 8 |
mod dividend divisor
|
>(mod 10 3) 1 >(mod -10 3) 2 |
rand [max]
Returns a random number between 0 and 1, or between 0 and
the specified integer (excluding the integer).
|
>(rand 10) 5 >(rand) 0.4255004866291074 |
sqrt number
Square root operation
|
>(sqrt 2) 1.4142135623730951 >(sqrt -1) 0+1i |
trunc number
Truncates to an integer. Was 'truncate' in arc0.
|
>(trunc 1.9) 1 >(trunc -1.1) -1 |
maptable proc table
Applies proc to each element of the table.
|
>(let x (table) (sref x 9 3) (sref x 16 4) (maptable (fn (key val) (prn key " " val)) x)) 4 16 3 9 #hash((3 . 9) (4 . 16)) |
table
Creates a hash table.
|
>(table) #hash() |
eval expression
Evaluates the expression.
|
>(eval '(+ 1 2)) 3 |
apply fn arglist
Applies the function to the arguments.
|
>(apply + '(1 2)) 3 |
ssexpand symbol
Expands special syntax (: ! . or ~). The :
character indicates composition. The ~ indicates complementing. The .
applies the first value to the remainder. The ! is like . except the
arguments are quoted.
|
>(ssexpand 'x:~y:z) (compose x (complement y) z) >(ssexpand '+.1.2) (+ 1 2) >(ssexpand '+!1!2) (+ (quote 1) (quote 2)) >(ssexpand 'cons!a!b) (cons (quote a) (quote b)) |
ssyntax symbol
Tests if the symbol contains special syntax (: ! . or ~).
|
>(ssyntax 'x:y) t |
annotate type obj
Tags the object with the given type. Only used for
macros.
|
>(type (annotate 'mac car)) mac |
macex macro
Expands a macro.
|
>(macex '(let a 1 (pr a))) ((fn (a) (pr a)) 1) |
macex1 macro
Expands a macro to one level.
|
>(macex1 '(let a 1 (pr a))) (with (a 1) (pr a)) |
rep obj
Returns the underlying object for an annotated object
|
>(rep whilet) #<procedure> |
sig
Hash table containing function signatures.
|
>(sig 'map) (f . seqs) |
uniq
Generates a unique symbol.
|
>(uniq) gs2503 |
call-w/stdin input-port thunk
Calls thunk, setting current-input-port
to the specified port.
|
>(call-w/stdin (instring "Hello") readline) "Hello" |
call-w/stdout output-port thunk
Calls thunk, setting current-input-port
to the specified port.
|
>(let sop (outstring) (call-w/stdout sop (fn () (prn '(1 2)))) (inside sop)) "(1 2)\n" |
close port [...]
Closes a port. In arc0, close took a single argument
only.
|
>(close (outfile "/tmp/junk")) nil |
disp [arg [output-port]]
Displays the argument on the output-port (or
current-output-port) using Scheme's display procedure.
|
>(disp '(1 2)) (1 2) nil >(disp "abc") abc nil |
peekc input-port
Peeks at the next character from the input port, but
leaves the character for future reads. It
uses current-input-port if the argument is nil. It returns the character, or nil for
end-of-file.
|
>(peekc (pipe-from "echo hello")) #\h |
pipe-from command
Executes command in the underlying OS. Then opens
an input-port to the results.
|
>(readline (pipe-from "echo hello")) "hello" |
readb [input-port]
Reads a byte from the input-port (or default of
current-input-port). Returns nil on end-of-file.
|
>(readb (pipe-from "echo hello")) 104 |
readc [input-port]
Reads a character from the input-port (or default of
current-input-port). Returns nil on end-of-file.
|
>(readc (pipe-from "echo ©")) #\© |
sread input-port eof-value
Reads a Scheme object from the input port. Returns eof-value
on end-of-file.
|
>(sread (pipe-from "echo '(1 2) (3)'") "junk") (1 2) |
stderr
current-error-port: returns the output-port stderr
|
>(stderr) #<output-port:stderr> |
stdin
current-input-port: returns the input-port stdin
|
>(stdin) #<input-port:stdin> |
stdout
current-output-port: returns the output-port stdout
|
>(stdout) #<output-port:string> |
write [arg [output-port]]
Writes the argument to the output-port (or
current-output-port). The write and disp procedures are subtly different.
The output from write is more 'raw' than the output from disp; see the
MzScheme
Default
Printer documentation for details.
|
>(write "abc") "abc" nil |
writeb int [output-port]
Writes the byte to the output-port (or
default of current-output-port).
|
>(writeb 65) A 65 |
writec char [output-port]
Writes the character to the output-port (or
default of current-output-port).
|
>(writec #\日) 日 #\日 |
inside string-output-port
Returns (as a string) the bytes accumulated
in a string-output-port generated by outstring. This is MzScheme's get-output-string.
|
>(let sop (outstring) (write "hello" sop) (inside sop)) "\"hello\"" |
instring string [name]
Creates an input port to read UTF-8 bytes from the
string. This is MzScheme's open-input-string.
|
>(readline (instring "hello")) "hello" |
outstring [name]
Creates an output-port that accumulates the output
into a byte string. The string can be retrieved with inside. This is
MzScheme's open-output-string.
|
>(outstring) #<output-port:string> |
client-ip tcp-output-port
Returns the IP address of the client
connected to a TCP port. The tcp-output-argument is the second value
returned from socket-accept. The address is returned as a string, the same as
the third result from socket-accept.
|
>(let s (socket-accept (open-socket 8080)) (client-ip (s 1))) "10.2.40.71" |
open-socket port
Opens a tcp-listener on the given port.
|
>(open-socket 8000) Error: tcp-listen: listen on 8000 failed (Address already in use; errno=98) |
socket-accept tcp-port
Accepts a connection on the given tcp-listener.
The thread blocks until a connection is received. It returns a list of
(input-port output-port client-ip-string)
|
>(socket-accept (open-socket 8080)) (#<input-port> #<output-port> "10.2.40.71") |
dir path
Returns the directory contents as a list.
|
>(dir "mydir") ("foo") |
dir-exists path
Tests if a directory exists.
|
>(dir-exists "mydir") "mydir" |
file-exists path
Tests if a file exists.
|
>(file-exists "mydir") nil |
infile filename ['binary | 'text]
Opens the specified path for
reading. By default, the file is opened in binary mode, and bytes are
returned as read from the file. In text mode, return and linefeed bytes are
filtered in a platform-specific way. (On Windows, return followed by
linefeed is filtered to a single linefeed.)
|
>(outfile "/tmp/junk" 'append) #<output-port:/tmp/junk> |
outfile filename ['append]
Opens the specified path for writing. By
default, the file is truncated if it already exists. Returns an
output-port. Arc supports only 'text mode for outfile.
|
>(outfile "/tmp/junk" 'append) #<output-port:/tmp/junk> |
rmfile path
Removes the specified file.
|
>(rmfile "/tmp/junk") nil |
atomic-invoke function
Invokes function, making sure that only one
thread at a time invokes something wrapped inside an atomic-invoke.
|
>(atomic-invoke (fn () "critical section" (+ 1 2))) 3 |
break-thread thread
Triggers a break exception on a thread.
|
>(let th (new-thread (fn () (sleep 2))) (break-thread th)) user break |
dead thread
Predicate to test if a thread has terminated.
|
>(let th (new-thread (fn () (sleep 1))) (prn (dead th)) (sleep 2) (prn (dead th))) nil t t |
kill-thread thread
Terminates the specified thread immediately.
|
>(let th (new-thread (fn () (sleep 100))) (kill-thread th) (dead th)) t |
new-thread procedure
Creates and returns a new thread. Was 'thread'
in arc0.
|
>(new-thread (fn () (+ 1 2))) #<thread> |
sleep secs
Causes the current thread to sleep for at least the
specified time.
|
>(sleep 0.1) nil |
details exception
Returns the message associated with an exception.
|
>(on-err (fn (ex) (details ex)) (err "boo")) Error: boo |
err string ...
Raises an exception with the given text.
|
>(err "Failure" 42) Error: Failure 42 |
on-err err-proc proc
Executes proc. Calls err-proc if an exception
occurs in proc. The exception is passed to err-proc
|
>(on-err (fn (ex) (string "caught " (details ex))) (fn () (/ 1 0))) "caught /: division by zero" |
ccc procedure
Packages up the current continuation into an 'escape
procedure' and passes it to the procedure. Equivalent to Scheme's call/cc or call-with-current-continuation.
|
>(ccc (fn (ep) (ep "bailout value") 42)) "bailout value" |
protect during-procedure after-procedure
Uses Scheme's
dynamic-wind to
ensure that after-procedure is executed whenever during-procedure exits.
|
>(protect (fn () (/ 1 0)) (fn () (prn "after"))) after Error: /: division by zero |
current-gc-milliseconds
Returns the amount of time spent in garbage
collection.
See MzScheme
for more details on Arc's time functions.
|
>(current-gc-milliseconds) 5476 |
current-process-milliseconds
Returns the number of milliseconds of
processor time used.
|
>(current-process-milliseconds) 13644 |
msec
Returns current time in milliseconds. The time is from an
arbitrary starting date, and can wrap or be negative.
|
>(msec) 355667501 |
seconds
Returns current time in seconds, from a platform-specific
starting date.
|
>(seconds) 1205093994 |
system string
Executes the string in the underlying OS.
|
>(system "date #/t") Sun Mar 9 13:19:54 PDT 2008 nil |
quit
Exits the interpreter.
|
>(quit) --exits-- |
Copyright 2008 Ken Shirriff.