git @ Cat's Eye Technologies Robin / 6e7e876
REBOOT LANGUAGE Chris Pressey 10 years ago
150 changed file(s) with 5752 addition(s) and 9157 deletion(s). Raw diff Collapse all Expand all
44
55 -----------------------------------------------------------------------------
66
7 Copyright (c)2012 Chris Pressey, Cat's Eye Technologies.
7 Copyright (c)2012-2014 Chris Pressey, Cat's Eye Technologies.
88
99 The authors intend this Report to belong to the entire Robin
1010 community, and so we grant permission to copy and distribute it for
1616
1717 -----------------------------------------------------------------------------
1818
19 All source code for the reference interpreter, except the Robin.Chan
20 module, is covered by this license:
19 All source code for the reference interpreter is covered by this BSD-style
20 license:
2121
2222 -----------------------------------------------------------------------------
2323
24 Copyright (c)2012 Cat's Eye Technologies. All rights reserved.
24 Copyright (c)2012-2014 Chris Pressey, Cat's Eye Technologies.
25 All rights reserved.
2526
2627 Redistribution and use in source and binary forms, with or without
2728 modification, are permitted provided that the following conditions
5152 POSSIBILITY OF SUCH DAMAGE.
5253
5354 -----------------------------------------------------------------------------
54
55 The Robin.Chan module is a derivative work based on the
56 Control.Concurrent.Chan module from the GHC project, and is thus
57 covered by this license:
58
59 -----------------------------------------------------------------------------
60
61 The Glasgow Haskell Compiler License
62
63 Copyright 2004, The University Court of the University of Glasgow.
64 All rights reserved.
65
66 Redistribution and use in source and binary forms, with or without
67 modification, are permitted provided that the following conditions are met:
68
69 - Redistributions of source code must retain the above copyright notice,
70 this list of conditions and the following disclaimer.
71
72 - Redistributions in binary form must reproduce the above copyright notice,
73 this list of conditions and the following disclaimer in the documentation
74 and/or other materials provided with the distribution.
75
76 - Neither name of the University nor the names of its contributors may be
77 used to endorse or promote products derived from this software without
78 specific prior written permission.
79
80 THIS SOFTWARE IS PROVIDED BY THE UNIVERSITY COURT OF THE UNIVERSITY OF
81 GLASGOW AND THE CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES,
82 INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND
83 FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
84 UNIVERSITY COURT OF THE UNIVERSITY OF GLASGOW OR THE CONTRIBUTORS BE LIABLE
85 FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
86 DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
87 SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
88 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
89 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
90 OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH
91 DAMAGE.
+0
-40
Main.lhs less more
0 > module Main where
1
2 > import System.Environment
3 > import System.Exit
4
5 > import Robin.Parser (parseRobin)
6 > import Robin.Module (evalRobin, mkModuleCache)
7
8 Command-line Entry Point
9 ------------------------
10
11 > main = do
12 > args <- getArgs
13 > processArgs args [] [] True
14
15 > processArgs args modulePath nonBuiltinModules printResult =
16 > case args of
17 > ("-B":moduleName:rest) ->
18 > processArgs rest modulePath (moduleName:nonBuiltinModules) printResult
19 > ("-m":directoryName:rest) ->
20 > processArgs rest (modulePath ++ [directoryName]) nonBuiltinModules printResult
21 > ("-n":rest) ->
22 > processArgs rest modulePath nonBuiltinModules False
23 > [filename] -> do
24 > program <- readFile filename
25 > case parseRobin program of
26 > Right ast -> do
27 > (_, result) <- evalRobin (mkModuleCache modulePath nonBuiltinModules) ast
28 > case printResult of
29 > True -> do
30 > putStrLn $ show result
31 > exitWith ExitSuccess
32 > False -> do
33 > exitWith ExitSuccess
34 > Left problem -> do
35 > print problem
36 > exitWith $ ExitFailure 1
37 > _ -> do
38 > putStrLn "Usage: robin {-B module} {-m dir} [-n] source.robin"
39 > exitWith $ ExitFailure 1
00 Robin
11 =====
22
3 Robin is a programming language which draws from [Scheme][] (via [Pixley][]),
4 [PicoLisp][], and [Erlang][].
3 _This is a work in progress_
54
6 Robin's core language is quite ascetic; however, Robin supports a module
7 system, by which functionality can be brought in from modules (written in
8 Robin, or some other language,) which expose their functionality to programs
9 and other modules.
5 Robin is a homoiconic S-expression-based language (similar to, for example,
6 [Scheme][], with influences from [Pixley][] and [PicoLisp][]) with the
7 following features:
108
11 The standard modules include a small "standard library" to make programming
12 slightly easier, a module for concurrent processes with message-passing, and
13 a module for handling exceptions.
9 * The _macro_ (rather than the function) as the fundamental abstraction
10 mechanism. There is a function form, but it's defined as a macro!
11 * A very small set of built-in operations.
12 * A very small reference implementation in Literate Haskell
13 (about 600 lines of code, excluding the explanatory prose.)
14 * A fairly rich standard library of macros built on top of those built-in
15 operations. (Thus it can be used as either a "low-level" or "high-level"
16 language.)
17 * A fairly rich test suite (about 460 test cases.)
18 * An almost zealous system-agnosticism.
19 * An almost zealous disdain for escape characters. Robin's string syntax
20 never needs them (it's more like a lightweight "heredoc".)
21 * A module system (which is rather fast-and-loose, so it's perhaps not
22 fair to call it a module system. It's more like C's `#include`s —
23 except it's zealously system-agnostic. And actually we're still working
24 out the details here. See the file `doc/Modules.markdown`.)
25 * A(n attempt at) a clean separation of evaluation (no "side-effects") and
26 execution (with "side-effects" and system interaction) by the use of
27 _reactors_ (which are basically event handlers.) See the file
28 `doc/Reactor.markdown` for more information.
1429
15 Robin programs are homoiconic, and presented in a S-expression-based syntax.
30 Quick Start
31 -----------
1632
17 Instead of function values, Robin supplies _macros_ as the primitive
18 abstraction. Robin's macros are somewhat like PicoLisp's one-argument
19 lambdas -- they do not automatically evaluate their arguments. Function
20 values are built on top of macros, using the built-in macro `eval`.
33 You'll need either `ghc` or Hugs installed.
2134
22 Like Erlang, Robin is purely functional except for message-passing.
23 That is, functions have no side-effects, with the single exception of
24 being able to send messages to, and receive messages from, other processes.
25 All facilities of the underlying system are modelled as such processes.
35 Clone this repo and `cd` into it, and run `./build.sh` to build the reference
36 interpreter `bin/robinri`, and the slightly-less-impractical interpreter
37 called `bin/whitecap` (for historical reasons, and subject to change.)
2638
27 Robin supports a simple system of raising and handling exceptions. This
28 helps define the semantics of otherwise undefined operations, such as trying
29 to obtain the `tail` of a number.
39 If you have a few minutes to spare, please do run the tests by running
40 `./test.sh`. (This requires [Falderal][].)
3041
31 Lastly, Robin unifies (to a degree) programming and static analysis. The
32 language itself defines essentially no rules of static correctness beyond
33 the basic rules about syntax. Static analyses are available in modules,
34 just like any other kind of functionality, letting the programmer choose
35 what level of pre-execution checking is applied to their code.
36
37 [Erlang]: http://erlang.org/
38 [PicoLisp]: http://picolisp.com/
39 [Pixley]: http://catseye.tc/projects/pixley/
40 [Scheme]: http://schemers.org/
41
42 Distribution
43 ------------
44
45 The current version of Robin under development is version 0.1. Even it
46 is unreleased, so what you're looking at here is pure "technology
47 preview" stuff. Expect everything to change, perhaps drastically.
48
49 Installation
50 ------------
51
52 Step 1: Obtain the sources.
53
54 $ hg clone https://bitbucket.org/catseye/robin
55
56 *or*
57
58 $ git clone git://github.com/catseye/Robin.git
59
60 Step 2: Make sure you have `ghc`, and the Haskell packages `parsec` and
61 (optionally) `hscurses` installed (these can both be instaled via `cabal`).
62 The following instructions are for Ubuntu; equivalents for other operating
63 systems are left as an exercise for the reader.
64
65 $ sudo apt-get install ghc cabal-install
66 $ cabal install parsec
67 $ cabal install hscurses # if you want to use the Console module
68 $ cabal install random # if you want to use the Random module
69
70 Step 3: Build the sources.
71
72 $ cd robin
73 $ ./build.sh
74
75 All built-in modules are built by default. If you want to exclude some
76 modules (for example `console`), you can list them in the `WITHOUT`
77 environment variable. For example,
78
79 $ WITHOUT="CrudeIO Console" ./build.sh
80
81 Note that if you exclude the built-in `small` module, `robin` will fall back
82 to the `small` module written in Robin, but expect it to be *much* slower.
83
84 Step 4: Get Falderal, so that you can run the tests.
85
86 $ cd ..
87 $ hg clone https://bitbucket.org/catseye/falderal
88 $ cd falderal
89 $ ./install.sh
90 $ cd ..
91
92 Step 5: Run the tests.
93
94 $ cd robin
95 $ ./test.sh
96
97 Step 6: Run an example program or two.
98
99 $ bin/robin -m modules eg/hunt-the-wumpus.robin
100
101 The `robin` executable so built is the reference interpreter; it is not
102 intended for production use, so much as to be a model for how to implement
103 Robin. It can, however, be used for light-duty tasks. We suggest creating
104 the following driver script and putting it on your executable search path:
105
106 #!/bin/sh
107 ROBIN_PATH=/path/to/robin/repo
108 ${ROBIN_PATH}/bin/robin -m ${ROBIN_PATH}/module $*
109
110 Of course, replace `/path/to/robin/repo` with the actual path to the clone
111 you created with Mercurial or git. If you write your own modules, you can
112 place them in a directory of your choosing, and pass it after another `-m`
113 option in the driver script (before the existing `-m` option, if you want
114 your modules to override the standard ones.)
115
116 It is possible to build `robin` under Windows, using `ghc` from the Haskell
117 Platform for Windows, and Cygwin to run the shell scripts; however, there
118 are various minor considerations which are currently outside the scope of
119 this README. If you're really motivated, you'll figure it out.
42 (There will be a link to a tutorial with further instructions in the future)
12043
12144 Documentation
12245 -------------
12346
12447 Robin's fundamental semantics are documented in
125 [doc/Robin.falderal](doc/Robin.falderal). From there you will find links
126 to documentation on each of the standard modules as well.
48 [doc/Robin.markdown](doc/Robin.markdown).
12749
128 Goals
129 -----
50 History
51 -------
13052
131 * To not be unduly burdensome to implement or analyze. The core language
132 is kept very small, the "standard library" can be written in Robin itself,
133 and features such as concurrency and exceptions are optional. The core
134 language is purely functional, to keep it mathematically simple, and the
135 reference implementation is in Haskell, which is a lot closer to an
136 "executable semantics" than one in, say, C would be. The functionality
137 of the language is thoroughly tested. Both the implementation and the
138 test suite are written in a literate style, to keep the prose of the
139 specification in close proximity to the code so that they can be easily
140 checked against each other for inconsistencies.
53 Robin 0.2 is a somewhat significant departure from Robin 0.1. It keeps:
14154
142 * To err on the side of beauty and simplicity and orthogonality, rather
143 than efficient implementation or expediency.
55 * its syntax
56 * its core builtins (mostly)
57 * some of its standard modules ("small", list, environment, boolean, arith)
58 * exceptions (and makes them standard rather than optional)
59 * its zealous system agnosticism
60 * its zealous disdain for escape characters (i.e. its literal string syntax)
14461
145 * At the same time, to allow the programmer to do "real" work, like
146 interfacing with an actual computer.
62 Robin 0.2 *discards* from Robin 0.1:
14763
148 * At the same time as that, to be decoupled from any particular computer
149 or operating system, as far as possible. The language does not specify
150 how Robin programs should be run, nor how to locate modules that are
151 imported. Devices are abstracted to "virtual devices" and are modelled
152 as processes; input and output are done with message-passing.
64 * bigrats. Instead, in Robin 0.2 you get 32-bit signed integers (yes,
65 precisely those.) Anything else, you have to build.
66 * its module system. Robin has its own, much less hermetic/holistic
67 system. See the file `doc/Modules.markdown`.
68 * concurrency.
69 * I/O and side-effects. It has reactors instead. See `doc/Reactor.markdown`.
70 * its grand ambitions. Robin would rather exist than be perfect.
15371
154 * To minimize atavisms and jargon. The legacy of Robin's lexicon is
155 Scheme, which itself comes from the legacy of Lisp; while there are some
156 good patterns here (like predicates whose names end in `?`), there are
157 also a lot of anachronisms (like `car` and `cdr`) which should be
158 jettisoned. Proper English words should be used instead, although of
159 course there is room for abbreviations when they are unambiguous
160 (`env`, `eval`, `expr`, `arith`, and so forth.)
72 Robin 0.2 *adds* to Robin 0.1:
16173
162 * To serve as an outlet for my predilictions. Sometimes, when using a
163 language, you come across a feature or aspect that just strikes you
164 as wrong-headed, and it makes you want to build something that doesn't
165 irritate you as badly. Robin is, to some extent, that, for me.
74 * _reactors_, which I hope will be a cleaner and more system-agnostic
75 way to do I/O. See `doc/Reactor.markdown`.
16676
167 * To not be taken *too* seriously -- it has many of the attributes of a
168 production language, but it *is* something I am undertaking for fun.
169
170 Plans
171 -----
172
173 ### Fundamental Semantics ###
174
175 * Add an opaque type -- opaque values have internals that can only be
176 accessed inside the module in which they were created. Actually, we
177 already have function values, and they're traditionally opaque; but
178 I'm not sure that solves the problem of them only being accessible
179 from the module in which they're defined. This will probably start
180 life as some sort of "object" type, which encapsulates some (immutable)
181 state, and supports methods (which may return a transformed object);
182 this may devolve into something which is implemented purely in terms
183 of function values (closing over the state, and returning a new
184 function value with a transformed state.)
185
186 * Work out the approach to short-circuiting (roughly, not given in the
187 semantics, but optimization is allowed by the implementation after it
188 has established all the arguments are pure.)
189
190 ### Standard Modules ###
191
192 * In the `concurrency` module, finalize the semantics for exception and
193 final-result and unknown-tag reply messages, particularly during `call`
194 and `respond`.
195
196 * Some kind of macro for capturing the recursive function call pattern
197 (like `letrec`, but not necessary to support mutual recursion.) Possibly
198 called `bind-recur`. Also `let-recur` could build on that. Turn:
199
200 (bind-recur foo (fun (a b c)
201 (if a
202 (b c)
203 (foo (bar a) b c))) ...)
204
205 into
206
207 (bind foo
208 (bind foo-r (fun (self a b c)
209 (if a
210 (b c)
211 (self self (bar a) b c)))
212 (fun (a b c) (foo-r foo-r a b c))) ...)
213
214 Lack of a `gensym` will make this tricky. We don't really have to
215 bind `foo-r`, we can just repeat the definition of the recursive
216 function; but I don't know how we can add the `self` parameter without
217 potentially shadowing a user parameter also named `self`.
218
219 An alternative which might be easier (but less elegant) would be to
220 introduce a primitive `(self)` which evaluates to the function currently
221 being evaluated. This might make the `self` parameter to macros redundant,
222 though.
223
224 But, it might just be simpler to punt on this and make it a part of the
225 sugar in the humane syntax, which could support a form like:
226
227 forward foo in
228 let
229 foo = fun(a, b, c)
230 if a then b(c) else foo(bar(a), b, c)
231 in
232 ...
233
234 ...and this would transform the binding as appropriate. This would also
235 extend to mutually recursive definitions (`forward foo, bar in ...`)
236
237 * Work out the static analysis modules. See the Static Analysis document
238 for more information.
239
240 ### Devices ###
241
242 * Create the `device` module and use it instead of `crude-io` and
243 `console`. Perhaps make those two into "interface modules"? I
244 suppose an interface module would expose a predicate to check if a
245 device supports a given interface.
246
247 * Write a `timer` device which can be asked (via a message) to send
248 back a message after a given time has passed. This could be used to
249 build a version of `recv` which can time out.
250
251 * Enhance the `console` device. Write a version of `robotfindskitten`
252 using it.
253
254 ### Possible Future Modules ###
255
256 * Write a `functional` module which exports some functions for working
257 with functions, such as `identity`, `compose`, and possibly `curry`
258 and `uncurry`.
259
260 * Possibly make a `transcendental` module to contain `exp`, `pow`,
261 `log`, `sqrt`, and so forth.
262
263 * Write a `trig` module which exports trigonometric functions `cos`,
264 `sin`, `tan`, `atan`, `pi`, etc. Initially write this in Robin,
265 but it's a good candidate for implementing natively.
266
267 * Write a `set` module which exports functions which treat lists as
268 sets, with each operation ensuring the set elements are unique in
269 the list.
270
271 * Write a `pixley` module which exports only the identifiers supported
272 by Pixley. This could be imported, instead of `core`, to emulate
273 Pixley in Robin.
274
275 * Create a new module for exception semantics extended as follows. Allow the
276 backtrace of an exception to be accessed as a Robin object, and, to some
277 extent, manipulated. When an exception is raised in a context where
278 another exception is being caught, allow the backtraces to be chained
279 together. When an exception is raised during (say) the reading of a text
280 file, allow the backtrace to be amended with the position within the text
281 file to which the problem can be traced. The purpose of all this is
282 to allow producing more complete error messages at the top level.
283
284 ### Documentation ###
285
286 * Document the alist functions in the `list` module.
287
288 * Document the literate Haskell implementation better -- right now it's
289 pretty scant.
290
291 * Document the evaluation rules (they're very similar to Scheme's, but
292 they should still be written down.)
293
294 ### Tests ###
295
296 * Fuller tests for `call`.
297
298 * Make the tests for `core` only ever import the `core` module -- rewrite
299 those tests which currently import `small`, although they may be pretty
300 ugly expressed purely in `core` terms.
301
302 * Have the test runner know to only test those built-in modules which were
303 selected for inclusion during the build step. (Write those options to
304 a text file which the test runner script reads.)
305
306 * Informally test tail-recursive behavior (does an infinite loop
307 leak memory?)
308
309 * Improve Falderal to let tests take some text as input; use this for the
310 tests for `crude-input`.
311
312 ### Other Implementations ###
313
314 * Build another implementation of Robin. This should probably wait,
315 as even the fundamental semantics are still a moving target, and
316 having to maintain two implementations is not so desirable. However,
317 this will let me have a place to implement "practical" things that
318 arguably don't belong in the reference implementation.
319
320 * Allow the implementation to use a configuration file (likely a `.robinrc`
321 file (or directory) in the user's home directory) to specify which files
322 (and where) to load for which modules.
323
324 * Implement a selective execution trace facility (configured in the
325 configuration file, probably) which starts and stops tracing at
326 configured points during program execution.
327
328 * Upon an uncaught exception, dump a backtrace. This should be based
329 on the current continuation at the time the exception was raised.
77 [Falderal]: http://catseye.tc/node/Falderal
78 [PicoLisp]: http://picolisp.com/
79 [Pixley]: http://catseye.tc/projects/pixley/
80 [Robin]: http://catseye.tc/node/Robin
81 [Scheme]: http://schemers.org/
+0
-124
Robin/Chan.lhs less more
0 > module Robin.Chan
1
2 This module implements channels for message-passing in Robin. It is
3 derived from the `[Control.Concurrent.Chan][]` library module from GHC,
4 and is thus (c)2001 The University of Glasgow, and covered under a
5 [BSD-style license][].
6
7 [Control.Concurrent.Chan]: http://www.haskell.org/ghc/docs/latest/html/libraries/base/src/Control-Concurrent-Chan.html
8 [BSD-style license]: http://www.haskell.org/ghc/docs/latest/html/libraries/base/LICENSE
9
10 It has been modified to associate each channel with exactly one thread, and
11 it allows only that thread to read values from the channel, unget items to
12 the channel, or check the channel for emptiness. This both makes the
13 message-passing semantics closer to those of Erlang (where each process
14 has private access to its own message queue), and prevents a [potential
15 deadlock][] between reading and ungetting (or reading and checking for
16 emptiness.)
17
18 [potential deadlock]: http://hackage.haskell.org/trac/ghc/ticket/4154
19
20 > (
21 > Chan, -- abstract
22 > newChan, -- :: IO (Chan a)
23 > setChanThread, -- :: Chan a -> ThreadId -> Chan a
24 > writeChan, -- :: Chan a -> a -> IO ()
25 > readChan, -- :: Chan a -> IO a
26 > unGetChan, -- :: Chan a -> a -> IO ()
27 > isEmptyChan -- :: Chan a -> IO Bool
28 > ) where
29
30 > import Control.Concurrent (ThreadId, myThreadId)
31 > import Control.Concurrent.MVar
32
33 `Chan` is an abstract type representing an unbounded FIFO channel.
34 A channel is represented by two `MVar`s keeping track of the two ends
35 of the channel contents,i.e., the read- and write ends. Empty `MVar`s
36 are used to handle consumers trying to read from an empty channel.
37
38 > data Chan a
39 > = Chan ThreadId
40 > (MVar (Stream a))
41 > (MVar (Stream a))
42 > deriving Eq
43
44 > type Stream a = MVar (ChItem a)
45
46 > data ChItem a = ChItem a (Stream a)
47
48 See the Concurrent Haskell paper for a diagram explaining the
49 how the different channel operations proceed.
50
51 @newChan@ sets up the read and write end of a channel by initialising
52 these two `MVar`s with an empty `MVar`.
53
54 Build and return a new instance of `Chan`.
55
56 > newChan :: IO (Chan a)
57 > newChan = do
58 > threadId <- myThreadId
59 > hole <- newEmptyMVar
60 > readVar <- newMVar hole
61 > writeVar <- newMVar hole
62 > return (Chan threadId readVar writeVar)
63
64 Set the thread that is allowed to read the `Chan`.
65
66 > setChanThread :: Chan a -> ThreadId -> Chan a
67 > setChanThread (Chan _ readVar writeVar) threadId =
68 > Chan threadId readVar writeVar
69
70 To put an element on a channel, a new hole at the write end is created.
71 What was previously the empty `MVar` at the back of the channel is then
72 filled in with a new stream element holding the entered value and the
73 new hole.
74
75 Write a value to a `Chan`.
76
77 > writeChan :: Chan a -> a -> IO ()
78 > writeChan (Chan _ _ writeVar) val = do
79 > new_hole <- newEmptyMVar
80 > modifyMVar_ writeVar $ \old_hole -> do
81 > putMVar old_hole (ChItem val new_hole)
82 > return new_hole
83
84 Read the next value from the 'Chan'.
85
86 > readChan :: Chan a -> IO a
87 > readChan (Chan threadId readVar _) = do
88 > me <- myThreadId
89 > case threadId == me of
90 > True ->
91 > modifyMVar readVar $ \read_end -> do
92 > (ChItem val new_read_end) <- readMVar read_end
93 > return (new_read_end, val)
94 > False ->
95 > error ((show me) ++ " not allowed to read from this Chan")
96
97 Put a data item back onto a channel, where it will be the next item read.
98
99 > unGetChan :: Chan a -> a -> IO ()
100 > unGetChan (Chan threadId readVar _) val = do
101 > me <- myThreadId
102 > case threadId == me of
103 > True -> do
104 > new_read_end <- newEmptyMVar
105 > modifyMVar_ readVar $ \read_end -> do
106 > putMVar new_read_end (ChItem val read_end)
107 > return new_read_end
108 > False ->
109 > error ((show me) ++ " not allowed to unget to this Chan")
110
111 Return `True` if the supplied `Chan` is empty.
112
113 > isEmptyChan :: Chan a -> IO Bool
114 > isEmptyChan (Chan threadId readVar writeVar) = do
115 > me <- myThreadId
116 > case threadId == me of
117 > True ->
118 > withMVar readVar $ \r -> do
119 > w <- readMVar writeVar
120 > let eq = r == w
121 > eq `seq` return eq
122 > False ->
123 > error ((show me) ++ " not allowed to check this Chan for emptiness")
+0
-229
Robin/Concurrency.lhs less more
0 > module Robin.Concurrency where
1
2 > import Control.Concurrent (forkIO, myThreadId)
3 > import Robin.Chan
4
5 > import Robin.IEnv
6 > import qualified Robin.Env as Env
7 > import Robin.Expr
8 > import Robin.Eval
9 > import Robin.Core
10
11 Concurrency
12 ===========
13
14 Helper Functions
15 ----------------
16
17 These functions can be imported and used by other Haskell modules,
18 especially built-in Robin modules which expose a process.
19
20 Get a Pid representing the current process out of its IEnv.
21
22 > getPid :: IEnv Expr -> Expr
23 > getPid ienv =
24 > Pid (getThreadId ienv) (getChannel ienv)
25
26 Get the channel of a pid.
27
28 > getChan (Pid _ c) = c
29 > getChan other = error ("getChan: not a Pid: " ++ show other)
30
31 Check if an Expr is a pid or not.
32
33 > isPid (Pid _ _) = True
34 > isPid _ = False
35
36 > assertPid = assert (isPid) "expected-pid"
37
38 Start a Haskell function in a Robin process. This ensures that the
39 new process has a chan it can use, and that the current process has
40 an appropriate reference to that chan as well. However, it will not
41 inform the child process who its parent process is.
42
43 > spawn :: (Chan Expr -> IO ()) -> IO Expr
44 > spawn fun = do
45 > chan <- newChan
46 > thread <- forkIO $ launch (fun) chan
47 > let chan' = setChanThread chan thread
48 > return $ Pid thread chan'
49 > where
50 > launch fun chan = do
51 > thread <- myThreadId
52 > let chan' = setChanThread chan thread
53 > fun chan'
54
55 Evaluate a Robin expression in a Robin process. After the Haskell
56 process has started, we set up an appropriate IEnv and evaluate
57 the macro in that.
58
59 TODO: should the final continuation send a message to the parent
60 too?
61
62 > spawnExpr :: Expr -> IEnv Expr -> Expr -> IO Expr
63 > spawnExpr env ienv expr = do
64 > spawn launch
65 > where
66 > launch chan = do
67 > thread <- myThreadId
68 > let parent = getPid ienv
69 > let exch = makeMsgSendingExcHandler parent
70 > let myIenv = newIEnv exch thread chan
71 > eval env myIenv expr (\x -> do return (List []))
72 > return ()
73
74 > makeMsgSendingExcHandler pid =
75 > \value -> do
76 > writeChan (getChan pid) (errMsg "uncaught-exception" value)
77 > return (List [])
78
79 Capture the "response" pattern for processes which handle `call`s. This
80 doesn't require that the process has a Robin pid.
81
82 > respond :: Chan Expr -> [(String, a -> Expr -> Expr -> IO (a, Expr))] -> a -> IO ()
83
84 > respond chan handlers state = do
85 > message <- readChan chan
86 > tid <- myThreadId
87 > let myPid = Pid tid chan
88 > case message of
89 > (List [sender, (Symbol tagText), payload]) ->
90 > case lookup tagText handlers of
91 > Just handler -> do
92 > (state', reply) <- handler state sender payload
93 > let response = List [myPid, (List [(Symbol tagText), (Symbol "reply")]), reply]
94 > writeChan (getChan sender) response
95 > respond chan handlers state'
96 > Nothing -> do
97 > let response = List [myPid, (List [(Symbol tagText), (Symbol "reply")]), (Symbol "what?")]
98 > writeChan (getChan sender) response
99 > respond chan handlers state
100 > _ -> do
101 > respond chan handlers state
102
103 Robin Functions
104 ---------------
105
106 These are the functions exported by this Robin module.
107
108 > robinMyself env ienv (List []) cc = do
109 > cc $ getPid ienv
110 > robinMyself env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
111
112 > pidP = predP isPid
113
114 > robinSpawn env ienv (List [id@(Symbol _), expr, body]) cc = do
115 > pid <- spawnExpr env ienv expr
116 > eval (Env.insert id pid env) ienv body cc
117 > robinSpawn env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
118
119 > send env ienv (List [pidExpr, msgExpr, body]) cc = do
120 > eval env ienv pidExpr (\pid ->
121 > assertPid ienv pid (\pid ->
122 > eval env ienv msgExpr (\msg -> do
123 > writeChan (getChan pid) msg
124 > eval env ienv body cc)))
125 > send env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
126
127 > recv env ienv (List [id@(Symbol _), body]) cc = do
128 > message <- readChan $ getChan $ getPid ienv
129 > --putStrLn ((show $ getPid ienv) ++ " just recvd " ++ (show message))
130 > eval (Env.insert id message env) ienv body cc
131 > recv env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
132
133 > msgsP env ienv (List []) cc = do
134 > isEmpty <- isEmptyChan $ getChan $ getPid ienv
135 > cc $ Boolean $ not isEmpty
136 > msgsP env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
137
138 This might, one day, be implemented in Robin, in some other module.
139 For now, for simplicity, it's here.
140
141 `call` is a synchronous communication with another process; it executes a
142 `send` and then a `recv`. It only finishes when the message received came
143 from the process to which the first message was sent; it queues up all other
144 messages in the meantime, and re-sends them to self when done.
145
146 TODO: This should also handle any "finished" or "uncaught exception" response
147 from the destination pid.
148
149 > call env ienv (List [pidExpr, tag@(Symbol _), payloadExpr, repsym@(Symbol _), body]) cc = do
150 > eval env ienv pidExpr (\pid ->
151 > assertPid ienv pid (\pid ->
152 > eval env ienv payloadExpr (\payload -> do
153 > let msg = List [(getPid ienv), tag, payload]
154 > writeChan (getChan pid) msg
155 > waitForResponse env ienv pid tag repsym body [] cc)))
156 > call env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
157
158 > waitForResponse env ienv pid tag repsym body queue cc = do
159 > message <- readChan $ getChan $ getPid ienv
160 > case message of
161 > (List [somePid, (List [someTag, (Symbol "reply")]), returnPayload]) -> do
162 > if (pid == somePid) && (tag == someTag) then do
163 > sendAll (getChan $ getPid ienv) (reverse queue)
164 > eval (Env.insert repsym returnPayload env) ienv body cc
165 > else
166 > waitForResponse env ienv pid tag repsym body (message:queue) cc
167 > (List [(Symbol "uncaught-exception"), excval]) ->
168 > raise ienv excval
169 > other ->
170 > waitForResponse env ienv pid tag repsym body (message:queue) cc
171
172 > sendAll chan [] = do
173 > return ()
174 > sendAll chan (msg:msgs) = do
175 > writeChan chan msg
176 > sendAll chan msgs
177
178 > robinRespond env ienv branches cc = do
179 > validateRespond ienv branches (\ok -> do
180 > message <- readChan $ getChan $ getPid ienv
181 > case message of
182 > (List [sender, tag@(Symbol _), payload]) -> do
183 > case lookupRespondTag tag branches of
184 > Just x@(bindVar, responseExpr, continue) -> do
185 > let newEnv = Env.insert bindVar payload env
186 > eval newEnv ienv responseExpr (\reply -> do
187 > let response = List [(getPid ienv), (List [tag, (Symbol "reply")]), reply]
188 > writeChan (getChan sender) response
189 > eval newEnv ienv continue cc)
190 > -- TODO: this should not necessarily just loop
191 > Nothing -> do
192 > let response = List [(getPid ienv), (List [tag, (Symbol "reply")]), (Symbol "what?")]
193 > writeChan (getChan sender) response
194 > robinRespond env ienv branches cc
195 > -- TODO: this should not necessarily just loop
196 > _ -> do
197 > robinRespond env ienv branches cc)
198
199 > validateRespond ienv (List []) cc = cc (List [])
200 > validateRespond ienv (List ((List [(Symbol _), (List [(Symbol _)]), responseExpr, continue]):rest)) cc =
201 > validateRespond ienv (List rest) cc
202 > validateRespond ienv other cc = raise ienv (errMsg "illegal-arguments" other)
203
204 > lookupRespondTag :: Expr -> Expr -> Maybe (Expr, Expr, Expr)
205
206 > lookupRespondTag tag (List []) = Nothing
207 > lookupRespondTag tag (List ((List [candidateTag, (List [bindVar]), responseExpr, continue]):rest))
208 > | tag == candidateTag = Just (bindVar, responseExpr, continue)
209 > | otherwise = lookupRespondTag tag (List rest)
210
211 Module Definition
212 -----------------
213
214 > moduleId = ("concurrency", 0, 1)
215
216 > moduleDef :: IO Expr
217 > moduleDef = do
218 > return $ Env.fromList $ map (\(name,bif) -> (name, Builtin name bif))
219 > [
220 > ("myself", robinMyself),
221 > ("pid?", pidP),
222 > ("spawn!", robinSpawn),
223 > ("send!", send),
224 > ("recv!", recv),
225 > ("call!", call),
226 > ("respond!", robinRespond),
227 > ("msgs?", msgsP)
228 > ]
+0
-74
Robin/Console.lhs less more
0 > module Robin.Console where
1
2 > import Control.Concurrent (myThreadId)
3
4 > import UI.HSCurses.Curses hiding (Pair)
5
6 > import Robin.Chan
7 > import Robin.Expr
8 > import qualified Robin.Env as Env
9 > import Robin.Parser
10
11 > import Robin.Core (ratFloor)
12 > import Robin.Concurrency (spawn, respond)
13
14 Console
15 =======
16
17 A rudimentary virtual console module for Robin, based loosely on
18 `Console::Virtual`.
19
20 The virtual console output device accepts messages, and alters the
21 state of the virtual console based on those messages.
22
23 > outputHandler :: Chan Expr -> IO ()
24
25 > outputHandler chan = respond chan [
26 > ("activate", \(x, y) sender payload -> do
27 > initCurses
28 > screen <- initScr
29 > cBreak True
30 > echo False
31 > keypad stdScr True
32 > return ((x, y), Symbol "ok")),
33 > ("deactivate", \(x, y) sender payload -> do
34 > keypad stdScr False
35 > echo True
36 > cBreak False
37 > endWin
38 > return ((x, y), Symbol "ok")),
39 > ("display", \(x, y) sender payload -> do
40 > let str = show payload
41 > mvWAddStr stdScr y x str
42 > return ((x + length str, y), Symbol "ok")),
43 > ("clear-screen", \(x, y) sender payload -> do
44 > wMove stdScr 0 0
45 > wclear stdScr
46 > refresh
47 > return ((0, 0), Symbol "ok")),
48 > ("clear-eol", \(x, y) sender payload -> do
49 > wMove stdScr y x
50 > clrToEol
51 > return ((x, y), Symbol "ok")),
52 > ("position", \(x, y) sender (List [Number xr, Number yr]) -> do
53 > let x' = fromIntegral (ratFloor xr) :: Int
54 > let y' = fromIntegral (ratFloor yr) :: Int
55 > return ((x', y'), Symbol "ok")),
56 > ("update", \(x, y) sender payload -> do
57 > wMove stdScr y x
58 > refresh
59 > return ((x, y), Symbol "ok"))
60 > ] (0, 0)
61
62 Module Definition
63 -----------------
64
65 > moduleId = ("console", 0, 1)
66
67 > moduleDef :: IO Expr
68 > moduleDef = do
69 > consoleOutputPid <- spawn outputHandler
70 > return $ Env.fromList (
71 > [
72 > ("console", consoleOutputPid)
73 > ])
+0
-132
Robin/Core.lhs less more
0 > module Robin.Core where
1
2 > import Data.Ratio
3
4 > import qualified Robin.Env as Env
5 > import Robin.Expr
6 > import Robin.Eval
7
8 Core
9 ====
10
11 > robinHead env ienv (List [expr]) cc = do
12 > eval env ienv expr (\x ->
13 > assertList ienv x (\val ->
14 > case val of
15 > List (a:_) -> cc a
16 > other -> raise ienv (errMsg "expected-list" other)))
17 > robinHead env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
18
19 > robinTail env ienv (List [expr]) cc = do
20 > eval env ienv expr (\x ->
21 > assertList ienv x (\val ->
22 > case val of
23 > List (_:b) -> cc (List b)
24 > other -> raise ienv (errMsg "expected-list" other)))
25 > robinTail env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
26
27 > robinPrepend env ienv (List [e1, e2]) cc = do
28 > eval env ienv e1 (\x1 -> eval env ienv e2 (\val ->
29 > case val of
30 > List x2 -> cc $ List (x1:x2)
31 > other -> raise ienv (errMsg "expected-list" other)))
32 > robinPrepend env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
33
34 > equalP env ienv (List [e1, e2]) cc = do
35 > eval env ienv e1 (\x1 -> eval env ienv e2 (\x2 -> cc $ Boolean (x1 == x2)))
36 > equalP env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
37
38 > predP pred env ienv (List [expr]) cc = do
39 > eval env ienv expr (\x -> cc $ Boolean $ pred $ stripMetadata x)
40 > predP pred env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
41
42 > symbolP = predP isSymbol
43 > booleanP = predP isBoolean
44 > listP = predP isList
45 > macroP = predP isMacro
46 > numberP = predP isNumber
47
48 > robinSubtract env ienv (List [xexpr, yexpr]) cc = do
49 > eval env ienv xexpr (\x ->
50 > assertNumber ienv x (\(Number xv) ->
51 > eval env ienv yexpr (\y ->
52 > assertNumber ienv y (\(Number yv) ->
53 > cc (Number (xv - yv))))))
54 > robinSubtract env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
55
56 > robinDivide env ienv (List [xexpr, yexpr]) cc = do
57 > eval env ienv xexpr (\x ->
58 > assertNumber ienv x (\(Number xv) ->
59 > eval env ienv yexpr (\y ->
60 > assertNumber ienv y (\(Number yv) ->
61 > if yv == (0%1) then
62 > raise ienv (errMsg "division-by-zero" x)
63 > else
64 > cc (Number (xv / yv))))))
65 > robinDivide env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
66
67 > robinFloor env ienv (List [expr]) cc = do
68 > eval env ienv expr (\x ->
69 > assertNumber ienv x (\(Number xv) ->
70 > cc $ Number (ratFloor xv % 1)))
71 > robinFloor env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
72
73 > ratFloor x = numerator x `div` denominator x
74
75 > robinSign env ienv (List [expr]) cc = do
76 > eval env ienv expr (\x ->
77 > assertNumber ienv x (\(Number xv) ->
78 > cc $ Number $ sign xv))
79 > robinSign env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
80
81 > sign x = if x == 0 then 0 else if x < 0 then -1 else 1
82
83 > robinIf env ienv (List [test, texpr, fexpr]) cc = do
84 > eval env ienv test (\x ->
85 > assertBoolean ienv x (\(Boolean b) ->
86 > case b of
87 > True -> eval env ienv texpr cc
88 > False -> eval env ienv fexpr cc))
89 > robinIf env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
90
91 > robinEval env ienv (List [envlist, form]) cc = do
92 > eval env ienv envlist (\newEnv ->
93 > eval env ienv form (\body -> do
94 > eval newEnv ienv body cc))
95 > robinEval env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
96
97 > macro env ienv (List [args@(List [(Symbol selfS), (Symbol argsS), (Symbol envS)]), body]) cc = do
98 > cc $ Macro env args body
99 > macro env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
100
101 > robinRaise env ienv (List [expr]) cc =
102 > eval env ienv expr (\v -> raise ienv v)
103 > robinRaise env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
104
105 Module Definition
106 -----------------
107
108 > moduleId = ("core", 0, 1)
109
110 > moduleDef :: IO Expr
111 > moduleDef = do
112 > return $ Env.fromList $ map (\(name,bif) -> (name, Builtin name bif))
113 > [
114 > ("head", robinHead),
115 > ("tail", robinTail),
116 > ("prepend", robinPrepend),
117 > ("list?", listP),
118 > ("symbol?", symbolP),
119 > ("boolean?", booleanP),
120 > ("macro?", macroP),
121 > ("number?", numberP),
122 > ("equal?", equalP),
123 > ("subtract", robinSubtract),
124 > ("divide", robinDivide),
125 > ("floor", robinFloor),
126 > ("sign", robinSign),
127 > ("macro", macro),
128 > ("eval", robinEval),
129 > ("if", robinIf),
130 > ("raise", robinRaise)
131 > ]
+0
-115
Robin/CrudeIO.lhs less more
0 > module Robin.CrudeIO where
1
2 > import Control.Concurrent (myThreadId)
3 > import qualified Control.Exception as Exc
4
5 > import Robin.Chan
6 > import Robin.Expr
7 > import qualified Robin.Env as Env
8 > import Robin.Parser
9
10 > import Robin.Concurrency (spawn, getChan, respond)
11
12 CrudeIO
13 =======
14
15 A rudimentary I/O module for Robin.
16
17 The virtual output device accepts messages, and prints the S-expression
18 representation of the message to standard output.
19
20 > outputHandler :: Chan Expr -> IO ()
21
22 > outputHandler chan = respond chan [
23 > ("write", \state sender payload -> do
24 > putStrLn $ show payload
25 > return (state, Symbol "ok"))
26 > ] ()
27
28 The virtual input device waits for a line of input to become available,
29 checks to see if it has any new subscribers (and if so, registers them),
30 parses the line of text, sends the result to all subscribers (it it could
31 be parsed), and loops.
32
33 If any I/O error is encountered, the virtual input device sends the
34 symbol `eof` to all of its subscribers, and goes into a "black hole" loop.
35 (Note that going into a "black hole" doesn't seem to help race conditions
36 much. It's this next thing that has a better effect...)
37
38 We wait for at least one subscriber before trying to process any input,
39 otherwise we might lose input before anyone has subscribed to us.
40
41 > inputHandler :: Chan Expr -> IO ()
42
43 > inputHandler chan = do
44 > inputHandler' chan []
45
46 > inputHandler' chan [] = do
47 > subscribers <- processNewSubscribers chan []
48 > inputHandler' chan subscribers
49
50 > inputHandler' chan subscribers = do
51 > line <- getLine `Exc.catch` excHandler
52 > subscribers' <- getAnyNewSubscribers chan subscribers
53 > case parseRobin line of
54 > Right expr@(Symbol "eof") -> do
55 > sendToSubscribers chan expr subscribers'
56 > respond chan [] () -- 'black hole'
57 > Right expr -> do
58 > sendToSubscribers chan expr subscribers'
59 > inputHandler' chan subscribers'
60 > Left _ ->
61 > inputHandler' chan subscribers'
62 > where
63 > excHandler :: Exc.SomeException -> IO String
64 > excHandler _ = do return "eof"
65
66 > getAnyNewSubscribers :: Chan Expr -> [Expr] -> IO [Expr]
67
68 > getAnyNewSubscribers chan subscribers = do
69 > isEmpty <- isEmptyChan chan
70 > case isEmpty of
71 > True -> do return subscribers
72 > False -> processNewSubscribers chan subscribers
73
74 > processNewSubscribers :: Chan Expr -> [Expr] -> IO [Expr]
75
76 > processNewSubscribers chan subscribers = do
77 > message <- readChan chan
78 > case message of
79 > (List [sender, (Symbol "subscribe"), _]) -> do
80 > tid <- myThreadId
81 > let myPid = Pid tid chan
82 > let response = List [myPid, (List [(Symbol "subscribe"), (Symbol "reply")]), (Symbol "ok")]
83 > writeChan (getChan sender) response
84 > getAnyNewSubscribers chan (sender:subscribers)
85 > (List (sender:tag:_)) -> do
86 > tid <- myThreadId
87 > let myPid = Pid tid chan
88 > let response = List [myPid, (List [tag, (Symbol "reply")]), (Symbol "what?")]
89 > writeChan (getChan sender) response
90 > getAnyNewSubscribers chan subscribers
91 > _ -> do
92 > getAnyNewSubscribers chan subscribers
93
94 > sendToSubscribers chan expr [] = do
95 > return ()
96 > sendToSubscribers chan expr (subscriber:rest) = do
97 > writeChan (getChan subscriber) expr
98 > --putStrLn ("just sent " ++ (show expr) ++ " to " ++ (show subscriber))
99 > sendToSubscribers chan expr rest
100
101 Module Definition
102 -----------------
103
104 > moduleId = ("crude-io", 0, 1)
105
106 > moduleDef :: IO Expr
107 > moduleDef = do
108 > crudeOutputPid <- spawn outputHandler
109 > crudeInputPid <- spawn inputHandler
110 > return $ Env.fromList (
111 > [
112 > ("crude-output", crudeOutputPid),
113 > ("crude-input", crudeInputPid)
114 > ])
+0
-27
Robin/Env.lhs less more
0 > module Robin.Env where
1
2 > import Robin.IEnv
3 > import Robin.Expr
4
5 Environments
6 ============
7
8 An environment is an alist which associates symbols with
9 values (arbitrary S-expressions).
10
11 > empty = List []
12
13 > insert s@(Symbol _) value env =
14 > append (List [List [s, value]]) env
15
16 Merge two environments to yield a new environment. The merge is
17 left-biased; entries in the left env override those in the right.
18
19 > union (List []) env = env
20 > union (List (binding:rest)) env =
21 > append (List [binding]) (union (List rest) env)
22
23 > fromList [] =
24 > List []
25 > fromList ((id, val):xs) =
26 > append (List [List [(Symbol id), val]]) (fromList xs)
+0
-105
Robin/Eval.lhs less more
0 > module Robin.Eval where
1
2 > import Robin.IEnv
3 > import qualified Robin.Env as Env
4 > import Robin.Expr
5
6 Evaluator
7 =========
8
9 This is written in continuation-passing style.
10
11 Every evaluation function is (and takes) a continuation, which is implemented
12 as a function with signature:
13
14 Expr -> IEnv -> Expr -> (Expr -> IO Expr) -> IO Expr
15
16 (This is actually the `Bif` type from `Robin.Expr`.)
17
18 The first argument is the Robin environment, which is directly visible
19 (and modifiable, during `eval`) by Robin program. The second is the
20 internal context, which contains things like the exception handler, etc.
21
22 When evaluating a symbol, look it up in the environment to obtain a
23 value. Then continue the current continuation with that value.
24
25 > eval :: Bif
26
27 > eval (List []) ienv s@(Symbol _) cc =
28 > raise ienv (errMsg "unbound-identifier" s)
29 > eval (List (b@(List [id@(Symbol _), value]):env)) ienv s@(Symbol _) cc
30 > | id == s = cc value
31 > | otherwise = eval (List env) ienv s cc
32 > eval (List ((List (other:_)):env)) ienv s@(Symbol _) cc =
33 > raise ienv (errMsg "expected-symbol" other)
34 > eval (List (head:tail)) ienv s@(Symbol _) cc =
35 > raise ienv (errMsg "expected-env-entry" head)
36 > eval env ienv s@(Symbol _) cc =
37 > raise ienv (errMsg "expected-env-alist" env)
38
39 Evaluating a list means we must make several evaluations. We
40 evaluate the head to obtain something to apply (which must be a
41 macro, built-in or not.) We then apply the body of the macro,
42 passing it the tail of the list.
43
44 > eval env ienv (List (applierExpr:actuals)) cc = do
45 > eval env ienv applierExpr (\applier ->
46 > case (stripMetadata applier) of
47 > m@(Macro _ _ body) -> do
48 > eval (makeMacroEnv env (List actuals) m) ienv body cc
49 > b@(Builtin _ fun) -> do
50 > fun env ienv (List actuals) cc
51 > other ->
52 > raise ienv (errMsg "inapplicable-object" other))
53
54 Evaluating something with metadata is the same as evaluating the same
55 thing without metadata.
56
57 > eval env ienv (Metadata _ e) cc =
58 > eval env ienv e cc
59
60 Everything else just evaluates to itself. Continue the current
61 continuation with that value.
62
63 > eval env ienv e cc = do
64 > cc e
65
66 Helper functions
67 ----------------
68
69 > errMsg msg term =
70 > List [(Symbol msg), term]
71
72 > makeMacroEnv env actuals m@(Macro closedEnv argList _) =
73 > let
74 > (List [argSelf@(Symbol _), argFormal@(Symbol _),
75 > envFormal@(Symbol _)]) = argList
76 > newEnv = Env.insert argSelf m closedEnv
77 > newEnv' = Env.insert argFormal actuals newEnv
78 > newEnv'' = Env.insert envFormal env newEnv'
79 > in
80 > newEnv''
81
82 Exception Handler
83 -----------------
84
85 > raise :: IEnv Expr -> Expr -> IO Expr
86 > raise ienv expr =
87 > (getExceptionHandler ienv) expr
88
89 Assertions
90 ----------
91
92 > assert pred msg ienv expr cc =
93 > let
94 > expr' = stripMetadata expr
95 > in
96 > case pred expr' of
97 > True -> cc expr'
98 > False -> raise ienv (errMsg msg expr')
99
100 > assertSymbol = assert (isSymbol) "expected-symbol"
101 > assertBoolean = assert (isBoolean) "expected-boolean"
102 > assertList = assert (isList) "expected-list"
103 > assertNumber = assert (isNumber) "expected-number"
104 > assertMacro = assert (isMacro) "expected-macro"
+0
-32
Robin/Exception.lhs less more
0 > module Robin.Exception where
1
2 > import Robin.IEnv
3 > import qualified Robin.Env as Env
4 > import Robin.Expr
5 > import Robin.Eval
6 > import Robin.Core
7
8 Exception
9 =========
10
11 > robinCatch env ienv (List [id@(Symbol _), handler, body]) cc =
12 > let
13 > handlerContinuation = (\errvalue ->
14 > eval (Env.insert id errvalue env) ienv handler cc)
15 > ienv' = setExceptionHandler handlerContinuation ienv
16 > in
17 > eval env ienv' body cc
18 > robinCatch env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
19
20 Module Definition
21 -----------------
22
23 > moduleId = ("exception", 0, 1)
24
25 > moduleDef :: IO Expr
26 > moduleDef =
27 > return $ Env.fromList $ map (\(name,bif) -> (name, Builtin name bif))
28 > [
29 > ("catch", robinCatch),
30 > ("raise", robinRaise)
31 > ]
+0
-107
Robin/Expr.lhs less more
0 > module Robin.Expr where
1
2 > import Data.Char
3 > import Data.Ratio
4
5 > import Control.Concurrent (ThreadId)
6
7 > import Robin.IEnv
8 > import Robin.Chan
9
10 Definitions
11 ===========
12
13 A "bif" is a "built-in function" -- an acronym borrowed from Erlang,
14 though somewhat regrettably, as it's quite lacking as a name.
15
16 > type Bif = Expr -> IEnv Expr -> Expr -> (Expr -> IO Expr) -> IO Expr
17
18 > data Expr = Symbol String
19 > | Boolean Bool
20 > | Number (Ratio Integer)
21 > | Pid ThreadId (Chan Expr)
22 > | Macro Expr Expr Expr
23 > | Builtin String Bif
24 > | List [Expr]
25 > | Metadata (Expr, Expr) Expr
26
27 Equality ignores metadata for now. That's too deep a question for
28 me to think about right now.
29
30 > instance Eq Expr where
31 > (Symbol x) == (Symbol y) = x == y
32 > (Boolean x) == (Boolean y) = x == y
33 > (Number x) == (Number y) = x == y
34 > (Pid x _) == (Pid y _) = x == y
35 > (Macro _ _ _) == (Macro _ _ _) = False
36 > (Builtin x _) == (Builtin y _) = x == y
37 > (List x) == (List y) = x == y
38 > (Metadata _ x) == (Metadata _ y) = x == y
39 > (Metadata _ x) == y = x == y
40 > x == (Metadata _ y) = x == y
41 > _ == _ = False
42
43 > instance Show Expr where
44 > show (Symbol s) = s
45 > show (Boolean True) = "#t"
46 > show (Boolean False) = "#f"
47 > show (Number n) = if
48 > denominator n == 1
49 > then
50 > show $ numerator n
51 > else
52 > ((show $ numerator n) ++
53 > "/" ++ (show $ denominator n))
54 > show (Pid t c) = "(pid " ++ (show t) ++ ")"
55 > show (Macro env args body) = ("(macro " ++ (show args) ++
56 > " " ++ (show body) ++ ")")
57 > show (Builtin name _) = "(builtin " ++ name ++ ")"
58 > show (Metadata _ x) = show x
59 > show (List exprs) = "(" ++ (showl exprs) ++ ")"
60
61 > showl [] = ""
62 > showl [expr] = show expr
63 > showl (expr:exprs) = (show expr) ++ " " ++ (showl exprs)
64
65 Helpers
66 -------
67
68 > append (List x) (List y) =
69 > List (x ++ y)
70
71 Metadata Helpers
72 ----------------
73
74 > hasMetadata metaName (Metadata (k, v) x)
75 > | k == metaName = True
76 > | otherwise = hasMetadata metaName x
77 > hasMetadata _ _ = False
78
79 > getMetadata metaName (Metadata (k, v) x)
80 > | k == metaName = Just v
81 > | otherwise = getMetadata metaName x
82 > getMetadata _ _ = Nothing
83
84 > stripMetadata (Metadata _ x) =
85 > stripMetadata x
86 > stripMetadata x =
87 > x
88
89 Predicates
90 ----------
91
92 > isSymbol (Symbol _) = True
93 > isSymbol _ = False
94
95 > isBoolean (Boolean _) = True
96 > isBoolean _ = False
97
98 > isNumber (Number _) = True
99 > isNumber _ = False
100
101 > isList (List _) = True
102 > isList _ = False
103
104 > isMacro (Macro _ _ _) = True
105 > isMacro (Builtin _ _) = True
106 > isMacro _ = False
+0
-30
Robin/IEnv.lhs less more
0 > module Robin.IEnv where
1
2 > import Control.Concurrent (ThreadId)
3 > import Robin.Chan (Chan)
4
5 Internal Environments
6 =====================
7
8 This is the evaluation environment for Robin which is entirely
9 internal; Robin programs cannot see or modify it directly. Here
10 we keep things like:
11
12 * the continuation which is the current exception handler
13 * the ThreadId and Chan of the current Pid
14 * whether tracing is enabled or not
15
16 > data IEnv t = IEnv (t -> IO t) ThreadId (Chan t)
17
18 > stop expr =
19 > error ("uncaught exception: " ++ show expr)
20
21 > newIEnv eh tid chan =
22 > IEnv eh tid chan
23
24 > getExceptionHandler (IEnv handler _ _) = handler
25 > setExceptionHandler handler (IEnv _ tid chan) =
26 > (IEnv handler tid chan)
27
28 > getThreadId (IEnv _ tid _) = tid
29 > getChannel (IEnv _ _ chan) = chan
+0
-41
Robin/Metadata.lhs less more
0 > module Robin.Metadata where
1
2 > import qualified Robin.Env as Env
3 > import Robin.Expr
4 > import Robin.Eval
5
6 Metadata
7 ========
8
9 > robinWith env ienv (List [metaName, metaValueExpr, expr]) cc =
10 > eval env ienv metaValueExpr (\metaValue ->
11 > eval env ienv expr (\value ->
12 > cc $ Metadata (metaName, metaValue) value))
13 > robinWith env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
14
15 > robinGet env ienv (List [metaNameExpr, expr]) cc =
16 > eval env ienv metaNameExpr (\metaName ->
17 > eval env ienv expr (\value ->
18 > case getMetadata metaName value of
19 > Just v -> cc v
20 > Nothing -> cc $ List []))
21 > robinGet env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
22
23 > hasP env ienv (List [metaName, expr]) cc =
24 > eval env ienv expr (\value ->
25 > cc $ Boolean $ hasMetadata metaName value)
26 > hasP env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
27
28 Module Definition
29 -----------------
30
31 > moduleId = ("metadata", 0, 1)
32
33 > moduleDef :: IO Expr
34 > moduleDef = do
35 > return $ Env.fromList $ map (\(name,bif) -> (name, Builtin name bif))
36 > [
37 > ("with", robinWith),
38 > ("has?", hasP),
39 > ("get", robinGet)
40 > ]
+0
-136
Robin/Module.lhs less more
0 > module Robin.Module where
1
2 > import Data.Ratio
3
4 > import Control.Concurrent (myThreadId)
5 > import System.Directory (doesFileExist)
6
7 > import Robin.Expr
8 > import Robin.Parser
9 > import Robin.Chan
10 > import Robin.IEnv
11 > import qualified Robin.Env as Env
12 > import Robin.Eval
13
14 > import Robin.Builtins (builtinModules)
15
16 Module Loading
17 --------------
18
19 > type ModuleRef = (String, Integer, Integer)
20
21 > data ModuleCache = ModuleCache [String] [String] [ModuleRef] [(ModuleRef, Expr)]
22
23 > mkModuleCache modulePath nonBuiltinModules =
24 > ModuleCache modulePath nonBuiltinModules [] []
25
26 > cacheModule :: ModuleCache -> ModuleRef -> Expr -> ModuleCache
27
28 > cacheModule mc@(ModuleCache mp nbi ip cachedModules) modRef modExpr =
29 > ModuleCache mp nbi ip ((modRef, modExpr):cachedModules)
30
31 > pushModuleInProgress mc@(ModuleCache mp nbi ip c) modRef =
32 > ModuleCache mp nbi (modRef:ip) c
33
34 > popModuleInProgress mc@(ModuleCache mp nbi (_:ip) c) =
35 > ModuleCache mp nbi ip c
36
37 > isModuleInProgress mc@(ModuleCache _ _ ip _) modRef =
38 > modRef `elem` ip
39
40 > qualifyModuleEnv :: Bool -> String -> Expr -> Expr
41
42 > qualifyModuleEnv False _ expr =
43 > expr
44 > qualifyModuleEnv True name (List exprs) =
45 > qualifyModuleEnv' name exprs
46
47 > qualifyModuleEnv' name [] =
48 > List []
49 > qualifyModuleEnv' name ((List [(Symbol id), val]):rest) =
50 > let
51 > List l = qualifyModuleEnv' name rest
52 > in
53 > List ((List [(Symbol (name ++ ":" ++ id)), val]):l)
54
55 > loadModule :: ModuleCache -> ModuleRef -> Bool -> IO (ModuleCache, Expr)
56
57 > loadModule mc@(ModuleCache _ nonBuiltinModules _ cachedModules) modRef@(name, major, minor) qualified =
58 > case lookup modRef cachedModules of
59 > Just expr -> do
60 > return (mc, expr)
61 > Nothing ->
62 > if name `elem` nonBuiltinModules then
63 > loadModuleFromFilesystem mc modRef qualified
64 > else
65 > case lookup modRef builtinModules of
66 > Just builtinModule -> do
67 > expr <- builtinModule
68 > let mc' = cacheModule mc modRef expr
69 > let expr' = qualifyModuleEnv qualified name expr
70 > return (mc', expr')
71 > Nothing ->
72 > loadModuleFromFilesystem mc modRef qualified
73
74 > loadModuleFromFilesystem :: ModuleCache -> ModuleRef -> Bool -> IO (ModuleCache, Expr)
75
76 > loadModuleFromFilesystem mc modRef@(name, major, minor) qualified =
77 > if isModuleInProgress mc modRef then
78 > error ("circular reference in module " ++ name)
79 > else
80 > findAndLoadModuleFromFilesystem mc modRef qualified
81
82 > findAndLoadModuleFromFilesystem mc@(ModuleCache [] _ _ _) modRef@(name, major, minor) _ =
83 > error ("could not locate module file for " ++ (show modRef))
84
85 > findAndLoadModuleFromFilesystem mc@(ModuleCache (dir:dirs) nbi ip c) modRef@(name, major, minor) qualified =
86 > let
87 > filename = dir ++ "/" ++ name ++ "_" ++ (show major) ++ "_" ++ (show minor) ++ ".robin"
88 > in do
89 > exists <- doesFileExist filename
90 > if exists then do
91 > mod <- readFile filename
92 > ast <- return $ insistParse mod
93 > let mc' = pushModuleInProgress mc (name, major, minor)
94 > (mc'', expr) <- evalRobin mc' ast
95 > let expr' = qualifyModuleEnv qualified name expr
96 > let mc''' = popModuleInProgress mc''
97 > -- XXX don't we need to call cacheModule here?
98 > return (mc''', expr')
99 > else
100 > findAndLoadModuleFromFilesystem (ModuleCache dirs nbi ip c) modRef qualified
101
102 > loadModules :: ModuleCache -> Expr -> IO (ModuleCache, Expr)
103
104 > loadModules mc (List exprs) =
105 > loadModules' mc exprs
106
107 > loadModules' mc [] = do
108 > return (mc, Env.empty)
109 > loadModules' mc ((List ((Symbol name):version:qualifiers)):rest) = do
110 > let qualified = case qualifiers of
111 > [(Symbol "*")] -> False
112 > [] -> True
113 > (major, minor) <- parseVersion version
114 > (mc', nextEnv) <- loadModules' mc rest
115 > (mc'', thisEnv) <- loadModule mc' (name, major, minor) qualified
116 > return (mc'', Env.union nextEnv thisEnv)
117
118 > parseVersion (List [(Number major), (Number minor)]) = do
119 > case (denominator major, denominator minor) of
120 > (1, 1) -> return (numerator major, numerator minor)
121 > _ -> error "version number components can't be fractions"
122
123 > evalRobin :: ModuleCache -> Expr -> IO (ModuleCache, Expr)
124
125 > evalRobin mc (List [(Symbol "robin"), version, modules, expr]) = do
126 > (major, minor) <- parseVersion version
127 > case (major, minor) of
128 > (0, 1) -> do
129 > (mc', initialEnv) <- loadModules mc modules
130 > threadId <- myThreadId
131 > chan <- newChan
132 > let ienv = newIEnv (stop) threadId chan
133 > result <- eval initialEnv ienv expr (\x -> do return x)
134 > return (mc', result)
135 > _ -> error ("unsupported language version " ++ show version)
+0
-107
Robin/Parser.lhs less more
0 > module Robin.Parser (parseRobin, insistParse) where
1
2 > import Data.Char
3 > import Data.Ratio
4
5 > import Text.ParserCombinators.Parsec
6
7 > import Robin.Expr
8
9 Parser
10 ======
11
12 The overall grammar of the language is:
13
14 Expr ::= (symbol | number | boolean | "(" {Expr} ["." Expr] ")")
15
16 A symbol is denoted by a string which may contain only alphanumeric
17 characters and certain other characters.
18
19 (TODO: this set of characters is provisional. It might be easier to specify
20 which characters are *not* allowed.)
21
22 > legalSymbolic = (char '*' <|> char '-' <|> char '/' <|>
23 > char '+' <|> char '<' <|> char '>' <|>
24 > char '<' <|> char '=' <|> char '?' <|>
25 > char '_' <|> char '!' <|> char '$' <|>
26 > char ':')
27
28 > symbol = do
29 > c <- (letter <|> legalSymbolic)
30 > cs <- many (alphaNum <|> legalSymbolic)
31 > return (Symbol (c:cs))
32
33 TODO: document these productions.
34
35 > number = do
36 > c <- digit
37 > cs <- many digit
38 > num <- return (read (c:cs) :: Integer)
39 > fraction num <|> return (Number (num % 1))
40
41 > fraction num = do
42 > string "/"
43 > c <- digit
44 > cs <- many digit
45 > denom <- return (read (c:cs) :: Integer)
46 > return (Number (num % denom))
47
48 > boolean = do
49 > string "#"
50 > c <- (char 't' <|> char 'f')
51 > return (if c == 't' then (Boolean True) else (Boolean False))
52
53 > list = do
54 > string "("
55 > spaces
56 > many comment
57 > e <- many expr
58 > string ")"
59 > return $ List e
60
61 > stringSugar = do
62 > string "'"
63 > sentinel <- many $ satisfy (\x -> x /= '\'')
64 > string "'"
65 > contents <- many $ satisfy (\x -> x /= '\'')
66 > string "'"
67 > (try $ stringTail sentinel contents) <|> (stringCont sentinel contents)
68
69 > stringCont sentinel contents = do
70 > contents' <- many $ satisfy (\x -> x /= '\'')
71 > let contents'' = contents ++ "'" ++ contents'
72 > string "'"
73 > (try $ stringTail sentinel contents'') <|> (stringCont sentinel contents'')
74
75 > stringTail sentinel contents = do
76 > string sentinel
77 > string "'"
78 > return $ List (map charToNum contents)
79 > where
80 > charToNum x = Number ((toInteger $ ord x) % 1)
81
82 > comment = do
83 > string ";"
84 > spaces
85 > expr
86
87 The top-level parsing function implements the overall grammar given above.
88 Note that we need to give the type of this parser here -- otherwise the
89 type inferencer freaks out for some reason.
90
91 > expr :: Parser Expr
92 > expr = do
93 > r <- (symbol <|> number <|> boolean <|> list <|> stringSugar)
94 > spaces
95 > many comment
96 > return r
97
98 Convenience functions for parsing Robin programs.
99
100 > parseRobin = parse expr ""
101
102 > insistParse program =
103 > let
104 > Right ast = parseRobin program
105 > in
106 > ast
+0
-39
Robin/Random.lhs less more
0 > module Robin.Random where
1
2 > import Data.Ratio
3 > import Control.Concurrent (myThreadId)
4 > import System.Random (randomRIO)
5
6 > import Robin.Chan
7 > import Robin.Expr
8 > import qualified Robin.Env as Env
9
10 > import Robin.Core (ratFloor)
11 > import Robin.Concurrency (spawn, getChan, respond)
12
13 Random
14 ======
15
16 This module could be written in Robin, but solely for my convenience,
17 it is written in Haskell for now.
18
19 > handler :: Chan Expr -> IO ()
20
21 > handler chan = respond chan [
22 > ("range", \state sender (List [(Number low), (Number high)]) -> do
23 > x <- randomRIO ((ratFloor low), (ratFloor high))
24 > return (state, Number (x % 1)))
25 > ] ()
26
27 Module Definition
28 -----------------
29
30 > moduleId = ("random", 0, 1)
31
32 > moduleDef :: IO Expr
33 > moduleDef = do
34 > randomPid <- spawn handler
35 > return $ Env.fromList (
36 > [
37 > ("random", randomPid)
38 > ])
+0
-97
Robin/Small.lhs less more
0 > module Robin.Small where
1
2 > import qualified Robin.Env as Env
3 > import Robin.Expr
4 > import Robin.Eval
5
6 > import qualified Robin.Core
7
8 Small
9 =====
10
11 This implementation of the `small` module is non-normative. For the
12 normative definition (in Robin), see `small.robin` in the `module` directory
13 of the distribution.
14
15 > literal env ienv (List (expr:_)) cc =
16 > cc expr
17 > literal env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
18
19 > evalAll env ienv [] acc cc =
20 > cc $ List $ reverse acc
21 > evalAll env ienv (head:tail) acc cc =
22 > eval env ienv head (\value ->
23 > evalAll env ienv tail (value:acc) cc)
24
25 > robinList env ienv (List exprs) cc =
26 > evalAll env ienv exprs [] cc
27
28 > robinEnv env ienv (List _) cc =
29 > cc env
30
31 > robinFun closedEnv ienv (List [(List formals), body]) cc = do
32 > cc $ Builtin "<lambda>" fun
33 > where
34 > fun env ienv (List actuals) cc = do
35 > evalArgs formals actuals actuals env ienv (\argEnv ->
36 > eval (Env.union argEnv closedEnv) ienv body cc)
37 > evalArgs [] [] _ _ _ cc = do
38 > cc Env.empty
39 > evalArgs (formal@(Symbol _):formals) (actual:actuals) origActuals env ienv cc = do
40 > eval env ienv actual (\value ->
41 > evalArgs formals actuals origActuals env ienv (\rest ->
42 > cc $ Env.insert formal value rest))
43 > evalArgs _ _ origActuals _ ienv cc = do
44 > raise ienv (errMsg "illegal-arguments" (List origActuals))
45 > robinFun env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
46
47 > choose env ienv (List [(List [(Symbol "else"), branch])]) cc =
48 > eval env ienv branch cc
49 > choose env ienv (List ((List [test, branch]):rest)) cc = do
50 > eval env ienv test (\x ->
51 > case x of
52 > Boolean True ->
53 > eval env ienv branch cc
54 > Boolean False ->
55 > choose env ienv (List rest) cc)
56 > choose env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
57
58 > bind env ienv (List [name@(Symbol _), expr, body]) cc =
59 > eval env ienv expr (\value ->
60 > eval (Env.insert name value env) ienv body cc)
61 > bind env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
62
63 > robinLet env ienv (List ((List bindings):body:_)) cc =
64 > bindAll bindings env ienv (\newEnv ->
65 > eval newEnv ienv body cc)
66 > where
67 > bindAll [] env ienv cc =
68 > cc env
69 > bindAll (List (name@(Symbol _):sexpr:_):rest) env ienv cc =
70 > eval env ienv sexpr (\value ->
71 > bindAll rest (Env.insert name value env) ienv cc)
72 > bindAll (other:rest) env ienv cc =
73 > raise ienv (errMsg "illegal-binding" other)
74 > robinLet env ienv other cc = raise ienv (errMsg "illegal-arguments" other)
75
76 Module Definition
77 -----------------
78
79 > bindings = [
80 > ("literal", literal),
81 > ("list", robinList),
82 > ("bind", bind),
83 > ("env", robinEnv),
84 > ("let", robinLet),
85 > ("choose", choose),
86 > ("fun", robinFun)
87 > ]
88
89 > moduleId = ("small", 0, 1)
90
91 > moduleDef :: IO Expr
92 > moduleDef = do
93 > core <- Robin.Core.moduleDef
94 > let small = Env.fromList $ map (\(name,bif) -> (name, Builtin name bif)) bindings
95 > return $ Env.union core small
96
0 #!/bin/sh
1
2 echo "Building Robin convenience packages..."
3
4 mkdir -p pkg
5 # note that intrinsics-wrappers require small
6 # but they *don't* require fun
7 cat stdlib/literal.robin stdlib/env.robin stdlib/list.robin stdlib/bind.robin \
8 stdlib/let.robin stdlib/choose.robin \
9 stdlib/bind-args.robin > pkg/small.robin
10
11 cat stdlib/if.robin \
12 stdlib/equal-p.robin \
13 stdlib/head.robin stdlib/tail.robin stdlib/prepend.robin stdlib/list-p.robin \
14 stdlib/symbol-p.robin stdlib/macro-p.robin stdlib/number-p.robin \
15 stdlib/subtract.robin stdlib/sign.robin stdlib/macro.robin stdlib/eval.robin \
16 stdlib/raise.robin stdlib/catch.robin > pkg/intrinsics-wrappers.robin
17
18 cat stdlib/empty-p.robin stdlib/map.robin stdlib/fold.robin stdlib/reverse.robin \
19 stdlib/filter.robin stdlib/find.robin stdlib/append.robin stdlib/elem-p.robin \
20 stdlib/length.robin stdlib/index.robin stdlib/take-while.robin stdlib/drop-while.robin \
21 stdlib/first.robin stdlib/rest.robin stdlib/last.robin stdlib/prefix-p.robin \
22 stdlib/flatten.robin stdlib/lookup.robin stdlib/extend.robin stdlib/delete.robin > pkg/list.robin
23
24 cat stdlib/fun.robin > pkg/fun.robin
25
26 cat stdlib/abs.robin stdlib/add.robin stdlib/cmp.robin \
27 stdlib/multiply.robin stdlib/divide.robin \
28 stdlib/remainder.robin > pkg/arith.robin
29
30 cat stdlib/boolean-p.robin \
31 stdlib/not.robin stdlib/and.robin stdlib/or.robin \
32 stdlib/xor.robin > pkg/boolean.robin
33
34 cat stdlib/env-p.robin stdlib/export.robin stdlib/sandbox.robin \
35 stdlib/unbind.robin stdlib/unshadow.robin > pkg/env.robin
36
37 cat stdlib/itoa.robin > pkg/misc.robin
38
39 cat pkg/small.robin \
40 pkg/intrinsics-wrappers.robin \
41 pkg/fun.robin \
42 pkg/boolean.robin \
43 pkg/arith.robin \
44 pkg/list.robin \
45 pkg/env.robin \
46 pkg/misc.robin \
47 > pkg/stdlib.robin
48
49 cat pkg/boolean.robin \
50 pkg/arith.robin \
51 pkg/list.robin \
52 pkg/env.robin \
53 pkg/misc.robin \
54 > "pkg/stdlib-for-robini.robin"
00 #!/bin/sh
11
2 # if you can't install hscurses, uncomment this:
3 # WITHOUT="Console"
4
5 ALL_MODULES="Small Concurrency Exception Metadata Random CrudeIO Console"
6 MODULES=""
7
8 for MODULE in $ALL_MODULES; do
9 ADD_IT=yes
10 for EXCEPT in $WITHOUT; do
11 if [ "${EXCEPT}x" = "${MODULE}x" ]; then
12 ADD_IT=no
13 fi
14 done
15 if [ "${ADD_IT}" = "yes" ]; then
16 MODULES="${MODULES} ${MODULE}"
17 fi
18 done
19
20 cat >Robin/Builtins.hs <<EOF
21 module Robin.Builtins (builtinModules) where
22
23 -- This file was automatically generated by build.sh.
24 -- Edit at your own risk!
25
26 import qualified Robin.Core
27 EOF
28
29 for MODULE in $MODULES; do
30 echo >>Robin/Builtins.hs "import qualified Robin.${MODULE}"
31 done
32
33 cat >>Robin/Builtins.hs <<EOF
34
35 builtinModules = [
36 EOF
37
38 for MODULE in $MODULES; do
39 echo >>Robin/Builtins.hs " (Robin.${MODULE}.moduleId, Robin.${MODULE}.moduleDef),"
40 done
41
42 cat >>Robin/Builtins.hs <<EOF
43 (Robin.Core.moduleId, Robin.Core.moduleDef)
44 ]
45 EOF
46
47 PACKAGES=""
48 for MODULE in $MODULES; do
49 if [ "${MODULE}x" = "Consolex" ]; then
50 PACKAGES="${PACKAGES} -package hscurses"
51 fi
52 done
2 if [ x`which ghc` = x -a x`which runhugs` = x ]; then
3 echo "Neither ghc nor runhugs found on search path."
4 exit 1
5 fi
536
547 mkdir -p bin
55 ghc ${PACKAGES} --make Main.lhs -o bin/robin
56 RESULT=$?
57 rm -f *.o *.hi Robin/*.o Robin/*.hi
58 exit $RESULT
8
9 if [ x`which ghc` = x -o ! x$USE_HUGS = x ]; then
10 # create scripts to run with Hugs
11 cat >bin/robinri <<'EOF'
12 #!/bin/sh
13 THIS=`realpath $0`
14 DIR=`dirname $THIS`/../src
15 cp $DIR/mains/robinri/Main.lhs $DIR/Main.lhs
16 runhugs $DIR/Main.lhs $*
17 EOF
18 chmod 755 bin/robinri
19 cat >bin/whitecap <<'EOF'
20 #!/bin/sh
21 THIS=`realpath $0`
22 DIR=`dirname $THIS`/../src
23 cp $DIR/mains/whitecap/Main.lhs $DIR/Main.lhs
24 runhugs $DIR/Main.lhs $*
25 EOF
26 chmod 755 bin/whitecap
27 else
28 rm -f src/Main.lhs
29 ghc -isrc --make src/mains/robinri/Main.lhs -o bin/robinri || exit 1
30 ghc -isrc --make src/mains/whitecap/Main.lhs -o bin/whitecap || exit 1
31 fi
32
33 ./build-packages.sh
0 #!/bin/sh
1
2 rm -rf src/Robin/*.o src/Robin/*.hi
3 rm -rf src/main/*/*.o src/main/*/*.hi
4 rm -rf pkg/*.robin
+0
-778
doc/Design_Decisions.markdown less more
0 Design Decisions
1 ================
2
3 The design space for programming languages is monstrously large. When you
4 are designing an esolang, you have the luxury of narrowing down the design
5 space, essentially arbitrarily, and focusing on a handful of computational
6 gimmicks, and how they interact.
7
8 In the process of designing a more "real" language, however, you have no
9 such luxury -- ideally, all of your choices should have reasons behind them.
10 There are no "right" decisions, of course, but the choices should be
11 justifiable, given some set of goals.
12
13 Perhaps more importantly, all of the reasons should be coherent, when taken
14 together -- the same justifications should support all of them. There is no
15 point in justifying one decision with "it should be simple to implement
16 instead of simple to program in", and another with just the opposite -- the
17 end result will be a hodge-podge, and we might as well have just made our
18 choices arbitrarily, without any justification at all.
19
20 Having had to make the design decisions behind Robin, I will try to document
21 the major ones here, and the reasons behind them. Of course, since Robin's
22 design is still under development, many of these are subject to change.
23
24 Meta-Design
25 -----------
26
27 #### Should Robin be rigorously specified?
28
29 Decision: Absolutely.
30
31 A rigorous specification of a language allows two things:
32
33 * Proofs of properties of programs in the language. Without a formal
34 semantics, this just isn't possible. It should also be standardized
35 (that is, there should be an "official" definition): it's all well and
36 good to independently define "a formal semantics" for some programming
37 language, but if different programmers are using different formal
38 semantics for the same language, they can't exchange their proofs.
39
40 * Commodification of implementations of the language. Allowing
41 implementors to independently implement the same language leads to a
42 "marketplace" of implementations, which (under prevailing economic
43 theories, anyway) leads to higher quality implementations through
44 competition.
45
46 #### Should Robin's core language have a simple definition?
47
48 Decision: Yes.
49
50 Keeping the definition simple contributes to the same commodification goal
51 listed above: it lowers the barriers to implementation.
52
53 Providing a lot of useful things in the core does make some things handier
54 for the programmer, but it does increase the effort to implement the
55 langage (think of all the nooks and crannies of Perl.) Instead, all these
56 handy things should be packages in modules, which need not always be
57 imported or used.
58
59 Approaching this naively can lead to inefficiencies, however, as more
60 advanced functionalities must be built up from simpler functionalities,
61 and the "sufficiently clever compiler" that can optimize these is hard to
62 come by. So, if there are any measures we can take to mitigate this
63 effect, without destroying simplicity -- we should investigate them.
64
65 #### Should Robin be defined with denotational semantics?
66
67 Decision: No.
68
69 It's inaccessible to most programmers, and it is essentially just
70 another programming language, which is itself not perfectly well
71 standardized.
72
73 A much better choice is the programming language Haskell. It is
74 quite well defined, quite close to denotational semantics (in its
75 pure form, anyway), and above all, executable -- leading immediately
76 to a usable reference interpreter.
77
78 #### Should Robin be defined using multiple definition languages?
79
80 Decision: Yes.
81
82 The method of description should employ at least two descriptions in two
83 language-describing languages. This way, a form of "error-detecting
84 code" applies: each description can be checked for consistency against the
85 other. (Using three languages would permit a form of "error-correcting
86 code": whichever behavior is in at least two of the descriptions is
87 considered official, and the third is considered erroneous. But this is
88 possibly too burdensome in practice.)
89
90 Given Haskell as one of the definition lanaguges, the logical choice here
91 is Literate Haskell, with each part of the Haskell definition accompanied
92 by a definition in (relatively formal) English.
93
94 #### Should the language also be defined with conformancy tests?
95
96 Decision: Yes.
97
98 Of course, it's very difficult to compose tests which actually define a
99 language. You can't effectively test that such-and-such a program leads
100 to an infinite loop, and you can't effectively test that such-and-such a
101 program has the same behaviour on *any* of an infinite possible set of
102 inputs.
103
104 But, you can write tests that detect a finite number of points where an
105 erroneous implementation fails to meet the definition. And, you can
106 execute these tests on a computer -- in the process of developing a new
107 implementation, this can help a lot. And, this brings the definition
108 closer to being "in triplicate" and thus having some properties of an
109 error-corrcting code. So, conformancy tests should definitely be part of
110 the language's documentation.
111
112 Design Proper
113 -------------
114
115 #### Should Robin be a general-purpose language?
116
117 Decision: Yes.
118
119 Not much to say about this. A general-purpose language with a module
120 system, not to mention macros, can be customized for specific purposes.
121 (We need to do more investigation into how "teleological contexts" and
122 metadata on values can be leveraged for such purposes.)
123
124 #### Should Robin's syntax be based on S-expressions?
125
126 Decision: Yes -- but it should not be the *only* syntax.
127
128 Robin, as it stands currently, is a "sugar-free" language. Programs and
129 modules are represented concretely as S-expressions, which typically map
130 directly to the AST (abstract syntax tree) used by the implementation.
131
132 Research in linguistics suggests there is such a thing as too much
133 regularity in a language for human comfort. All spoken languages have
134 some irregularity in them. When constructed languages such as Esperanto
135 are taught as native languages to children, they tend to be "irregularized"
136 as they are acquired. Perhaps the human mind needs these irregularities as
137 "handles" to better grasp the ways to express concepts, or perhaps it uses
138 them as "checksums" for error correction and disambiguation -- but these
139 are just pet theories. Whatever the reason is, it happens.
140
141 My point is, S-expression-based languages are certainly a formal instance
142 of language structure which is "too regular for comfort", so programming
143 in Robin (or Scheme, or Lisp) often tends to be somewhat brutal (especially
144 without editor support to match parentheses for you.)
145
146 However, mathematically and in software engineering, this regularity
147 provides immense benefits, because it both makes the structure of
148 the language simple, and thus easy to define and analyze, and makes the
149 language very expressive -- the ease of writing code that works on code
150 makes it possible to create very flexible and coherent (I daresay
151 "powerful") abstractions. So, Robin errs on the side of this benefit.
152
153 However, there is no reason that Robin should fixate on this syntax.
154 It is important not to neglect usability, and, although one has not yet
155 been devised, there is no reason that Robin cannot have other, more "humane"
156 alternate syntaxes which are easier to read and write.
157
158 A sugared "humane" syntax might look like the following.
159
160 robin 1.0
161 import small 1.0
162
163 pi = 3.14159
164
165 fac(x) =
166 if x <= 1 then 1 else
167 r = fac(x - 1)
168 r * x
169 end
170
171 fac(7) * pi
172
173 It would be translated by a pre-processing step to something like:
174
175 (robin (1 . 0) (small (1 . 0))
176 (bind pi 314159/100000
177 (bind fac (lambda (self X)
178 (if (<= x 1)
179 1
180 (bind r (self self (- x 1)) (* r x))))
181 (* (fac fac 7) pi))))
182
183 #### What should be in the core?
184
185 Decision: A semantically minimal set of macros.
186
187 I went back and forth before deciding what should be in the core and
188 why. One possibility was to make it the same as Pixley. But macros
189 would be added to it, and macros would need to be in the core (as they
190 can't be written directly in Pixley), and once you have macros, a lot
191 of the Pixley functions, like `let*` and `cond`, *can* be written in
192 the language. So, should they remain in the core?
193
194 I decided no: the core would be simpler to implement and analyze
195 without them.
196
197 The only place where I waver on this currently is `fun`. While `fun`
198 *can* be defined as a macro, it is so basic to writing modules in
199 Robin, that it is very tempting to place it in the core. (The version
200 defined as a macro is very inefficient, but of course the `small`
201 module need not be implemented in Robin itself.)
202
203 #### Should all programs be contained in some kind of header form?
204
205 Decision: Yes.
206
207 We want to be able to quickly identify what S-expressions are
208 Robin programs, and what aren't, especially if we're using some of the
209 same identifiers as other languages, like Scheme. Also, this is a
210 good place to specify the version of Robin in use, and a good place
211 to import required modules.
212
213 An alternative idea was some kind of meta-format called "Parts":
214
215 (parts (import (robin 1 0) ...)
216
217 But "Parts" would not establish the deep semantics of the language
218 (reduction order, etc.) And subsequent imports might rely (heavily)
219 on those semantics. Meaning, imports would have to import fundamental
220 semantics, and imports would depend on that being imported first,
221 and, the result is just ugly.
222
223 #### Should you have to import the core?
224
225 Decision: Yes.
226
227 This is actually a special case of a more general design decision,
228 namely:
229
230 #### Should modules be fine-grained?
231
232 Decision: Yes.
233
234 If modules are fine-grained, and only a few are truly required, the task
235 of implementing (or porting) the language is much simpler.
236
237 This applies as well to architectures that don't support all functions
238 in all modules. For example, clockless systems won't have a way to
239 retrieve the current time of day. *But*, such systems would still be
240 capable of manipulate date and time values. Therefore, those two sets
241 of functions, though closely related, should not be bundled into the
242 same module.
243
244 It's true that it's annoying for the programmer to remember which
245 module a function is in. For this reason, we can have "umbrella modules"
246 which simply re-export all the functions in a large set of standard
247 modules -- assuming there are no name conflicts amongst them.
248
249 More philosophically: if something is part of the core semantics of
250 the language (like error codes,) should it be put in a module? Largely
251 I've been able to arrange things to avoid this issue. For example, if
252 `head` fails, it raises an exception if the implementation supports
253 exceptions, otherwise it just aborts execution. But, when when support
254 for exceptions exists, if a raised exception is not caught, execution
255 is aborted -- so the behaviour is compatible. However, there are
256 potentially other instances of "semantics for this are in the core, but
257 you have to import this module to get at thim" -- I've seen them in
258 other languages, and when I remember or re-find an example of it, I'll
259 add it here.
260
261 #### Should importing be done in the header, or by a function?
262
263 Decision: In the header.
264 Chance of changing: Non-zero.
265
266 Importing modules in the header is a form of statically declaring the
267 dependencies of a program; if one of the modules isn't available on
268 some system, it can instantly say "no, I can't run this."
269
270 If there was instead a function to import modules, such a system would
271 need to statically analyze the program to see if dependencies are met
272 (see Python's `setuptools`). When it can't figure that out exactly,
273 which is inevitable, the program will break at some arbitrary point
274 during execution.
275
276 Also, importing via a function would require that the function to do
277 the importing would be exported before everything else; in other words,
278 `(robin (1 0) ...)` would need to export one function, `import`. This
279 is slightly un-orthogonal.
280
281 The downside of statically declaring the modules in the header is that
282 you might want to write a program which is somewhat flexible: if a
283 particular module is available, it will take advantage of it, but if not,
284 it will fall back to something perhaps less optimal but still usable.
285 You can't do that in the current regime.
286
287 However, there may be better ways to think about this, and they go back
288 to ideas I had about Robin when it was in my mind more like an operating
289 system. The issue is often not the availability of a module but rather
290 the availability of a resource; modules are, at best, definitions,
291 rather than suppliers, of resources. But, I will have to think about
292 this more.
293
294 #### Should function names follow in the Lisp/Scheme tradition?
295
296 Decision: No.
297
298 It's good to have roots, but there are limits.
299
300 Lisp/Scheme names posess a lot of awfulness due to their legacy.
301 `cdr` absolutely sucks as a name. Unfortunately, things like `tail`
302 and `snd` aren't standard replacements for it, yet. `lambda` is
303 less offensive, but only because it's a widespread standard; there is
304 nothing except Church's work that ties the Greek letter lambda to
305 the idea of a function, and even that is, if you believe the folklore,
306 mainly due to typesetting limitations he encountered in publishing.
307
308 Just because programmers are familiar with a notation or concept is not
309 enough of a reason to incorporate it into the language's foundation. At
310 the same time, we'd obviously prefer not to alienate programmers
311 completely (that's what esolangs are for!)
312
313 If the programmer really wants Lisp/Scheme names, they can always
314 define them in a "compatibility module". (In fact, I should probably
315 anticipate this, and accomodate it with an established convention.)
316
317 #### Should `#t` and `#f` be Church booleans?
318
319 Decision: No.
320
321 While it's tempting in that it would allow us to not have `if` in the
322 core, it just moves that complexity from `if`, a built-in macro, to
323 the evaluator and/or type system. Having an explicit, separate `if`
324 lets `#t` and `#f` be more like plain symbols. In fact, one day, they
325 might be classified as such -- if I can grapple other design decisions
326 in the way of that.
327
328 #### Should Robin allow improper lists?
329
330 Decision: No.
331
332 Drawing directly from the Lisp/Scheme tradition, and being supported by the
333 idea that the core semantics should admit as much "goo" as possible ("it's
334 not a language so much as it's a building material"), with static analysis,
335 if desired, being layered on top of that, improper lists were originally
336 allowed in Robin.
337
338 However, there are several points that can be made against them, so they
339 were removed from the language.
340
341 * We may want to base everything on "goo", but we should want clean "goo".
342
343 * You can always simulate an improper list with a proper list with some
344 kind of marker term at the end.
345
346 * The very name "improper" should be a big hint that these constructs are
347 not clean. (However, this argument could be regarded as sophistry.)
348
349 * Various functions in the `list` module currently have slightly different
350 behaviour on proper versus improper lists. Proper lists only would make
351 them more orthogonal.
352
353 * Improper lists maybe have a place in history; when resources like memory
354 were scarce, they were a way of saving a cons cell. However, this now
355 goes against treating resources as not scarce in order to have a more
356 abstract and elegant description of programs.
357
358 * When you have both proper and improper lists, `list?` is O(n); with only
359 proper lists, `list?` is O(1), basically the same as `pair? or null?`.
360
361 #### Should we require lists in syntax where they aren't strictly necessary?
362
363 Decision: Yes.
364
365 What do I even mean by this? Well, for example, Scheme's `let*` requires
366 that you put all the bindings in a list:
367
368 (let* ((a 1)
369 (b 2)
370 (c 3))
371 (foo a b c))
372
373 That intermediate list isn't really necessary; the implementation of `let*`
374 could just treat the last term as the expression to be evaluated in the new
375 environment:
376
377 (let* (a 1)
378 (b 2)
379 (c 3)
380 (foo a b c))
381
382 This is good under the theory "the fewer parentheses, the better", and this
383 is not a bad theory. Also, it is perhaps less efficient (because the
384 implementation must look ahead to see if something is a binding or not), but
385 again, resources should not be considered scarce; it can always be converted
386 internally to something more efficient.
387
388 But, Robin will one day have a more humane syntax, so that programmers won't
389 have to deal with these forms unless they want to. The intermediate list
390 could also be seen as more orthogonal to the semantics (you really are
391 working with a list of bindings, and you shouldn't overload the meanings of
392 things in the list.)
393
394 So, Robin's `let` does have an intermediate list. (On the other hand,
395 `bind` doesn't need a list at all, obviating the issue.) Following suit,
396 the syntax for importing modules uses a list to contain the module specifiers
397 (although it did not originally.)
398
399 As a corollary to this, `choose` should probably have a list of conditions,
400 and should not need an `else` branch -- the "body" of the `choose` should
401 be the "else".
402
403 #### Should the language define static analyses?
404
405 Decision: No, but it should accomodate them.
406
407 This is a pretty subtle issue, which is explained more fully in the
408 Static Analysis document. But in short, to work towards the goal of
409 keeping the language simple, we want to move things out of it, to modules
410 and/or to implementation issues (such as configuration files), and one
411 of the things we can move out is static analysis.
412
413 At the same time, the language should be designed to accomodate static
414 analyzers that are built on top of it, and some of those static analyzers
415 should be standard.
416
417 A language can define a type system without specifying that types should
418 be checked statically. However, if no thought is put into how easily the
419 types of a program can be statically analyzed, this raises barriers to
420 actually doing it. Static analyzers in the world of scripting languages
421 in particular are often an afterthought, and we want to try to minimize
422 that effect.
423
424 #### How should serializability be handled?
425
426 Decision: ...
427
428 OK, so: one reason to choose an S-expression based syntax is that terms
429 so represented are, for the most part, "trivially serializable", because
430 many forms simply evaluate to themselves, and when they don't, they can
431 be wrapped in `literal`.
432
433 This is useful because, where-ever values are serialized (disk files,
434 messages between nodes, etc.,) they look just like they would in a program
435 text.
436
437 However, there is an inherent tension between concrete representations and
438 abstract types.
439
440 In the following, _erroneous access_ means transformations of data that
441 result in a non-conformant structure. _Interchangeability_ means only
442 allowing a set of operations whose implementations can be changed.
443
444 Concrete representations serialize trivially, and can be pattern-matched,
445 but they do not prevent erroneous access, nor support interchangeability.
446
447 Abstract types prevent erroneous access and support interchangeability,
448 but they do not serialize trivially, nor can they be pattern-matched.
449
450 (Abstract types are also traditionally desirable because they allow
451 optimizations, but since performance is a non-goal of Robin, we won't
452 discuss that here.)
453
454 A solution is to ensure every abstract type has two operations, `to-repr`
455 and `from-repr`, which convert the abstract value into a concrete
456 representation and vice-versa. `to-repr` should be deterministic; for all
457 values _v_ of some abstract type _t_, all implementations of _t_ should
458 produce the same value for `to-repr` _v_. For example, an abstract type
459 of dictionaries might have as its representation a sorted, non-redundant
460 alist.
461
462 This permits serialization, pattern-matching, equality testing, etc.,
463 simply by (implicitly) calling `to-repr` on the value first.
464
465 These two functions should be round-trippable, in that for all _v_,
466 `(from-repr (to-repr v))` = v. Some information may be lost, but
467 such information should not be critical information (e.g. caching most
468 recently used values for the sake of performance, etc.)
469
470 You can still try to perform erroneous access by converting the abstract
471 value to a concrete representation, mucking with the representation, then
472 converting it back to the abstract value. However, the representation
473 should be defined at the level of properties of the abstraction, and trying
474 to convert it to an abstract value should raise an exception if those
475 properties do not hold (i.e. if the concrete value is "corrupt".)
476
477 We could treat macro values as abstract values. The representation of a
478 macro value is its definition, plus any values that might be closed over in
479 it (represented as a `let` wrapping the definition.) But there is one
480 desired property that does not hold -- the representation of a macro is not
481 deterministic; there are an infinite number of equivalent representations of
482 any macro, and no effective procedure to select the "simplest" one (or any
483 other way to effectively order possible representations.)
484
485 We could treat pids as abstract values. One might hope to do information
486 hiding with pids; you should be unable to send a message to a process unless
487 you got its pid from it or its parent (perhaps indirectly). However,
488 `from-repr` lets you make up pids "from scratch" (from arbitrary concrete
489 representations) and even if the pid structures contains an obscure
490 fingerprint or the like, you might accidentally hit upon an existing pid.
491
492 However, maybe that is not so bad; we could call it the "how did you get
493 this phone number" problem. Even if pids are abstract, a process can't
494 really rely on its parent not somehow sharing its pid with some process it
495 knows nothing about, barring some really involved proofs. And, even with an
496 abstract pid, you can't guarantee e.g. that sending it a message has some
497 meaning; the process might have died, maybe long enough ago that the pid was
498 recycled and a new process lives there now. (Though, of course, we should
499 take measures to reduce the chances of all these things.)
500
501 Can we implement abstract values as functions? Take a queue for instance:
502
503 (bind q (queue:empty)
504 (((q enqueue 33) enqueue 66) deqpeek))
505
506 ...should evaluate to 33. This is pretty good. What would the
507 implementation look like?
508
509 (bind empty
510 (bind contents ()
511 (macro (self args env)
512 ; if args#0 is 'enqueue', return a macro like 'self'
513 ; closed over (pair args#1 contents)
514 ; else if args#0 is 'deqpeek', return (list:last contents)
515 )
516
517 But it looks like this might involve mucking with the closed-over
518 environment of the macro -- which we could make possible. But I'm not
519 sure we want to. Anyway, this macro would also need to implement the
520 operations `(q to-repr)` and `(q from-repr (list 1 2 3))`. The latter
521 is actually a "class method" and doesn't need to be on an existing
522 instance; but that is its own, fairly involved design decision.
523
524 Also, Robin potentially has the ability to use different implementations
525 (representations) of the same abstract data type in different modules,
526 independent of the program: the module configuration file could point
527 one module to an alist-backed dictionary data type, and another module
528 at a hash-table-backed dictionary data type. Those two modules ought to
529 still be able to pass objects of the dictionary data type back and forth
530 to each other.
531
532 #### Should environments be abstract data types?
533
534 Decision: Currently they aren't, but they should be.
535
536 Currently, all macros in the standard modules accept and return alist
537 representations of environments. But there are mismatches between this
538 representation, and what environments actually support. There can be
539 multiple entries for the same key in an alist, and alists expose an order
540 to their entries, neither of which is a necessity of environments. There
541 are potentially many ways to represent an environment. So, environments
542 should be encapsulated in an abstract data type that supports the
543 operations `lookup` and `extend`.
544
545 #### Should strings be abstract data types?
546
547 Decision: Again, currently they aren't, but they should be.
548
549 Again, there are multiple possible ways to represent a string: a naive
550 list of integers (representing characters) suffices for many applications,
551 but other applications may benefit from using a "rope" representation, or
552 some other representation.
553
554 #### Should there be a distinction between processes and devices?
555
556 Decision: No.
557
558 I backtracked on this one.
559
560 It's tempting to unify the two, and say that there are only devices,
561 and that every concurrent process you spawn is a device of some sort.
562
563 The argument against unifying the two is that devices represent resources
564 beyond just cycles and memory, while you can have a "compute" process
565 which just uses cycles and memory. It doesn't need to be acquired, or
566 released, or registered for access by some other, anonymous program.
567
568 But that's not quite true. It's not "just cycles and memory"; cycles
569 and memory, and the privilege to create a process that uses them,
570 constitute a device that must be acquired (started), released (stopped),
571 and possibly even registered for access, if the notion of IPC involves
572 sending messages from process to process.
573
574 So I think we need a concept of a "processing device". Normally this would
575 be a "virtual processor" (backed by an OS process or other simulated
576 concurrency.)
577
578 But also -- other devices may or may not acquire their own virtual processor,
579 or use an existing virtual processor instead. These two options map to
580 having each service in its own process (an Erlang ideal) and to having a
581 library of functions that run "inline" (in the caller's thread -- a C reality.)
582
583 It would be great if devices could be contrived so as to be flexible on that
584 point.
585
586 Starting up a virtual processor to run a Robin program is a bootstrapping
587 issue. You generally wouldn't have to write any code to acquire the initial
588 processor device -- I mean you couldn't: what started the virtual processor
589 that *that* code was running on? This would instead be the responsibility of
590 Robin's kernel, which is, conceptually, a black box in this regard. But you
591 could start *another* processor device, in your code, to run your code --
592 basically, to spawn a process.
593
594 See also the "Programming Languages vs. Operating Systems" section I just
595 added to the Practical Matters doc (though it doesn't really belong there.)
596
597 #### Should the `random` facility be a device?
598
599 Decision: No.
600
601 Following the decision immediately above, and the decision to have
602 fine-grained modules -- the `random` module itself is simply doing
603 computation (generating ever-more pseudo-random numbers from a seed.)
604 *However*, it may be seeded with a source of entropy from the system --
605 which implies that there should, indeed, be an `entropy` device.
606
607 But considering naming conventions -- possibly, for the same reason,
608 the `random` module should be called `pseudo-random` or similar. And
609 `entropy` might likewise be better named `random`. Not sure.
610
611 #### Should all messaging transactions be synchronous?
612
613 Decision: It's tempting, but I'm starting to think it's not practical.
614
615 While the Erlang paradigm for message-passing is very simple -- just
616 `Pid ! msg` and you've sent a message -- it's also very low-level. For
617 Erlang/OTP, things like `gen_server` are built on top of this, using
618 sets of functions to abstract away the details. Robin does something
619 similar with `call!` and `respond!`. This lets you write code where you
620 can be reasonably sure that the other processes you are sending messages
621 to are in the state that you expect.
622
623 Being able to send a message to a process and not expect a reply does
624 let you write potentially more efficient code; you don't have to wait for
625 your message to be acknowledged. But combining this with `call!`/`respond!`
626 can lead to complex patterns of communication, where it is difficult to
627 reason about whether the other processes are in the state you expect.
628 (If the server process uses `respond!`, what should it do about messages
629 that don't require an acknowledgement? How sophisticated does `respond!`
630 need to be?)
631
632 Also, requiring synchronous communication between processes does not
633 preclude asynchonous processing -- it's just that your "start doing this"
634 message needs to be acknowledged by the other process, and your process
635 needs to wait for that acknowledgement. The activity itself still goes
636 on independent of the current process.
637
638 Also, race conditions are among the hardest bugs to detect, isolate and
639 fix, and unacknowledged asynchronous messages probably lead to them (though
640 not so much as shared updatable storage leads to them.) Doing what we can
641 to encourage programmers to avoid race conditions in design is probably
642 called for.
643
644 However... the problem is that if all messaging is synchronous, you lose
645 one of the main benefits of messaging, which is (this sounds tautological)
646 asynchronicity. If you always need to wait for another process to confirm
647 that it got your message, you can't do anything else in the meantime.
648
649 Perhaps there is a way around this. I'll need to come up with some
650 examples and write them down here.
651
652 #### Should all messaging consist of message structures (with envelopes)?
653
654 Decision: Again, not sure, leaning towards yes.
655
656 Again, `Pid ! Msg` where `Msg` is anything is very simple, but again, it
657 is very low-level. It is useful to have metadata about the message, like
658 which process sent it, and when. But I need to think about this more.
659
660 #### Should symbols be atomic?
661
662 Decision: Currently, yes.
663 Chance of changing: High.
664
665 In the Lisp tradition, symbols are "atomic" -- you can't take them apart,
666 you can't (always) create new ones at runtime, they have no intrinsic order,
667 and so forth. Beyond a certain conceptual cleanliness, this has the
668 advantage that each symbol can be associated with, and after a compilation
669 process, can be replaced by, a small integer of fixed size. This is good
670 for efficiency, but efficiency is not what we're going for here. Later
671 languages in the Lisp tradition introduced things like `gensym` to create
672 new symbols, and a separate string type and operations like `symbol->string`
673 and `string->symbol`.
674
675 Being able to create new symbols during runtime is very useful in program
676 transformation, and for our purposes, should outweigh any efficiency gains
677 from having a fixed set of atomic symbols.
678
679 Also, if two nodes of a distributed Robin system are exchanging terms
680 produced by software the other knows-not-what, they *must* be prepared to see
681 symbols that they don't already know.
682
683 In Robin, we can regard having a fixed, static set of symbols in use in a
684 program as a *luxury*; if a static analysis reveals that you can "afford" it,
685 (i.e. that you're not creating new ones at runtime and so forth,) a compiler
686 can replace the symbols with small integers for efficiency in your case.
687
688 ### Should symbols and strings be different types?
689
690 Decision: Currently, yes.
691 Chance of changing: High.
692
693 Given Scheme's approach to the above (`symbol->string` and `string->symbol`),
694 let's ask ourselves: what's *really* the difference between the two types?
695 In an essentially purely functional language like Robin, both symbols and
696 strings are immutable. In implementations where strings are "intern'ed",
697 this is not so different from inserting symbols in a symbol table. And,
698 in a language like Robin where equality and identity are identical,
699 `(equal? "foo" "foo")` should evaluate to true whether the two strings are
700 two copies of the same text, or two pointers to the same single text.
701
702 This all points to the idea that symbols and strings should be unified; or
703 rather, that there should be no symbols, only strings. A traditional
704 symbol literal, then, should be one syntax for specifying a string; and on
705 the other hand, you ought to be able to say things like
706
707 (''let'' ((''( ('' 1)) ('X'+'X' 1 ''( (''))
708
709 with impunity.
710
711 ### Should macro-type values even exist?
712
713 Decision: Currently, yes.
714 Chance of changing: non-zero.
715
716 PicoLisp has some good ideas here (although identifying numbers with
717 machine addresses of functions strikes me as going way too far.) Robin
718 has already wholeheartedly adopted the macro (which treats its arguments
719 as unevaluated terms) as a core abstraction, and builds functions on top
720 of them. However, it could get even closer to PicoLisp's paradigm here,
721 and not treat macros as their own data type. Instead, they are simply
722 terms of a certain form which, when they appear as the first element of
723 a list being evaluated, are expanded through substitution.
724
725 One reason to do this is that serializing, or otherwise depicting, a
726 macro is somewhat problematic. We can use the definition that was used
727 to define the macro, but it's awkward.
728
729 Here's an example of what would be different if there were no macro-type
730 values. Take the following code:
731
732 (bind dup (macro (self args env)
733 (bind a (eval env (head args))
734 (list a a)))
735 (dup (literal foo)))
736
737 Currently, this would be evaluated as follows. The `(macro ...)` term
738 evaluates to a value of macro type, and this value is bound to the name
739 `dup` in a new environment. The `(dup ...)` term is evaluated, `dup` is
740 looked up in the environment to find that value of macro type, and that
741 macro definition is evaluated with the given arguments.
742
743 Here is what would happen if macros were just terms. First, the code
744 would need to be written something more like:
745
746 (bind dup (literal (macro (self args env)
747 (bind a (eval env (head args))
748 (list a a))))
749 (dup (literal foo)))
750
751 Then, during evaluation, `dup` is bound to a literal term in a new
752 environment. The `(dup ...)` term is evaluated, and `dup` is looked up
753 in the environment to find a literal term. That term is virtually
754 inserted in the term being evaluated:
755
756 ((macro (self args env)
757 (bind a (eval env (head args))
758 (list a a))) (literal foo))
759
760 This term is examined, and it is found to conform to a "macro evaluation
761 form"; it is virtually expanded thusly:
762
763 (bind self (macro (self args env)
764 (bind a (eval env (head args))
765 (list a a)))
766 (bind args (literal (literal foo))
767 (bind env (env)
768 (bind a (eval env (head args))
769 (list a a)))))
770
771 Although the `(env)` may be fudging it a bit, this evaluation process is
772 now rather nicely depictable in Robin (although an implementation would
773 almost certainly make the new environment itself, without evaluating `bind`
774 to do so.)
775
776 This still doesn't help much with dealing with the same issues surrounding
777 built-in macros, though.
+0
-626
doc/Fundamental_Semantics.markdown less more
0 Robin
1 =====
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 The document defines the fundamental semantics of Robin.
6
7 Fundamentals
8 ------------
9
10 In the following, words in ALL-CAPS indicate variables.
11
12 Every Robin program is contained in a `robin` form. It has the syntax:
13
14 (robin VERSION (MODULE-SPEC ...) EXPRESSION)
15
16 The `VERSION` gives the version of the Robin semantics in use. It has
17 the syntax:
18
19 (NAT NAT)
20
21 ...where `NAT` is a natural number (an integer not less than zero.)
22 More on versions later; the only version of Robin that currently
23 exists is 0.1 (aka `(0 1)`), so we'll use that.
24
25 The list of `MODULE-SPEC`s may be empty. So, without further ado,
26 here is one of the simplest Robin programs one can write:
27
28 | (robin (0 1) () #t)
29 = #t
30
31 Versioning
32 ----------
33
34 The rules for version numbering follow [semantic versioning][].
35 i.e., If you ask for version 2.1, you may get version 2.2, 2.3,
36 etc; the assumption is that each of these will implement everything
37 2.1 does, in a fashion which is backwards-compatible with version 2.1.
38 You will not get 3.x, because it is assumed 3.x exports a different
39 interface from 2.x; nor will you get 1.x, for the same reason. In the
40 0.x series, nothing is considered backwards-compatible with anything
41 else; if you ask for 0.2, you will not get 0.1.
42
43 Backwards-compatibility does not include functionality which is deemed
44 to be a bug. Programs which rely on bugs are themselves buggy, and
45 when the bug is fixed, they need to be fixed as well. There is probably
46 a grey area where it's unclear if something is a bug or a feature, but
47 my hope is that ample documentation, tests, and literate specifications
48 where-ever possible will reduce the number of functionalities which
49 fall into this grey area.
50
51 [semantic versioning]: http://semver.org/
52
53 An implementation might, obviously, provide or not provide any
54 particular version of the language.
55
56 | (robin (0 781) () #t)
57 ? unsupported language version (0 781)
58
59 The Robin semantics brought in by the version number in the `robin`
60 form include things like datatypes and evaluation rules, and are not
61 likely to change frequently. They do not include identifiers. These
62 are supplied only by modules, and each module has its own version.
63
64 Module Import
65 -------------
66
67 Each `MODULE-SPEC` specifies a module, and a minimum required
68 version, to import. It optionally contains a list of qualifiers which
69 constrain how to import the module. The identifiers exported by the
70 module will be available to the `EXPRESSION`.
71
72 The module need not be implemented in Robin.
73
74 If it is implemented in Robin, when it is imported, the definition of
75 the module in Robin is evaluated to obtain a binding alist (see
76 "Conventional Data Types", below, for more details on this data structure.)
77 The bindings therein are added to the environment in which the
78 `EXPRESSION` will be evaluated. They shadow any previous bindings with
79 the same names.
80
81 How the implementation locates any module for loading is *completely*
82 implementation-dependent. In Robin, we consider this an implementation-
83 level detail of which the language is blissfully unaware. This decouples
84 the language definition from the details of the operating system, such
85 as what a "file" is or where they may be loaded from the "file system".
86
87 A `MODULE-SPEC` has the syntax:
88
89 (MODULE-NAME VERSION [QUALIFIER...])
90
91 It is possible for the list of `MODULE-SPEC`s to be empty, but then
92 no identifiers will be defined, and you will only be able to state
93 the most basic of `EXPRESSION`s, such as ones consisting of a single
94 literal of one of the built-in datatypes that can be expressed directly.
95
96 Here is an example of importing a module (but not doing anything
97 with it.)
98
99 | (robin (0 1) ((core (0 1))) #t)
100 = #t
101
102 A particular version of a module might, naturally, not be available.
103
104 | (robin (0 1) ((small (0 781))) #t)
105 ? could not locate module
106
107 And a particular module might, naturally, not even be available.
108
109 | (robin (0 1) ((gzgptzgztxxky (1 0))) #t)
110 ? could not locate module
111
112 And a particular version of a module may rely on a particular version
113 of the fundamental semantics, so some combinations may not make sense.
114 For example, if `small` 3.0 relies on Robin 2.0, this will fail
115 (with a more appropriate error message like "Robin 2.0 required"):
116
117 | (robin (1 0) ((small (3 0))) #t)
118 ? unsupported language version (1 0)
119
120 By default, identifiers are imported qualified.
121
122 | (robin (0 1) ((core (0 1)))
123 | (core:number? 3/5))
124 = #t
125
126 | (robin (0 1) ((core (0 1)))
127 | (number? 3/5))
128 ? uncaught exception: (unbound-identifier number?)
129
130 The `*` qualifier imports a module unqualified.
131
132 | (robin (0 1) ((core (0 1) *))
133 | (number? 3/5))
134 = #t
135
136 | (robin (0 1) ((core (0 1) *))
137 | (core:number? 3/5))
138 ? uncaught exception: (unbound-identifier core:number?)
139
140 Intrinsic Data Types
141 --------------------
142
143 ### S-expressions ###
144
145 An S-expression is a sort of catch-all data type which includes
146 all the other data types. It is inductively defined as follows:
147
148 * A symbol is an S-expression.
149 * A boolean is an S-expression.
150 * A rational number is an S-expression.
151 * A macro is an S-expression.
152 * An opaque value is an S-expression.
153 * An empty list is an S-expression.
154 * A list cell containing an S-expression, prepended to another list,
155 is an S-expression.
156 * Nothing else is an S-expression.
157
158 S-expressions have a textual representation, but not all types have values
159 that can be directly expressed in this textual representation. All
160 S-expressions have some meaning when interpeted as Robin programs, as
161 defined by Robin's evaluation rules, but that meaning might be to
162 raise an exception to indicate an error.
163
164 ### Symbol ###
165
166 A symbol is an atomic value represented by a string of characters
167 which may not include whitespace or parentheses or a few other
168 characters (TODO: decide which ones) and which may not begin with
169 a `#` (pound sign) or a few other characters (TODO: decide which
170 ones.)
171
172 When in a Robin program proper, a symbol can be bound to a value, and
173 in this context is it referred to as an _identifier_. However, if an
174 attempt is made to evaluate a symbol which is not bound to an identifier,
175 an exception will be raised. For a symbol to appear unevaluated in a Robin
176 program, it must be an argument to a macro. For that reason, we can't
177 show an example of a literal symbol without first defining a macro. For
178 illustrative purposes, we shall import the macro `literal` from the `small`
179 module for this purpose, as it is the most straightforward way to create
180 a literal symbol in a Robin program.
181
182 | (robin (0 1) ((small (0 1)))
183 | (small:literal hello))
184 = hello
185
186 A Robin program is not expected to be able to generate new symbols
187 at runtime.
188
189 ### Booleans ###
190
191 There are two values of Boolean type, `#t`, representing truth, and `#f`,
192 representing falsehood. By convention, an identifier which ends in `?`
193 is a macro or function which evaluates to a Boolean. The `if` macro from
194 the `core` module expects a Boolean expression as its first argument.
195
196 Booleans always evaluate to themselves.
197
198 ### Rational Numbers ###
199
200 A rational number is a pair of integers, called the numerator and the
201 denominator, considered as a ratio. No bounds are imposed upon rational
202 numbers, save that the denominator cannot be zero; further, all rational
203 numbers in Robin are exact.
204
205 The rationale here is that Robin isn't meant for high-performance
206 numerical computing, which is what floating-point values are meant
207 for, so it doesn't have them; at the same time, you occasionally
208 need to compute fractional values, and you don't want to worry
209 overmuch about whether they will overflow or not. (Analysis
210 techniques could be used to prove that, in a performance-critical
211 section of code, a rational number is always an integer and/or
212 always within a certain range, and this information could be used
213 to optimize that section of code. But we'll worry about that
214 later.)
215
216 For example, 5 is a rational number:
217
218 | (robin (0 1) () 5)
219 = 5
220
221 The literal syntax for rational numbers allows one to use `/` to
222 denote a fraction:
223
224 | (robin (0 1) () 4/5)
225 = 4/5
226
227 Rational numbers always evaluate to themselves.
228
229 ### Macros ###
230
231 A macro is an S-expression, in an environment, which describes how to
232 translate one S-expression to another.
233
234 One area where Robin diverges heavily from Lisp and Scheme is that,
235 whereas Lisp and Scheme support macro capabilities, in Robin, the macro
236 is a fundamental type. Other abstractions, such as function values, are
237 built on top of macros. Macros are first-class objects that may exist
238 at runtime and can evaluate to other macros. Therefore, the word "macro"
239 has, perhaps, a slightly different meaning in Robin than in Lisp or Scheme.
240
241 They can also be compared to the one-argument `lambda` form from PicoLisp;
242 again, however, unlike PicoLisp's variety of `lambda` forms, Robin's
243 macros are the only abstraction of this kind fundamentally available, and
244 other abstractions must be built on top of macros.
245
246 Whereas a function evaluates each of its arguments to values, and
247 binds each of those values to a formal parameter of the function, then
248 evaluates the body of the function in that new environment, a macro
249 binds the literal tail of the list of the macro application to the second
250 formal parameter of the macro, and evaluates the body of the macro.
251
252 Each macro has two other formal parameters available to it; the first
253 formal parameter is bound to the macro itself (to facilitate writing
254 recursive macros), and the third formal parameter is bound to a binding
255 alist representing the environment in effect at the point the macro was
256 evaluated.
257
258 There also exist macros which cannot effectively be expressed directly
259 in Robin -- these are the "built-in" macros. One such "built-in"
260 macro is `eval`. Many macros will make use of `eval`, to evaluate
261 that literal tail they receive in a (perhaps modified) environment.
262
263 Macros are defined with the `macro` macro in the `core` module.
264 Macros are represented as the S-expression expansion of their
265 implementation, except in the case of built-in macros.
266
267 | (robin (0 1) ((core (0 1)))
268 | (core:macro (self args env) args))
269 = (macro (self args env) args)
270
271 A built-in macro is represented thusly. (TODO: this representation
272 has problems; see section on lists below.)
273
274 | (robin (0 1) ((core (0 1)))
275 | core:head)
276 = (builtin head)
277
278 One upshot of built-in macros is that *all* intrinsic Robin functionality,
279 even things that in Scheme are special forms, can be passed around as
280 values.
281
282 | (robin (0 1) ((core (0 1) *))
283 | (prepend if (prepend head ())))
284 = ((builtin if) (builtin head))
285
286 Macros always evaluate to themselves.
287
288 ### Lists ###
289
290 A list is either the empty list, or a list cell containing a value of any
291 type, prepended to another list.
292
293 The "head" of a list cell is the value (of any type) that it contains;
294 the "tail" is the other list that it is prepended to. The empty list
295 has neither head nor tail.
296
297 Lists have a literal representation in Robin's S-expression based
298 syntax.
299
300 The empty list is notated `()` and it evaluates to itself.
301
302 | (robin (0 1) ()
303 | ())
304 = ()
305
306 A list with several elements is notated as a sequence of those
307 elements, preceded by a `(`, followed by a `)`, and delimited
308 by whitespace.
309
310 Lists do not evaluate to themselves; rather, they represent a macro
311 application. However, the `literal` macro may be used to obtain a
312 literal list.
313
314 | (robin (0 1) ((small (0 1)))
315 | (small:literal (7 8)))
316 = (7 8)
317
318 Representations of some types (like built-in macros) look funny because
319 they don't follow the rules for depicting lists -- effectively, the parens
320 are "fake" on these things.
321
322 | (robin (0 1) ((core (0 1) *))
323 | (prepend #f (prepend boolean? ())))
324 = (#f (builtin boolean?))
325
326 Conventional Data Types
327 -----------------------
328
329 This section lists data types that are not intrinsic, but are rather
330 arrangements of intrinsic types in a way that follows a convention.
331
332 ### Alists ###
333
334 An alist, short for "association list", is simply a list of two-element
335 sublists. The idea is that each of these two-elements associates, in some
336 context, the value of its first element with the value of its second element.
337
338 ### Binding Alists ###
339
340 When the first element of each two-element sublist in an alist is a symbol,
341 we call it a _binding alist_. The idea is that it is a Robin representation
342 of an evaluation environment, where the symbols in the heads of the sublists
343 are bound to the values in the tails of the pairs. Binding alists can be
344 created from an environment in effect (such as in the third argument of a
345 macro) and can be used to change the evaluation environment in effect (such
346 as in the first argument to `eval`.)
347
348 TODO: binding alists will be replaced by abstract map objects of some kind.
349
350 ### Strings ###
351
352 Strings are just lists of integers, where each integer refers to a
353 particular Unicode codepoint. Robin supports a sugared syntax for
354 specifying literal strings. The characters of the string are given
355 between pairs of single quotes.
356
357 | (robin (0 1) ((small (0 1) *))
358 | (literal ''Hello''))
359 = (72 101 108 108 111)
360
361 A single single quote may appear in string literals of this kind.
362
363 | (robin (0 1) ((small (0 1) *))
364 | (literal ''He'llo''))
365 = (72 101 39 108 108 111)
366
367 Between the single quotes delimiting the string literal, a *sentinel*
368 may be given. The sentinel between the leading single quote pair must
369 match the sentinel given between the trailing single quote pair. The
370 sentinel may consist of any text not containing a single quote.
371
372 | (robin (0 1) ((small (0 1) *))
373 | (literal 'X'Hello'X'))
374 = (72 101 108 108 111)
375
376 | (robin (0 1) ((small (0 1) *))
377 | (literal '...@('Hello'...@('))
378 = (72 101 108 108 111)
379
380 SKIP
381 !| (robin (0 1) ((small (0 1) *))
382 !| (literal 'X'Hello'Y'))
383 !? (line 3, column 1):
384 !? unexpected end of input
385 !? expecting "'"
386
387 A sentinelized literal like this may embed a pair of single quotes.
388
389 | (robin (0 1) ((small (0 1) *))
390 | (literal 'X'Hel''lo'X'))
391 = (72 101 108 39 39 108 111)
392
393 By choosing different sentinels, string literals may contain any other
394 string literal.
395
396 | (robin (0 1) ((small (0 1) *))
397 | (literal 'X'Hel'Y'bye'Y'lo'X'))
398 = (72 101 108 39 89 39 98 121 101 39 89 39 108 111)
399
400 No interpolation of escape sequences is done in a Robin string literal.
401 (Functions to convert escape sequences commonly found in other languages
402 may one day be available in a standard module.)
403
404 | (robin (0 1) ((small (0 1) *))
405 | (literal ''Hello\nworld''))
406 = (72 101 108 108 111 92 110 119 111 114 108 100)
407
408 All characters which appear in the source text between the delimiters
409 of the string literal are literally included in the string.
410
411 | (robin (0 1) ((small (0 1) *))
412 | (literal ''Hello
413 | world''))
414 = (72 101 108 108 111 10 119 111 114 108 100)
415
416 Adjacent string literals are not automatically concatenated.
417
418 | (robin (0 1) ((small (0 1) *))
419 | (literal (''Hello'' ''world'')))
420 = ((72 101 108 108 111) (119 111 114 108 100))
421
422 Comments
423 --------
424
425 Any S-expression preceded by a `;` symbol is a comment. It will still
426 be parsed, but it will be ignored.
427
428 | (robin (0 1) ((core (0 1) *))
429 | ;(this program produces a list of two booleans)
430 | (prepend #f (prepend #f ())))
431 = (#f #f)
432
433 Because S-expressions may nest, and because comments may appear
434 inside S-expressions, comments may nest.
435
436 | (robin (0 1) ((core (0 1) *))
437 | ;(this program produces
438 | ;(what you might call)
439 | a list of two booleans)
440 | (prepend #f (prepend #f ())))
441 = (#f #f)
442
443 Comments are still parsed. A syntax error in a comment is an error.
444
445 SKIP
446 !| (robin (0 1) ((core (0 1) *))
447 !| ;(this program produces
448 !| #k
449 !| a list of booleans)
450 !| (prepend #f (prepend #f ())))
451 !? (line 3, column 6):
452 !? unexpected "k"
453 !? expecting "t" or "f"
454
455 Any number of comments may appear together.
456
457 | (robin (0 1) ((core (0 1) *))
458 | (prepend ;what ;on ;earth #f (prepend #f ())))
459 = (#f #f)
460
461 Comments may appear before a closing parenthesis.
462
463 | (robin (0 1) ((core (0 1) *))
464 | (prepend #f (prepend #f ()) ;foo))
465 = (#f #f)
466
467 | (robin (0 1) ((core (0 1) *))
468 | (prepend #f (prepend #f ()) ;peace ;(on) ;earth))
469 = (#f #f)
470
471 Comments may appear in an empty list.
472
473 | (robin (0 1) ()
474 | ( ;hi ;there))
475 = ()
476
477 Comments need not be preceded by spaces.
478
479 | (robin (0 1) ()
480 | (;north;by;north;west))
481 = ()
482
483 To put truly arbitrary text in a comment, the string sugar syntax may be
484 used.
485
486 | (robin (0 1) ((core (0 1) *))
487 | ;''This program, it produces a list of two booleans. #k ?''
488 | (prepend #f (prepend #f ())))
489 = (#f #f)
490
491 Standard Modules
492 ----------------
493
494 ### `core` ###
495
496 Robin's `core` module exports the fundamental functionality that is used
497 to evaluate programs, and that cannot be expressed as macros written
498 in Robin.
499
500 `core` is not optional -- every Robin implementation must provide a
501 `core` module, or it's not Robin.
502
503 The `core` module is documented in
504 [module/Core.falderal](module/Core.falderal).
505
506 ### `small` ###
507
508 Robin's `small` module exports everything `core` does, and a few
509 macros (which could be written in Robin, but could also be implemented
510 natively for efficiency) to make writing programs somewhat easier --
511 basically to bring the language up to parity, in expressive power, with
512 Pixley.
513
514 `small` is technically an optional module, but it's really handy,
515 and could be written in pure Robin, so it's likely to be available.
516
517 The `small` module is documented in
518 [module/Small.falderal](module/Small.falderal).
519
520 ### `exception` ###
521
522 Robin's `exception` module exports macros for catching exceptions.
523
524 This module is optional. A Robin form that imports this module is asserting
525 that it requires an implementation in which exceptions can be caught.
526
527 Note that exceptions can still be raised in an implementation where they
528 cannot be caught; they simply cause an immediate termination of the Robin
529 program instead.
530
531 The `exception` module is documented in
532 [module/Exception.falderal](module/Exception.falderal).
533
534 ### `concurrency` ###
535
536 Robin's `concurrency` module exports macros for working with concurrently-
537 executing processes which communicate with each other via message-
538 passing.
539
540 This module is optional. A Robin form that imports this module is asserting
541 that it requires an implementation which supports concurrency.
542
543 The `concurrency` module is documented in
544 [module/Concurrency.falderal](module/Concurrency.falderal).
545
546 ### `list` ###
547
548 Robin's `list` module exports macros and functions for working with
549 data of conventional list type.
550
551 All macros in this module can be expressed in Robin, but of course
552 could also be implemented natively for efficiency.
553
554 `list` is technically an optional module, but it's really handy,
555 and could be written in pure Robin, so it's likely to be available.
556
557 The `list` module is documented in
558 [module/List.falderal](module/List.falderal).
559
560 ### `env` ###
561
562 Robin's `env` module exports macros and functions for examining and
563 manipulating evaluation environments and, to the extent they are
564 represented as binding alists, binding alists.
565
566 All macros in this module can be expressed in Robin, but of course
567 could also be implemented natively for efficiency.
568
569 `env` is technically an optional module, but it's really handy,
570 and could be written in pure Robin, so it's likely to be available.
571
572 The `env` module is documented in
573 [module/Environment.falderal](module/Environment.falderal).
574
575 ### `boolean` ###
576
577 Robin's `boolean` module exports macros and functions for working
578 with Boolean values, including the traditional Boolean operators.
579
580 All macros in this module can be expressed in Robin, but of course
581 could also be implemented natively for efficiency.
582
583 `boolean` is technically an optional module, but it's really handy,
584 and could be written in pure Robin, so it's likely to be available.
585
586 The `boolean` module is documented in
587 [module/Boolean.falderal](module/Boolean.falderal).
588
589 ### `arith` ###
590
591 Robin's `arith` module exports macros and functions for performing
592 basic arithmetic and numeric comparison operations.
593
594 All macros in this module can be expressed in Robin, but of course
595 could also be implemented natively for efficiency.
596
597 `arith` is technically an optional module, but it's really handy,
598 and could be written in pure Robin, so it's likely to be available.
599
600 The `arith` module is documented in
601 [module/Arithmetic.falderal](module/Arithmetic.falderal).
602
603 ### `crude-io` ###
604
605 Robin's `crude-io` module exports a rudimentary, process-based
606 interface to the operating system's idea of "standard input" and
607 "standard output". Textual S-expressions may be read and written,
608 one per line.
609
610 `crude-io` is an optional module. It cannot be written directly
611 in Robin.
612
613 The `crude-io` module is documented in
614 [module/CrudeIO.falderal](module/CrudeIO.falderal).
615
616 ### `random` ###
617
618 Robin's `random` module exports a process-based interface to a pseudo-
619 random number generator.
620
621 `random` is an optional module. It can be written in Robin, save for the
622 fact that it is not deterministic (seeding is a problem.)
623
624 The `random` module is documented in
625 [module/Random.falderal](module/Random.falderal).
0 <html>
1 <head>
2 <style>
3 table {
4 border: 1px solid;
5 padding: 1em;
6 margin: 1em;
7 }
8 </style>
9 </head>
10 <body>
11
12 <table>
13 <tr><th>Standard Library</th></tr>
14 <tr><td>
15
16 <p><i>(boolean)</i> and or xor not boolean?</p>
17
18 <p><i>(list)</i> empty? map fold reverse filter find append elem? length index
19 take-while drop-while first rest last prefix? flatten</p>
20
21 <p><i>(alist)</i> lookup extend delete</p>
22
23 <p><i>(env)</i> env? export sandbox unbind unshadow</p>
24
25 <p><i>(arith)</i> abs add &gt; &gt;= &lt; &lt;= multiply divide remainder</p>
26
27 <p><i>(misc)</i> itoa</p>
28
29 <table>
30 <tr><th>"Fun"</th></tr>
31 <tr><td>
32
33 fun
34
35 <table>
36 <tr><th>Intrinsics-Wrappers</th></tr>
37 <tr><td>
38 head
39 tail
40 prepend
41 list?
42 symbol?
43 macro?
44 number?
45 equal?
46 subtract
47 sign
48 macro
49 eval
50 if
51 raise
52 catch
53
54 <table>
55 <tr><th>"Small"</th></tr>
56 <tr><td>
57 literal
58 list
59 bind
60 env
61 let
62 choose
63 bind-args
64
65 <table>
66 <tr><th>Intrinsics</th></tr>
67 <tr><td>
68 @head
69 @tail
70 @prepend
71 @list?
72 @symbol?
73 @macro?
74 @number?
75 @equal?
76 @subtract
77 @sign
78 @macro
79 @eval
80 @if
81 @raise
82 @catch
83 </td></tr>
84 </table>
85
86 </td></tr>
87 </table>
88
89 </td></tr>
90 </table>
91
92 </td></tr>
93 </table>
94
95 </td></tr>
96 </table>
0 Robin Intrinsics
1 ================
2
3 -> Tests for functionality "Interpret core Robin Program"
4
5 An _intrinsic_ is one of the data types in Robin. It is like a macro, except
6 that it is implemented intrinsically (and thus does not support quite
7 every operation that is supported on macros, for example, examining its
8 internals.)
9
10 Robin provides (as of this writing) 15 intrinsics. These represent
11 the fundamental functionality that is used to evaluate programs, and that
12 cannot be expressed (non-meta-circularly) as macros written in Robin.
13 All other macros are built up on top of the intrinsics.
14
15 This set of intrinsics is not optional — every Robin implementation must
16 provide them, or it's not Robin.
17
18 Intrinsics usually have undefined behaviour if their preconditions are
19 not met (called with wrong number or types of arguments.) Obviously,
20 we can't write tests for those cases here. However, for each intrinsics,
21 there is a corresponding macro in `stdlib` which wraps the intrinsics,
22 and is named the same except omitting the `@`. These wrappers give
23 the intrinsics predictable failure modes in these cases, by raising
24 defined exceptions.
25
26 ### `@prepend` ###
27
28 `@prepend` evaluates both of its arguments, then evaluates to a list cell
29 which contains the first value as its data and the second value as the
30 continuation of the list.
31
32 | (display
33 | (@prepend () ()))
34 = (())
35
36 | (display
37 | (@prepend #t (@prepend #f ())))
38 = (#t #f)
39
40 `@prepend` expects exactly two arguments. The first may be of any type.
41 The second`@prepend` must be a list. If these conditions are not met,
42 the behaviour is undefined.
43
44 `@prepend` is basically equivalent to Scheme's `cons`, except for the
45 requirement that the second argument be a list.
46
47 ### `@head` ###
48
49 `@head` evaluates its argument to a list, and evaluates to the first element
50 of that list.
51
52 | (display
53 | (@head (@prepend #t ())))
54 = #t
55
56 `@head` expects exactly one argument, and expects it to be a list.
57 If these conditions are not met, the behaviour is undefined.
58
59 `@head` is basically equivalent to Scheme's `car`.
60
61 ### `@tail` ###
62
63 `@tail` evaluates its argument to a list, and evaluates to the tail of that
64 list (the sublist obtained by removing the first element.)
65
66 | (display
67 | (@tail (@prepend #t (@prepend #f ()))))
68 = (#f)
69
70 `@tail` expects exactly one argument, and expects it to be a list.
71 If these conditions are not met, the behaviour is undefined.
72
73 `@tail` is basically equivalent to Scheme's `cdr`.
74
75 ### `@if` ###
76
77 `@if` evaluates its first argument to a boolean value. If that value is
78 `#t`, it evaluates, and evaluates to, its second argument; or if that value
79 is `#f` it evaluates, and evaluates to, its third argument. In all cases,
80 at most two arguments are evaluated.
81
82 | (display
83 | (@if #t 7 9))
84 = 7
85
86 | (display
87 | (@if #f 7 9))
88 = 9
89
90 The identifiers named in the branch which is not evaluated need not be
91 properly bound to values in the environment.
92
93 | (display
94 | (@if #t 1 (prepend fred ethel)))
95 = 1
96
97 The second and third arguments can be arbitrary expressions, but `@if`
98 expects its first argument to be a boolean. `@if` expects exactly three
99 arguments. If these conditions are not met, the behaviour is undefined.
100
101 `@if` is basically equivalent to Scheme's `if`.
102
103 ### `@equal?` ###
104
105 `@equal?` evaluates both of its arguments to arbitrary S-expressions
106 and compares them for deep equality.
107
108 `@equal?` works on symbols.
109
110 | (define literal (@macro (s a e) (@head a)))
111 | (display
112 | (@equal?
113 | (literal this-symbol)
114 | (literal this-symbol)))
115 = #t
116
117 | (define literal (@macro (s a e) (@head a)))
118 | (display
119 | (@equal?
120 | (literal this-symbol)
121 | (literal that-symbol)))
122 = #f
123
124 `@equal?` works on lists.
125
126 | (display
127 | (@equal? (@prepend 1 (@prepend 2 (@prepend 3 ())))
128 | (@prepend 1 (@prepend 2 (@prepend 3 ())))))
129 = #t
130
131 `@equal?` works on lists, deeply.
132
133 | (display
134 | (@equal? (@prepend 1 (@prepend 2 (@prepend 7 ())))
135 | (@prepend 1 (@prepend 2 (@prepend 3 ())))))
136 = #f
137
138 Two values of different types are never equal.
139
140 | (define literal (@macro (s a e) (@head a)))
141 | (display
142 | (@equal? #t
143 | (@prepend (literal a) ())))
144 = #f
145
146 | (display
147 | (@equal? #f
148 | ()))
149 = #f
150
151 `@equal?` expects exactly two arguments, of any type.
152
153 ### `@list?` ###
154
155 `@list?` evaluates its argument, then evaluates to `#t` if it is a list,
156 `#f` otherwise.
157
158 | (define literal (@macro (s a e) (@head a)))
159 | (display
160 | (@list? (literal (a b))))
161 = #t
162
163 | (define literal (@macro (s a e) (@head a)))
164 | (display
165 | (@list? (literal (a b c d e f))))
166 = #t
167
168 | (display
169 | (@list? (@prepend 4 (@prepend 5 ()))))
170 = #t
171
172 The empty list is a list.
173
174 | (display
175 | (@list? ()))
176 = #t
177
178 Symbols are not lists.
179
180 | (define literal (@macro (s a e) (@head a)))
181 | (display
182 | (@list? (literal a)))
183 = #f
184
185 The argument to `@list?` may (naturally) be any type, but there must be
186 exactly one argument.
187
188 ### `@macro?` ###
189
190 `@macro?` evaluates its argument, then evaluates to `#t` if it is a macro,
191 or `#f` if it is not.
192
193 | (display
194 | (@macro? (@macro (self args env) args)))
195 = #t
196
197 TODO: this should probably be false. Intrinsics are slightly different
198 from macros. Either that, or, it should be, like `@applyable?`, or
199 something.
200
201 | (display
202 | (@macro? @macro))
203 = #t
204
205 | (display
206 | (@macro? ((@macro (self args env) (@head args)) @macro)))
207 = #f
208
209 | (display
210 | (@macro? 5))
211 = #f
212
213 The argument to `@macro?` may (naturally) be any type, but there must be
214 exactly one argument.
215
216 ### `@symbol?` ###
217
218 `@symbol?` evaluates its argument, then evaluates to `#t` if it is a symbol,
219 `#f` otherwise.
220
221 | (define literal (@macro (s a e) (@head a)))
222 | (display
223 | (@symbol? (literal this-symbol)))
224 = #t
225
226 Numbers are not symbols.
227
228 | (display
229 | (@symbol? 9))
230 = #f
231
232 Lists are not symbols.
233
234 | (display
235 | (@symbol? (@prepend 1 ())))
236 = #f
237
238 The argument to `@symbol?` may (naturally) be any type, but there must be
239 exactly one argument.
240
241 ### `@number?` ###
242
243 `@number?` evaluates its argument, then evaluates to `#t` if it is a
244 number, `#f` otherwise.
245
246 | (display
247 | (@number? 7))
248 = #t
249
250 | (display
251 | (@number? 0))
252 = #t
253
254 | (display
255 | (@number? ()))
256 = #f
257
258 | (display
259 | (@number? #t))
260 = #f
261
262 | (define literal (@macro (s a e) (@head a)))
263 | (display
264 | (@number? (literal seven)))
265 = #f
266
267 That's a good question...
268
269 | (define literal (@macro (s a e) (@head a)))
270 | (display
271 | (@number? (literal 7)))
272 = #t
273
274 The argument to `@number?` may (naturally) be any type, but there must be
275 exactly one argument.
276
277 ### `@subtract` ###
278
279 `@subtract` evaluates its first argument to a rational number, then
280 evaluates its second argument to a rational number, then evaluates
281 to the difference between the first and second numbers.
282
283 | (display
284 | (@subtract 6 4))
285 = 2
286
287 | (display
288 | (@subtract 1000 8000))
289 = -7000
290
291 Addition may be accomplished by negating the second argument.
292
293 | (display
294 | (@subtract 999 (@subtract 0 999)))
295 = 1998
296
297 `@subtract` expects both of its arguments to be numbers.
298
299 `@subtract` expects exactly two arguments.
300
301 ### `@sign` ###
302
303 `@sign` evaluates its sole argument to a number, then
304 evaluates to 0 if that number is 0, 1 if that number is positive, or
305 -1 if that number is negative.
306
307 | (display
308 | (@sign 26))
309 = 1
310
311 | (display
312 | (@sign 0))
313 = 0
314
315 | (display
316 | (@sign (@subtract 0 200)))
317 = -1
318
319 `@sign` expects exactly one argument.
320
321 ### `@eval` ###
322
323 `@eval` evaluates its first argument to obtain an environment, then
324 evaluates its second argument to obtain an S-expression; it then
325 evaluates that S-expression in the given environment.
326
327 | (define literal (@macro (s a e) (@head a)))
328 | (define env (@macro (s a e) e))
329 | (display
330 | (@eval (env) (literal
331 | (@prepend (literal a)
332 | (@prepend (literal b) ())))))
333 = (a b)
334
335 | (define literal (@macro (s a e) (@head a)))
336 | (display
337 | (@eval () (literal
338 | (@prepend (literal a)
339 | (@prepend (literal b) ())))))
340 ? uncaught exception: (unbound-identifier @prepend)
341
342 Something fairly complicated that uses `bind`...?
343
344 | (define literal (@macro (s a e) (@head a)))
345 | (define bind (@macro (self args env)
346 | (@eval
347 | (@prepend (@prepend (@head args) (@prepend (@eval env (@head (@tail args))) ())) env)
348 | (@head (@tail (@tail args))))))
349 | (display
350 | (bind bindings (@prepend
351 | (@prepend (literal same) (@prepend @equal? ()))
352 | (@prepend
353 | (@prepend (literal x) (@prepend #f ()))
354 | ()))
355 | (@eval bindings (literal (same x x)))))
356 = #t
357
358 If two bindings for the same identifier are supplied in the environment
359 alist passed to `@eval`, the one closer to the front of the alist takes
360 precedence.
361
362 | (define literal (@macro (s a e) (@head a)))
363 | (define bind (@macro (self args env)
364 | (@eval
365 | (@prepend (@prepend (@head args) (@prepend (@eval env (@head (@tail args))) ())) env)
366 | (@head (@tail (@tail args))))))
367 | (display
368 | (bind bindings (@prepend
369 | (@prepend (literal foo) (@prepend (literal yes) ()))
370 | (@prepend
371 | (@prepend (literal foo) (@prepend (literal no) ()))
372 | ()))
373 | (@eval bindings (literal foo))))
374 = yes
375
376 ### `@macro` ###
377
378 `@macro` takes its first argument to be a list of three formal
379 parameters, and its second argument to be an arbitrary expression,
380 and uses these two arguments to build, and evaluate to, a macro
381 value.
382
383 When this macro value is evaluated, the first formal argument will
384 be bound to the macro itself, the second will be bound to the
385 literal, unevaluated list of arguments passed to the macro, and the
386 third will be bound to an alist representing the environment in
387 effect at the point the macro value is evaluated.
388
389 These formals are conventionally called `self`, `args`, and `env`,
390 but different names can be chosen in the `macro` definition, for
391 instance to avoid shadowing.
392
393 `literal`, in fact, can be defined as a macro, and it is one of the
394 simplest possible macros that can be written:
395
396 | (display
397 | ((@macro (self args env) (@head args)) (why hello there)))
398 = (why hello there)
399
400 And when we want to use it in the tests, we'll define it first, like
401 this:
402
403 (define literal (@macro (s a e) (@head a)))
404
405 Another facility that can be defined simply by a macro is `env`,
406 and we'll define it like this:
407
408 (define env (@macro (s a e) e))
409
410 Macros have "closure" behavior; that is, bindings in force when a
411 macro is defined will still be in force when the macro is applied,
412 even if they are no longer lexically in scope. (Please try to ignore
413 the heavy `define`s that are used in this test...)
414
415 | (define literal (@macro (s a e) (@head a)))
416 | (define bind (@macro (self args env)
417 | (@eval
418 | (@prepend (@prepend (@head args) (@prepend (@eval env (@head (@tail args))) ())) env)
419 | (@head (@tail (@tail args))))))
420 | (define let (@macro (self args env)
421 | (bind bindings (@head args)
422 | (@if (@equal? bindings ())
423 | (@eval env (@head (@tail args)))
424 | (bind binding (@head bindings)
425 | (bind name (@head binding)
426 | (@if (@symbol? name)
427 | (bind value (@eval env (@head (@tail binding)))
428 | (bind newenv (@prepend (@prepend name (@prepend value ())) env)
429 | (bind newbindings (@tail bindings)
430 | (bind newargs (@prepend newbindings (@tail args))
431 | (@eval newenv (@prepend self newargs))))))
432 | (@raise (prepend (literal illegal-binding) (@prepend binding ()))))))))))
433 | (display
434 | ((let
435 | ((a (literal these-are))
436 | (m (@macro (self args env) (@prepend a args))))
437 | m) my args))
438 = (these-are my args)
439
440 Macros can return macros.
441
442 | (define literal (@macro (s a e) (@head a)))
443 | (define bind (@macro (self args env)
444 | (@eval
445 | (@prepend (@prepend (@head args) (@prepend (@eval env (@head (@tail args))) ())) env)
446 | (@head (@tail (@tail args))))))
447 | (define let (@macro (self args env)
448 | (bind bindings (@head args)
449 | (@if (@equal? bindings ())
450 | (@eval env (@head (@tail args)))
451 | (bind binding (@head bindings)
452 | (bind name (@head binding)
453 | (@if (@symbol? name)
454 | (bind value (@eval env (@head (@tail binding)))
455 | (bind newenv (@prepend (@prepend name (@prepend value ())) env)
456 | (bind newbindings (@tail bindings)
457 | (bind newargs (@prepend newbindings (@tail args))
458 | (@eval newenv (@prepend self newargs))))))
459 | (@raise (prepend (literal illegal-binding) (@prepend binding ()))))))))))
460 | (display
461 | (let
462 | ((mk (@macro (self argsa env)
463 | (@macro (self argsb env)
464 | (@prepend (@head argsb) argsa))))
465 | (mk2 (mk vindaloo)))
466 | (mk2 chicken)))
467 = (chicken vindaloo)
468
469 Arguments to macros shadow any other bindings in effect.
470
471 | (define literal (@macro (s a e) (@head a)))
472 | (define bind (@macro (self args env)
473 | (@eval
474 | (@prepend (@prepend (@head args) (@prepend (@eval env (@head (@tail args))) ())) env)
475 | (@head (@tail (@tail args))))))
476 | (define let (@macro (self args env)
477 | (bind bindings (@head args)
478 | (@if (@equal? bindings ())
479 | (@eval env (@head (@tail args)))
480 | (bind binding (@head bindings)
481 | (bind name (@head binding)
482 | (@if (@symbol? name)
483 | (bind value (@eval env (@head (@tail binding)))
484 | (bind newenv (@prepend (@prepend name (@prepend value ())) env)
485 | (bind newbindings (@tail bindings)
486 | (bind newargs (@prepend newbindings (@tail args))
487 | (@eval newenv (@prepend self newargs))))))
488 | (@raise (prepend (literal illegal-binding) (@prepend binding ()))))))))))
489 | (display
490 | (let
491 | ((args (literal a))
492 | (b (@macro (self args env) (@prepend args args))))
493 | (b 7)))
494 = ((7) 7)
495
496 `self` is there to let you write recursive macros. The following
497 example demonstrates this; it evaluates `(prepend b d)` in an environment
498 where all the identifiers you list after `qqq` have been bound to 0.
499
500 | (define literal (@macro (s a e) (@head a)))
501 | (define bind (@macro (self args env)
502 | (@eval
503 | (@prepend (@prepend (@head args) (@prepend (@eval env (@head (@tail args))) ())) env)
504 | (@head (@tail (@tail args))))))
505 | (display
506 | (bind qqq
507 | (@macro (self args env)
508 | (@if (@equal? args ())
509 | (@eval env (literal (@prepend b (@prepend d ()))))
510 | (@eval (@prepend (@prepend (@head args) (@prepend 0 ())) env)
511 | (@prepend self (@tail args)))))
512 | (bind b 1 (bind d 4 (qqq b c d)))))
513 = (0 0)
514
515 | (define literal (@macro (s a e) (@head a)))
516 | (define bind (@macro (self args env)
517 | (@eval
518 | (@prepend (@prepend (@head args) (@prepend (@eval env (@head (@tail args))) ())) env)
519 | (@head (@tail (@tail args))))))
520 | (display
521 | (bind qqq
522 | (@macro (self args env)
523 | (@if (@equal? args ())
524 | (@eval env (literal (@prepend b (@prepend d ()))))
525 | (@eval (@prepend (@prepend (@head args) (@prepend 0 ())) env)
526 | (@prepend self (@tail args)))))
527 | (bind b 1 (bind d 4 (qqq x y z)))))
528 = (1 4)
529
530 Your recursive `macro` application doesn't have to be tail-recursive.
531
532 | (define literal (@macro (s a e) (@head a)))
533 | (define bind (@macro (self args env)
534 | (@eval
535 | (@prepend (@prepend (@head args) (@prepend (@eval env (@head (@tail args))) ())) env)
536 | (@head (@tail (@tail args))))))
537 | (display
538 | (bind make-env
539 | (@macro (self args env)
540 | (@if (@equal? args ())
541 | ()
542 | (@prepend (@prepend (@head args)
543 | (@prepend (@eval env (@head args)) ()))
544 | (@eval env
545 | (@prepend self (@tail args))))))
546 | (bind b 1 (bind d 4 (make-env b d @macro)))))
547 = ((b 1) (d 4) (@macro @macro))
548
549 `@macro` expects exactly two arguments.
550
551 `@macro` expects its first argument to be a list of exactly three
552 symbols.
553
554 ### `@raise` ###
555
556 `@raise` evaluates its argument to obtain a value, then raises an
557 exception with that value.
558
559 If no exception handlers have been installed in the execution
560 history, the Robin program will terminate with an error, ceasing execution
561 of all Robin processes immediately, returning control to the operating
562 system. For the sake of usability, the error should include a message which
563 refers to the exception that triggered it, but this is not a strict
564 requirement.
565
566 | (display
567 | (@raise 999999))
568 ? uncaught exception: 999999
569
570 `@raise`'s single argument may be any kind of value, but `raise` expects
571 exactly one argument.
572
573 ### `@catch` ###
574
575 `@catch` installs an exception handler.
576
577 If an exception is raised when evaluating the final argument of
578 `@catch`, the exception value is bound to the symbol given as the
579 first argument of `@catch`, and the second argument of `@catch` is
580 evaluated in that new environment.
581
582 | (define literal (@macro (s a e) (@head a)))
583 | (define list (@macro (self args env)
584 | (@if (@equal? args ())
585 | ()
586 | (@prepend (@eval env (@head args))
587 | (@eval env (@prepend self (@tail args)))))))
588 | (display
589 | (@catch error (list error #f)
590 | (@raise (literal (nasty-value 999999)))))
591 = ((nasty-value 999999) #f)
592
593 `@catch` *cannot necessarily* catch exceptions raised by intrinsics.
594 It ought to be able to catch exceptions raised by intrinsics wrappers,
595 though.
596
597 The innermost `@catch` will catch the exception.
598
599 | (define literal (@macro (s a e) (@head a)))
600 | (define list (@macro (self args env)
601 | (@if (@equal? args ())
602 | ()
603 | (@prepend (@eval env (@head args))
604 | (@eval env (@prepend self (@tail args)))))))
605 | (display
606 | (@catch error (list error 5)
607 | (@catch error (list error 9)
608 | (@raise (literal derpy-value)))))
609 = (derpy-value 9)
610
611 An exception raised from within an exception handler is
612 caught by the next innermost exception handler.
613
614 | (define list (@macro (self args env)
615 | (@if (@equal? args ())
616 | ()
617 | (@prepend (@eval env (@head args))
618 | (@eval env (@prepend self (@tail args)))))))
619 | (display
620 | (@catch error (list error 5)
621 | (@catch error (list error 9)
622 | (@catch error (@raise (list error error))
623 | (@raise 7)))))
624 = ((7 7) 9)
625
626 `@catch` expects its first argument to be an identifier.
627
628 `@catch` expects exactly three arguments.
0 Robin: Modules
1 ==============
2
3 In this document, "Robin" refers to the Robin programming language
4 version 0.1.
5
6 Robin module system is this: Robin does not have a module system.
7
8 We're still working this out, so bear with us. Let's start with
9 some fundamental principles of Robin. You may love them or think
10 they are stupid (I can't tell, myself,) but they are what they are.
11
12 * The core Robin language include only a handful of symbols,
13 called _intrinsics_. These represent functionality that would
14 be impossible or highly impractical to write in Robin itself.
15
16 * A Robin program may, of course, define new symbols internal
17 to it, by assigning them meanings in its environment.
18
19 * The Robin language expresses Robin programs; it does not
20 express metadata about Robin programs.
21
22 * Corollary: the contents of a Robin program is kept separate
23 from the metadata about that Robin program.
24
25 * Corollary: a Robin program that uses a symbol which is defined
26 outside of that program does not, and in fact _cannot_, care
27 where it is defined.
28
29 * Corollary: dependencies between Robin (sub)programs and/or
30 modules is an implementation-level concern, not a
31 language-level concern.
32
33 * Corollary: how the reference implementation solves the problem
34 of dependencies between Robin programs is not necessarily how
35 any other implementation should solve the problem.
36
37 * ... all the Robin language really "knows" is that a Robin
38 program may be split up into seperate files (or rather,
39 "inputs of program texts into the implementation", I guess.)
40
41 * Robin recognizes a set of symbols, currently called `stdlib`,
42 that (should) have a (relatively) fixed meaning for all Robin
43 programs, whether they are used in that program or not.
44
45 * Note (that should be elsewhere?): most of the macros defined
46 in `stdlib` are supposed to, intentionally, take a fixed number
47 of arguments for some reason (nominally, to make some kind of
48 future static analysis easier.)
49
50 * It is something like Maslow's hierarchy of needs. Robin's
51 intrinsics make programming possible (*barely* possible —
52 survival-level.) Robin's `stdlib` makes programming liveable.
53 If there was another level, it might make programming pleasant,
54 even.
55
56 Some implications of this setup in practice are:
57
58 * If you distribute a Robin program to someone else, you need to
59 tell them (somehow) what other Robin (sub)programs/modules it
60 depends on.
61
62 * Actually this is hardly different from C, where dependency
63 information is encoded both in `#include`'s and in a `Makefile`
64 or similar, which links in the correct modules. The difference
65 in Robin is simply that there are no `#include`s.
66
67 * Other languages, such as Haskell and Python, try to include
68 all dependency information in the program source code itself.
69 This does away with `Makefile`-type dependency information,
70 but at the cost of entangling programs and metadata about
71 programs into the same files, into the same language grammar.
72
73 * It would be entirely possible to define a "Robin dependency
74 language" which:
75
76 * describes the dependencies between different Robin programs
77 * informs a tool like `make`
78 * uses Robin's syntax
79 * and perhaps even embeds Robin as an embedded language
80
81 ...*but*, the important thing to note is that such a language
82 would *not be Robin itself*.
83
84 * Any symbol in `stdlib` could be implemented in any language
85 whatsoever, as long as the implementation knows what the
86 semantics of the symbol is.
87
88 The more pragmatic aspect of how the reference implementation
89 currently handles the issue of dependencies between Robin programs,
90 keeping in mind that this is an implementation issue and _not_ a
91 language issue:
92
93 * Each symbol defined in the Robin `stdlib` is written in its own
94 Robin source file in the `stdlib` subdirectory, bundled along
95 with tests for it.
96
97 * All of the symbols in the `stdlib` directory are implemented in
98 Robin. This is because, being a reference implementation, they
99 are "executable specifications" rather than production code.
100 They are supposed to be correct and simple and understandable,
101 rather than performant.
102
103 * Groups of symbols in the `stdlib` are collected into files
104 called "packages", in the `pkg` subdirectory, which are simply
105 concatenations, topologically sorted by dependency, of those
106 individual files in the `stdlib` subdirectory. (These packages
107 are built both by `./build.sh` and `./test.sh`.)
108
109 * The groupings of symbols within a package follow certain themes,
110 but are largely arbitrary, due to the ease with which a
111 particular symbol could be grouped into two different packages
112 by theme, and partly done for the convenience of the test suite,
113 and to make dependencies work out "nicely", so that symbols can
114 be implemented in terms of other symbols.
115
116 * However, two packages have the following justifications:
117
118 * The package `intrinsics-wrappers` contains macros which are
119 simply wrappers for the intrinsics with the same names
120 (prefixed with `@`). These serve two purposes: to let
121 you not have to type `@` all the time, and to perform
122 better argument type and number checking than the intrinsics
123 are defined to do.
124
125 * The package `small` is identified as a fairly minimal set
126 of symbols to make programming tolerable
127 (somewhere between possible and liveable in that "Maslow's
128 hierarchy" analogy.) No symbol in it depends on any symbol
129 defined in any other package; only intrinsics and other symbols
130 in `small`. The price paid for this is that macros in
131 `small`, like the intrinsics, do not have very good argument
132 checking.
133
134 Note that `intrinsics-wrappers` depends on `small`; the use
135 `bind-args` to do the argument checking, which in turn needs
136 `let` and `bind` and so forth.
137
138 For a graphical depiction of the "hierarchy" of defined symbols
139 (which is not really a proper hierarchy), please see
140 `doc/Hierarchy_of_Defined_Symbols.html` (it's in HTML because it'd
141 be trickier to depict in plain text or Markdown.)
+0
-148
doc/Object_Orientation.markdown less more
0 Object Orientation
1 ==================
2
3 Should Robin support object-oriented programming, and if so, in what sense
4 should it be "oriented" towards "objects"? It's a tough question. It is
5 so knotty, in fact, that instead of writing about in the Design Decisions
6 document, I'm going to write about it in this standalone document -- even
7 if Robin's support for it turns out to be minimal or non-existent.
8
9 Why would we want object-orientation? To achive polymorphism at the value
10 level. We already have polymorphism at the module level (your configuration
11 file can point a module at any given implementation of it) and the device
12 level (the device manager can return any device it likes for your request,
13 so long as that device supports the requested operations).
14
15 Still, polymorphism at the value level would be handy. Consider
16 environments. We don't care how they're represented, so long as they support
17 a few operations -- `lookup`, `extend`, perhaps `to-alist` and `from-alist`
18 or the like.
19
20 It doesn't make sense to model environments as devices, because
21 they have no independent existence (through time, or otherwise) from the
22 code that uses them.
23
24 We could simply provide multiple implementations of an `env` module, which
25 use different representations, but all support the given operations.
26 However, this does not buy us any data hiding.
27
28 So let's consider what an object system in Robin could look like, and how
29 it could be implemented.
30
31 Approach
32 --------
33
34 I would like to see the style of object-orientation to be prototype-based
35 (with "manual" inheritance; if your object doesn't understand a method, it's
36 up to it to pass that request on to some other object) and duck-typing based
37 (no explicit classes; if an object supports some set of methods that a duck
38 supports, then it's a duck, or at least you can treat it like one.)
39
40 Should Robin be "purely" object-oriented -- that is, should *everything* be
41 an object, or should there be some things which are not objects?
42
43 I haven't decided. If it is "pure", it will surely make the fundamental
44 semantics more complex, because the base types will need to support some
45 basic methods "out of the box".
46
47 But the reason the core should be simple is to make a rigorous definition
48 easier, and if we have a rigorous definition, and it's still not too hard to
49 make a rigorous definition, maybe the extra complexity is worth it.
50
51 If it's not purely object-oriented,
52
53 * There might be some values I can't treat as objects. Oh noes.
54 * Different groups of developers might make up their own incompatible object
55 systems (think: Lua.)
56
57 The second problem could be mitigated by providing an object system in the
58 standard library -- you don't *have* to use it, but its presence would
59 encourage developers to build their objects in a compatible way. (Kind of
60 like Perl; there, it's a convention, but a pretty strong convention.)
61
62 Implementation
63 --------------
64
65 Objects, and their methods, can be implemented (almost) using macros. An
66 object is a macro which expects its first argument to be a literal symbol
67 which is the method name. The rest of the arguments are the argument to
68 the method. The return value is a (possibly) modified version of the object,
69 or some other value, or possibly even a pair of these two things.
70
71 I say "almost" because I think we need dynamic binding to do it purely as a
72 macro, or at least it would be really, really helpful. Consider:
73
74 (bind val 0
75 (macro (self args env)
76 (let ((method (head args)) (args (tail args))
77 (choose
78 ((equal? method (literal inc))
79 (bind val (+ 1 val) self))
80 ((equal? method (literal dec))
81 (bind val (- 1 val) self))
82 ((equal? method (literal what))
83 val)
84 (else
85 (super method args))))))
86
87 How would this look?
88 --------------------
89
90 For example, lists:
91
92 (LIST head) -> VALUE
93 (LIST tail) -> LIST
94 (LIST cons VALUE) -> LIST
95
96 We don't have a `List` class (and we don't want one either.) Luckily, we
97 have a built-in prototypical object for lists, `()`, so we can say...
98
99 (() cons 5)
100
101 ...but this actually makes the list `(5)`, i.e. it's in an unusual order:
102
103 ((() cons 5) cons 7)
104
105 That one makes the list `(7 5)`.
106
107 Things have a Smalltalk-y flavour after doing this.
108
109 Of course, those are only the methods that lists implement. A list,
110 ultimately, should conform to a collection interface that other collections
111 conform to, which supports things like `fold`, `find`, `size`, and whatnot.
112 Basic lists should probably not support these out-of-the-box (the core would
113 be too complicated.) But, it should be possible, maybe, to wrap a list in a
114 list-container, like
115
116 (list-container ((() cons 5) cons 7))
117
118 If Robin is purely object-oriented, where do the non-instance methods live?
119 Do we have class objects (metaclass etc a la Smalltalk?) I'd rather not
120 (duck-prototyping only.) So that suggests we either put all these methods
121 on some object (effectively a class object, in some aspects, perhaps), or
122 retain plain macros (if objects are built from them then they're still
123 available for that purpose), or something else...
124
125 Problems
126 --------
127
128 One of the biggest problems here is how objects would interact with static
129 analysis. A macro which operates on an object doesn't care about how the
130 object implements the methods on it, but it *does* care that the method
131 operation meets the interface expectations.
132
133 To do static analysis on objects, we would need to codify the expectations on
134 the interface(s) that each object supports. With traditional name-only duck
135 typing, this is not possible; we would need to extend names with the interface
136 module that they're from (so you can distinguish `tree:bark` from `dog:bark`.)
137
138 Also, we would need to start putting metadata into interfaces somehow.
139
140 We need to do this anyway, to some extent; if I make a new macro called
141 `assign` which works a lot like `bind` or `let` but has a different syntax,
142 how do I let the static analyzer know that it does that? (For that matter,
143 how does the static analyzer know that the concurrency macros bind a new
144 value to one of the identifiers passed to them?)
145
146 So, this should probably be put on hold until I have a better idea of what
147 metadata will eventually look like.
0 Robin Reactors
1 ==============
2
3 To seperate the concerns of computation and interaction, Robin provides
4 a construct called a _reactor_. While normal S-expression evaluation
5 accomplishes side-effect-free computation, reactors permit the construction
6 of interactive programs. Reactors are similar to event handlers in
7 languages such as Javascript, or to `gen_server`s in Erlang.
8
9 In Robin, a reactor is installed by a top-level form with the syntax
10 `(reactor LIST-OF-SYMBOLS STATE-EXPR BODY-EXPR)`.
11
12 The first argument of the `reactor` form is a literal (unevaluated) list
13 of symbols, called the _subscriptions_ for the reactor. Each symbol names
14 a _facility_ with which the reactor wishes to be able to interact.
15
16 The second argument is evaluated, and becomes the _initial state_ of the
17 reactor.
18
19 The third argument is evaluated, presumably to a macro. This is called the
20 _body_ of the reactor.
21
22 Whenever an event of interest to the reactor (as determined by the facilities
23 with which the reactor requested interaction) occurs, the body is evaluated,
24 being passed three (pre-evaluated) arguments:
25
26 * A literal symbol called the _event code_, specifying what kind of event
27 happened;
28 * An arbitrary value called the _event payload_ containing more data about
29 the event, in a format specific to that kind of event; and
30 * The previous state of the reactor. (This will be the initial state
31 if the reactor body has never before been evaluated.)
32
33 The body is expected to return a list where the first element is the new
34 state of the reactor, and each of the subsequent elements is a _response_
35 to the facility. A response it iself a two-element list containing:
36
37 * A literal symbol called the _response code_ specifying the kind of
38 response to the event that is being made; and
39 * An arbitrary value called the _response payload_ containing more data
40 about the response, in a format specific to that kind of response.
41
42 There may of course be zero responses in the returned list. If the
43 returned value is not a list containing at least one element, no responses
44 will be made and the state of the reactor will remain unchanged.
45
46 It will be difficult to provide examples of how to use reactors without
47 introducing a concrete facility to react with, so we'll do that now.
48
49 Facility `line-terminal`
50 ------------------------
51
52 -> Tests for functionality "Interpret Robin Program (with Small)"
53
54 The `line-terminal` facility allows a Robin program to interact with a
55 terminal-based, line-buffered "standard I/O" a la Unix. Note that there is
56 nothing in the Robin language that requires this to be "the real standard
57 I/O"; Robin denies any knowledge of that sort of thing. It could well be
58 simulated with modal dialogue boxes in a GUI, or with textareas on an web
59 page under Javascript.
60
61 A reactor accessing the `line-terminal` facility may make responses in the
62 form
63
64 (writeln <STRING> <NEW-STATE>)
65
66 The `<STRING>` argument should be a Robin string (list of integers). Those
67 integers, as bytes, are sent to something that resembles the "standard output"
68 under Unix. (When attached to a terminal, this would typically cause an
69 ASCII representation of those bytes to be displayed.)
70
71 In the following example, the string is printed multiple times because the
72 reactor is reacting indiscriminately to multiple events — we'll get to that
73 in a second. In addition, note that this reactor essentially doesn't keep
74 any state — the initial state of the reactor is simply the integer 0, and
75 the state is set to 0 after each event is reacted to.
76
77 | (reactor (line-terminal) 0 (macro (self args env)
78 | (list 0 (list (literal writeln) (literal ''Hello, world!'')))))
79 = Hello, world!
80 = Hello, world!
81
82 Reactors which interact with `line-terminal` receive three kinds of events.
83
84 The first, `init`, is sent when the facility with which the reactor is
85 reacting initially becomes ready for use. In the example above, this is one
86 of the events actually being reacted to (even though we don't explicitly
87 check for it.) To make it explicit, and correct,
88
89 | (reactor (line-terminal) 0 (macro (self args env)
90 | (bind event (head args)
91 | (if (equal? event (literal init))
92 | (list 0 (list (literal writeln) (literal ''Hello, world!'')))
93 | (list 0)))))
94 = Hello, world!
95
96 The payload for `init` is not yet defined.
97
98 Note that the arguments to the reactor body come already-evaluated, so
99 there's no need to write it as a `fun` or to use `bind-args`.
100
101 The second event, `readln`, is sent when a line of text is received
102 on the "standard input". The payload for this event is a Robin string
103 of the line of text received. This string does not contain any end-of-line
104 marker characters.
105
106 Thus we can construct a simple `cat` program:
107
108 | (reactor (line-terminal) 0 (macro (self args env)
109 | (bind event (head args)
110 | (bind payload (head (tail args))
111 | (if (equal? event (literal readln))
112 | (list 0 (list (literal writeln) payload))
113 | (list 0))))))
114 + Cat
115 + Dog
116 = Cat
117 = Dog
118
119 The third event, `eof`, is sent when no more input is available
120 ("end of file") on the "standard input". Perhaps input was redirected
121 from a file and that file has come to an end, or perhaps the user pressed
122 Ctrl+D.
123
124 The payload for `eof` is not yet defined.
125
126 Here is an example of handling all three kinds of events:
127
128 | (reactor (line-terminal) 0 (macro (self args env)
129 | (bind event (head args)
130 | (bind payload (head (tail args))
131 | (choose
132 | ((equal? event (literal init))
133 | (list 0 (list (literal writeln) (literal ''Hello, world!''))))
134 | ((equal? event (literal readln))
135 | (list 0 (list (literal writeln) payload)))
136 | ((equal? event (literal eof))
137 | (list 0 (list (literal writeln) (literal ''Goodbye, world!''))))
138 | (else
139 | (list 0)))))))
140 + Cat
141 + Dog
142 = Hello, world!
143 = Cat
144 = Dog
145 = Goodbye, world!
146
147 A reactor accessing the `line-terminal` facility may also make responses in the
148 form
149
150 (close <ARG> <NEW-STATE>)
151
152 This informs the `line-terminal` facility that it is no longer needed by this
153 reactor, and can stop sending it events. The `<ARG>` is not yet defined.
154
155 So the "Hello, world" example above still isn't quite right; the only reason
156 it looks right is because the test suite is giving it an empty input, so it
157 gets an EOF and terminates. If you run it on the command line, the Robin
158 implementation will wait for more input after printing "Hello, world!".
159 (As is its wont. It's not expected to know that none of its reactors wants
160 or needs more input.)
161
162 To write it properly, in classic hello-world form, we'd have to say
163
164 | (reactor (line-terminal) 0 (macro (self args env)
165 | (bind event (head args)
166 | (if (equal? event (literal init))
167 | (list 0
168 | (list (literal writeln) (literal ''Hello, world!''))
169 | (list (literal close) 0))
170 | (list 0)))))
171 = Hello, world!
172
173 General Reactor properties
174 --------------------------
175
176 Facilities can handle multiple responses in response to an event.
177
178 | (reactor (line-terminal) 0 (macro (self args env)
179 | (bind event (head args)
180 | (bind payload (head (tail args))
181 | (if (equal? event (literal readln))
182 | (list 0
183 | (list (literal writeln) (literal ''Line:''))
184 | (list (literal writeln) payload))
185 | (list 0))))))
186 + Cat
187 + Dog
188 = Line:
189 = Cat
190 = Line:
191 = Dog
192
193 When receiving a malformed response, a facility may produce a warning
194 message of some kind, but it should otherwise ignore it and keep going.
195
196 | (reactor (line-terminal) 0 (macro (self args env)
197 | (bind event (head args)
198 | (bind payload (head (tail args))
199 | (if (equal? event (literal readln))
200 | (list 0
201 | (literal what-is-this)
202 | (literal i-dont-even)
203 | (list (literal writeln) payload))
204 | (list 0))))))
205 + Cat
206 + Dog
207 = Cat
208 = Dog
209
210 After a reactor closes, additional responses are ignored. (Thus, a close
211 response, if sent, should be last in the list.)
212
213 | (reactor (line-terminal) 0 (macro (self args env)
214 | (bind event (head args)
215 | (bind payload (head (tail args))
216 | (if (equal? event (literal init))
217 | (list 0
218 | (list (literal writeln) (literal ''Hello''))
219 | (list (literal close) 0)
220 | (list (literal writeln) (literal ''there'')))
221 | (list 0))))))
222 = Hello
223
224 Reactors can keep state.
225
226 | (define inc (macro (self args env)
227 | (subtract (eval env (head args)) (subtract 0 1))))
228 | (reactor (line-terminal) 65 (macro (self args env)
229 | (bind event (head args)
230 | (bind payload (head (tail args))
231 | (bind state (head (tail (tail args)))
232 | (if (equal? event (literal readln))
233 | (list (inc state) (list (literal writeln) (list state)))
234 | (list state)))))))
235 + Cat
236 + Dog
237 + Giraffe
238 = A
239 = B
240 = C
241
242 Multiple reactors can be installed for a facility.
243
244 | (define inc (macro (self args env)
245 | (subtract (eval env (head args)) (subtract 0 1))))
246 | (reactor (line-terminal) 65 (macro (self args env)
247 | (bind event (head args)
248 | (bind payload (head (tail args))
249 | (bind state (head (tail (tail args)))
250 | (if (equal? event (literal readln))
251 | (list (inc state) (list (literal writeln) (list state)))
252 | (list state)))))))
253 | (reactor (line-terminal) 0 (macro (self args env)
254 | (bind event (head args)
255 | (bind payload (head (tail args))
256 | (if (equal? event (literal readln))
257 | (list 0 (list (literal writeln) payload))
258 | (list 0))))))
259 + Cat
260 + Dog
261 + Giraffe
262 = Cat
263 = A
264 = Dog
265 = B
266 = Giraffe
267 = C
268
269 Reactors react in the *opposite* order they were installed.
270
271 | (define inc (macro (self args env)
272 | (subtract (eval env (head args)) (subtract 0 1))))
273 | (reactor (line-terminal) 0 (macro (self args env)
274 | (bind event (head args)
275 | (bind payload (head (tail args))
276 | (if (equal? event (literal readln))
277 | (list 0 (list (literal writeln) payload))
278 | (list 0))))))
279 | (reactor (line-terminal) 65 (macro (self args env)
280 | (bind event (head args)
281 | (bind payload (head (tail args))
282 | (bind state (head (tail (tail args)))
283 | (if (equal? event (literal readln))
284 | (list (inc state) (list (literal writeln) (list state)))
285 | (list state)))))))
286 + Cat
287 + Dog
288 + Giraffe
289 = A
290 = Cat
291 = B
292 = Dog
293 = C
294 = Giraffe
295
296 Closing one reactor does not stop others.
297
298 | (define inc (macro (self args env)
299 | (subtract (eval env (head args)) (subtract 0 1))))
300 | (reactor (line-terminal) 0 (macro (self args env)
301 | (bind event (head args)
302 | (bind payload (head (tail args))
303 | (if (equal? event (literal readln))
304 | (list 0 (list (literal writeln) payload))
305 | (list 0))))))
306 | (reactor (line-terminal) 65 (macro (self args env)
307 | (bind event (head args)
308 | (bind payload (head (tail args))
309 | (bind state (head (tail (tail args)))
310 | (if (equal? state 67)
311 | (list state (list (literal close) 0))
312 | (if (equal? event (literal readln))
313 | (list (inc state) (list (literal writeln) (list state)))
314 | (list state))))))))
315 + Cat
316 + Dog
317 + Giraffe
318 + Turkey
319 + Wallaby
320 = A
321 = Cat
322 = B
323 = Dog
324 = Giraffe
325 = Turkey
326 = Wallaby
327
328 In fact the `init` event type and the `close` response are not specific
329 to `line-terminal`, but rather, generic; every facility that a reactor can
330 react to should send and understand them.
331
332 This leaves some open questions about reactors (and so their semantics
333 will definitely change slightly in a subsequent 0.x version of Robin.)
334 Namely:
335
336 * How does the reactor know which facility the `init` is for?
337 * Can a reactor response with a `close` to a facility other than the
338 facility that sent it the event it is currently handling?
339 * Currently reactors cannot communicate with each other at all.
340 How can reactors communicate with each other? (Our idea is to have
341 a "reactor bus" facility which can relay responses from one reactor
342 into an event for another reactor.)
0 Robin
1 =====
2
3 This document defines the fundamental semantics of Robin (except for the
4 meanings of the intrinsics: see `Intrinsics.markdown` for those.)
5
6 -> Tests for functionality "Interpret core Robin Program"
7
8 Top-level S-expressions
9 -----------------------
10
11 A Robin program consists of a series of "top-level" S-expressions.
12 Each top-level S-expression must have a particular form, but most of these
13 top-level S-expressions may contain general, evaluatable S-expressions
14 themselves. Allowable top-level forms are given in the subsections below.
15
16 ### `display` ###
17
18 `(display EXPR)` evaluates the <expr> and displays the result in a canonical
19 S-expression rendering, followed by a newline.
20
21 | (display #t)
22 = #t
23
24 Note that a Robin program may be split over several files in the filesystem.
25 Also, more than one top-level S-expression may appear in a single file.
26
27 | (display #t)
28 | (display #f)
29 = #t
30 = #f
31
32 ### `define` ###
33
34 `(define ATOM EXPR)` defines a global name.
35
36 | (define true #t)
37 | (display true)
38 = #t
39
40 You may not try to define anything that's not an atom.
41
42 | (define #f #t)
43 | (display #f)
44 ? illegal top-level form: (define #f #t)
45
46 You may define multiple names.
47
48 | (define true #t)
49 | (define false #f)
50 | (display false)
51 | (display true)
52 = #f
53 = #t
54
55 Names may not be redefined once defined.
56
57 | (define true #t)
58 | (define true #f)
59 ? symbol already defined: true
60
61 ### `reactor` ###
62
63 `(reactor LIST-OF-ATOMS STATE-EXPR BODY-EXPR)` installs a reactor. Reactors
64 permit the construction of interactive Robin programs. See the document
65 `Reactor.markdown` for more information on, examples of, and tests for reactors.
66
67 Intrinsic Data Types
68 --------------------
69
70 ### S-expressions ###
71
72 An S-expression is a sort of catch-all data type which includes
73 all the other data types. It is inductively defined as follows:
74
75 * A symbol is an S-expression.
76 * A boolean is an S-expression.
77 * An integer is an S-expression.
78 * A macro is an S-expression.
79 * An intrinsic is an S-expression.
80 * An empty list is an S-expression.
81 * A list cell containing an S-expression, prepended to another list,
82 is an S-expression.
83 * Nothing else is an S-expression.
84
85 S-expressions have a textual representation, but not all types have values
86 that can be directly expressed in this textual representation. All
87 S-expressions have some meaning when interpeted as Robin programs, as
88 defined by Robin's evaluation rules, but that meaning might be to
89 raise an exception to indicate an error.
90
91 ### Symbol ###
92
93 A symbol is an atomic value represented by a string of characters
94 which may not include whitespace or parentheses or a few other
95 characters (TODO: decide which ones) and which may not begin with
96 a `#` (pound sign) or a few other characters (TODO: decide which
97 ones.)
98
99 When in a Robin program proper, a symbol can be bound to a value, and
100 in this context is it referred to as an _identifier_. However, if an
101 attempt is made to evaluate a symbol which is not bound to an identifier,
102 an exception will be raised. For a symbol to appear unevaluated in a Robin
103 program, it must be an argument to a macro. For that reason, we can't
104 show an example of a literal symbol without first defining a macro... but
105 will go ahead and show the example, and will explain macros later.
106
107 | (define literal (@macro (self args env) (@head args)))
108 | (display (literal hello))
109 = hello
110
111 A Robin implementation is not expected to be able to generate new symbols
112 at runtime.
113
114 Symbols can be applied, and that is the typical use of them. But actually,
115 it is what the symbol is bound to in the environment that is applied.
116
117 ### Booleans ###
118
119 There are two values of Boolean type, `#t`, representing truth, and `#f`,
120 representing falsehood. By convention, an identifier which ends in `?`
121 is a macro or function which evaluates to a Boolean. The `@if` intrinsic
122 expects a Boolean expression as its first argument.
123
124 Booleans always evaluate to themselves.
125
126 | (display #t)
127 = #t
128
129 | (display #f)
130 = #f
131
132 Booleans cannot be applied.
133
134 | (display (#t 1 2 3))
135 ? uncaught exception: (inapplicable-object #t)
136
137 ### Integers ###
138
139 An integer, in the context of Robin, is always a 32-bit signed integer.
140 If you want larger integers or rational numbers, you'll need to build a
141 bigint library or such.
142
143 For example, 5 is an integer:
144
145 | (display 5)
146 = 5
147
148 Whereas 6167172726261721 is not, and you get the 32-bit signed integer
149 equivalent:
150
151 | (display 6167172726261721)
152 = -878835751
153
154 Integers always evaluate to themselves.
155
156 Integers cannot be applied.
157
158 | (display (900 1 2 3))
159 ? uncaught exception: (inapplicable-object 900)
160
161 ### Macros ###
162
163 A macro is an S-expression, in an environment, which describes how to
164 translate one S-expression to another.
165
166 One area where Robin diverges heavily from Lisp and Scheme is that,
167 whereas Lisp and Scheme support macro capabilities, in Robin, the macro
168 is a **fundamental type**. Other abstractions, such as function values, are
169 built on top of macros. Macros are first-class objects that may exist
170 at runtime and can evaluate to other macros. Therefore, the word "macro"
171 has, perhaps, a slightly different meaning in Robin than in Lisp or Scheme.
172
173 They can also be compared to the one-argument `lambda` form from PicoLisp;
174 again, however, unlike PicoLisp's variety of `lambda` forms, Robin's
175 macros are the *only* abstraction of this kind fundamentally available, and
176 other such abstractions *must* be built on top of macros.
177
178 Whereas a function evaluates each of its arguments to values, and
179 binds each of those values to a formal parameter of the function, then
180 evaluates the body of the function in that new environment, a macro:
181
182 * binds the macro value itself to the first formal parameter of the
183 macro (by convention called `self`) — this is to facilitate writing
184 recursive macros;
185 * binds the literal tail of the list of the macro application to
186 the second formal parameter of the macro (by convention called `args`);
187 * binds a binding alist representing the environment in effect at the
188 point the macro was evaluated to the third formal parameter (by
189 convention called `env`); and
190 * evaluates the body of the macro in that environment.
191
192 Macros are defined with the `@macro` intrinsic.
193
194 Macros evaluate to themselves.
195
196 Macros are represented as the S-expression expansion of their
197 implementation.
198
199 | (display
200 | (@macro (self args env) args))
201 = (@macro (self args env) args)
202
203 Macros can be applied, and that is the typical use of them.
204
205 ### Intrinsics ###
206
207 (This section needs rewriting.)
208
209 There also exist functions which cannot effectively be expressed directly
210 in Robin — these are the so-called _intrinsics_. All symbols representing
211 intrinsics directly begin with the character `@`.
212
213 One important intrinsic is `@eval`. Many macros will make use of `eval`,
214 to evaluate that literal tail they receive. When they do this in the
215 environment in which they were called, they behave a lot like functions.
216 But they are not obligated to; they might evaluate them in a modified
217 environment, or not evaluate them at all and treat them as a literal
218 S-expression.
219
220 Intrinsics evaluate to themselves.
221
222 An intrinsic is represented thusly.
223
224 | (display @head)
225 = @head
226
227 One upshot of intrinsics is that all intrinsic Robin functionality
228 (excepting top-level forms) can be passed around as values.
229
230 | (display
231 | (@prepend @if (@prepend @head ())))
232 = (@if @head)
233
234 Intrinsics can be applied, and that is the typical use of them.
235
236 ### Lists ###
237
238 A list is either the empty list, or a list cell containing a value of any
239 type, prepended to another list.
240
241 The "head" of a list cell is the value (of any type) that it contains;
242 the "tail" is the other list that it is prepended to. The empty list
243 has neither head nor tail.
244
245 Lists have a literal representation in Robin's S-expression based
246 syntax.
247
248 The empty list is notated `()` and it evaluates to itself.
249
250 | (display
251 | ())
252 = ()
253
254 A list with several elements is notated as a sequence of those
255 elements, preceded by a `(`, followed by a `)`, and delimited
256 by whitespace.
257
258 Lists do not evaluate to themselves; rather, they represent a macro
259 application. However, the `literal` macro may be used to obtain a
260 literal list.
261
262 | (define literal (@macro (s a e) (@head a)))
263 | (display
264 | (literal (7 8)))
265 = (7 8)
266
267 Lists cannot be directly applied, but since a list itself represents an
268 application, that application is undertaken, and the result of it can
269 be applied.
270
271 Conventional Data Types
272 -----------------------
273
274 This section lists data types that are not intrinsic, but are rather
275 arrangements of intrinsic types in a way that follows a convention.
276
277 ### Strings ###
278
279 Strings are just lists of integers, where each integer refers to a
280 particular Unicode codepoint. Robin supports a sugared syntax for
281 specifying literal strings. The characters of the string are given
282 between pairs of single quotes.
283
284 | (define literal (@macro (s a e) (@head a)))
285 | (display
286 | (literal ''Hello''))
287 = (72 101 108 108 111)
288
289 A single single quote may appear in string literals of this kind.
290
291 | (define literal (@macro (s a e) (@head a)))
292 | (display
293 | (literal ''He'llo''))
294 = (72 101 39 108 108 111)
295
296 Between the single quotes delimiting the string literal, a *sentinel*
297 may be given. The sentinel between the leading single quote pair must
298 match the sentinel given between the trailing single quote pair. The
299 sentinel may consist of any text not containing a single quote.
300
301 | (define literal (@macro (s a e) (@head a)))
302 | (display
303 | (literal 'X'Hello'X'))
304 = (72 101 108 108 111)
305
306 | (define literal (@macro (s a e) (@head a)))
307 | (display
308 | (literal '...@('Hello'...@('))
309 = (72 101 108 108 111)
310
311 | (define literal (@macro (s a e) (@head a)))
312 | (display
313 | (literal 'X'Hello'Y'))
314 ? unexpected end of input
315
316 A sentinelized literal like this may embed a pair of single quotes.
317
318 | (define literal (@macro (s a e) (@head a)))
319 | (display
320 | (literal 'X'Hel''lo'X'))
321 = (72 101 108 39 39 108 111)
322
323 By choosing different sentinels, string literals may contain any other
324 string literal.
325
326 | (define literal (@macro (s a e) (@head a)))
327 | (display
328 | (literal 'X'Hel'Y'bye'Y'lo'X'))
329 = (72 101 108 39 89 39 98 121 101 39 89 39 108 111)
330
331 No interpolation of escape sequences is done in a Robin string literal.
332 (Functions to convert escape sequences commonly found in other languages
333 may one day be available in a standard module.)
334
335 | (define literal (@macro (s a e) (@head a)))
336 | (display
337 | (literal ''Hello\nworld''))
338 = (72 101 108 108 111 92 110 119 111 114 108 100)
339
340 All characters which appear in the source text between the delimiters
341 of the string literal are literally included in the string.
342
343 | (define literal (@macro (s a e) (@head a)))
344 | (display
345 | (literal ''Hello
346 | world''))
347 = (72 101 108 108 111 10 119 111 114 108 100)
348
349 Adjacent string literals are not automatically concatenated.
350
351 | (define literal (@macro (s a e) (@head a)))
352 | (display
353 | (literal (''Hello'' ''world'')))
354 = ((72 101 108 108 111) (119 111 114 108 100))
355
356 ### Alists ###
357
358 An alist, short for "association list", is simply a list of two-element
359 sublists. The idea is that each of these two-elements associates, in some
360 context, the value of its first element with the value of its second element.
361
362 ### Binding Alists ###
363
364 When the first element of each two-element sublist in an alist is a symbol,
365 we call it a _binding alist_. The idea is that it is a Robin representation
366 of an evaluation environment, where the symbols in the heads of the sublists
367 are bound to the values in the tails of the pairs. Binding alists can be
368 created from an environment in effect (such as in the third argument of a
369 macro) and can be used to change the evaluation environment in effect (such
370 as in the first argument to `eval`.)
371
372 TODO: binding alists will be replaced by abstract map objects of some kind.
373
374 Comments
375 --------
376
377 Any S-expression preceded by a `;` symbol is a comment. It will still
378 be parsed, but it will be ignored.
379
380 | (display
381 | ;(this program produces a list of two booleans)
382 | (@prepend #f (@prepend #f ())))
383 = (#f #f)
384
385 Because S-expressions may nest, and because comments may appear
386 inside S-expressions, comments may nest.
387
388 | (display
389 | ;(this program produces
390 | ;(what you might call)
391 | a list of two booleans)
392 | (@prepend #f (@prepend #f ())))
393 = (#f #f)
394
395 Comments are still parsed. A syntax error in a comment is an error.
396
397 | (display
398 | ;(this program produces
399 | #k
400 | a list of booleans)
401 | (prepend #f (prepend #f ())))
402 ? (line 3, column 6):
403 ? unexpected "k"
404 ? expecting "t" or "f"
405
406 Any number of comments may appear together.
407
408 | (display
409 | (@prepend ;what ;on ;earth #f (@prepend #f ())))
410 = (#f #f)
411
412 Comments may appear before a closing parenthesis.
413
414 | (display
415 | (@prepend #f (@prepend #f ()) ;foo))
416 = (#f #f)
417
418 | (display
419 | (@prepend #f (@prepend #f ()) ;peace ;(on) ;earth))
420 = (#f #f)
421
422 Comments may appear in an empty list.
423
424 | (display
425 | ( ;hi ;there))
426 = ()
427
428 Comments need not be preceded by spaces.
429
430 | (display
431 | (;north;by;north;west))
432 = ()
433
434 To put truly arbitrary text in a comment, the string sugar syntax may be
435 used.
436
437 | (display
438 | ;''This program, it produces a list of two booleans. #k ?''
439 | (@prepend #f (@prepend #f ())))
440 = (#f #f)
+0
-240
doc/Static_Analysis.markdown less more
0 Robin's Approach to Static Analysis
1 ===================================
2
3 This document is a draft. It contains a bunch of not-necessarily
4 well-integrated notes on how Robin approaches the problem of static
5 analysis.
6
7 > Static analysis is abstract interpretation, and abstract
8 > interpretation is just interpretation over a different domain.
9
10 Static Analysis
11 ---------------
12
13 Robin itself does not define any system of static analysis. It has a
14 (latent) system of types, but does not require any type mismatch to
15 be detected at any point in time before the expression involving that
16 type mismatch is evaluated.
17
18 There is a reason for this. Just as functionality is not built-in
19 to the language but rather provided in modules, so too is static
20 analysis not built-in to the language; different type systems (and
21 other sets of correctness rules) of differing strengths can be applied
22 in a modular fashion to Robin programs (and, in a fine-grained fashion,
23 to individual Robin modules.)
24
25 (This already happens with other languages, but in a perhaps less
26 structured fashion. The classic tool `lint` analyzes C programs using
27 a type system more restrictive than that defined by C itself [cite
28 Dragon book here]. The tool `pyflakes` checks more rules about Python
29 programs than the Python language defines, and so forth.)
30
31 At the same time, I'd like Robin itself to be amenable to various
32 forms of static analysis. That Robin itself defines very few rules for
33 static correctness should not be taken as advocacy for dynamic typing;
34 rather, it should be taken as advocacy for letting each developer choose
35 the level of static analysis they wish to apply.
36
37 `macro` and `eval`
38 ------------------
39
40 The choice of `macro` as one of the fundamental abstractions, and the
41 corresponding requirement to use `eval` to implement things like
42 functions on top of it, seem to pose some barriers to static analysis.
43
44 And, they do make some things harder. But, these barriers are not
45 insurmountable.
46
47 One of the difficulties of `eval` in non-homoiconic languages (for
48 example, `exec` in Python) is that the expression being evaluated
49 exists as a string of Python code. To analyze it, it must be parsed.
50 Since, in Robin, the thing being `eval`ed is simply a term, no parsing
51 need take place.
52
53 In a sense, we're `eval`ing things everywhere anyway; `eval` is simply
54 an explicit invokation of this on a term which is not known in advance.
55 We can say, rather, that it is not known *entirely* in advance. If we
56 know some properties about term we are `eval`ing, we can know more
57 about what to expect of the result of its evaluation. In other words,
58 we can use static analysis to help us (somewhat) in our static analysis.
59
60 As a more concrete example, if we have a macro which `eval`s one of its
61 arguments in an unaltered environment (i.e. the very same value that
62 the macro was passed in its third argument,) we know just as much about
63 that evaluation as we would any argument to any function. A static
64 analyzer can detect this case by checking what it knows about the values
65 of the bindings we are passing to `eval`.
66
67 And of course, it is always an option to punt. There will always be
68 terms that have some property, but which no static analyzer can prove
69 have that property. If it is simply too complex to prove some property
70 of `macro` expressions, the static analyzer can always say it doesn't
71 know; it is still useful on programs, or parts of programs, which do
72 not contain `macro` expresions.
73
74 Constructing Static Analyzers
75 -----------------------------
76
77 We can take the "static analyses are modules" paradigm quite far in
78 Robin. Since Robin allows metadata to be associated with every value,
79 we may record properties we have proved about a value on that value,
80 and use these established properties to check further proofs of properties.
81
82 In other words, we can write Robin macros which statically check their
83 contents, and only evaluate to a value if their contents pass that
84 check. In this sense, different static analyses really *could* be
85 available in different Robin modules. For example, a module `total`
86 could export an identifier `fun` which shadows `small`'s `fun`, and
87 which only evaluates to a function value if it can prove that the
88 function being defined always halts. (Otherwise, it would presumably
89 raise an exception.)
90
91 In this way, Robin could provide tools for static analysis, of the same
92 sort that mainstream languages like Java and C and Haskell support, while
93 not abandoning the "it's not a programming language, it's a building
94 material" flexibility of it's homoiconic Lisp and Scheme heritage. In
95 addition (as I've already mentioned, but just to stress the point,) any
96 number of different static analyses, of different strengths, for different
97 purposes, could be applied to different modules (or even perhaps different
98 parts of the same program), giving the developer a wide range of choices
99 between flexibility and confidence in correctness.
100
101 I don't expect this will be easy, of course, but I do hope it is somehow
102 possible.
103
104 Some Implications of this Approach
105 ----------------------------------
106
107 The "static" in "static analysis" means that the code is analyzed without
108 running it; it does not strictly mean that it happens *before the code is
109 run*. Since, in Robin, you (the programmer) write static analyzers in
110 Robin, then it's your responsibility to make sure they run when you want
111 them to run (and yes, typically this will be before the code itself is
112 run; otherwise you might as well just not have any static analysis, and
113 wait for incorrect code to crash when it runs.)
114
115 Fortuitously, there is a convenient time to run static analyses on a
116 module -- when that module is imported. The code to construct the
117 environment exported by the module needs to run at that point anyway, and
118 the static analysis might as well run then too. This also means that
119 statically analyzing a set of a modules is as simple as constructing a
120 test program which simply imports all of those modules; if any of them
121 fail static analysis, an exception will be thrown at import time:
122
123 (robin (0 1) ((foo (0 1) *) (bar (0 1) *) (baz (0 1) *))
124 #t)
125
126 There is also room here for optimization. If static analysis for a module
127 happens at module-import time, the implementation, after successfully
128 importing a module, can create an equivalent version of the module by
129 replacing each instance of a checked function definition with an unchecked
130 function definition. This version will be weaker from an analysis
131 perspective, but that won't matter, since the equivalent module has already
132 been checked; and the weaker module will be more efficient, at least during
133 import.
134
135 Another implication of running static analyzers "in" the code they are
136 statically analyzing -- and this relates to having the option to punt --
137 is that they, like the rest of your program, may not be perfect. In the
138 end, they are constructed from the same goo as the rest of your program,
139 and to have confidence that those goo formations do what you expect them
140 to, you should have tests for them. If a static analyzer is imperfect,
141 this just means you can't rely on it as heavily as you could if it was
142 perfect; it doesn't mean you can't still use it. When you think about it,
143 the static analyzer in some Java compiler you're using might contain a bug,
144 too, but such a bug might be harder for you to fix, what with that compiler
145 possibly being written in a different language. (The flip side of this is
146 that Robin's static analyzers ought, in some cases at least, to be able to
147 analyze themselves easily -- leading to better confidence that the analyzers
148 themselves are correct.)
149
150 Yet another implication is the impact this splitting off of static analysis
151 from the language per se has on coding style. Often, the simplest way to
152 code a function does not handle errors well, or consistently. Take, for
153 example, `export`. It would be useful, from a software engineering stand-
154 point, to be made aware of when you're trying to `export` a binding which
155 doesn't exist (maybe you made a typo.) But the most straightforward way
156 to implement `export` is as a `filter` over the environment. Making
157 `export` raise an exception if one of the identifiers you listed doesn't
158 exist in the environment would mean adding a dynamic check to the
159 implementation of `export` that roughly doubles its complexity. It seems
160 that the Robin approach would be to avoid that complexity and keep the
161 definition of `export` simple, even though it is not quite as useful as it
162 could be; and make up for it with a static analysis to catch such problems
163 later on in the game.
164
165 Concrete Applications
166 ---------------------
167
168 Let's provide an overview of some of the possible concrete applications of
169 static analysis in Robin.
170
171 `consistent`
172 ------------
173
174 An expression is consistent if each identifier used in the expression is
175 bound to some value in the environment in effect in the place that it is
176 used.
177
178 This is a fairly simple analysis (and probably should have been the one
179 I started working on first, instead of `pure`.)
180
181 A better(?) name for this analysis might be `bound`.
182
183 `non-shadowing`
184 ---------------
185
186 An expression is non-shadowing if it does not redefine any names, i.e.
187 it does not bind a value to an identifier to which a value is already
188 bound.
189
190 `pure`
191 ------
192
193 A macro is referentially transparent if, for every set of possible particular
194 actual arguments, it always evaluates to the same particular result value.
195
196 "Referentially transparent" is a bit of a mouthful, so in Robin, we (for
197 better or worse) call macros with this property *pure*.
198
199 There is a convention that macros that are not pure are bound to names that
200 end with an exclamation point (`!`). However, this is a convention, and so
201 is not enforced; also, purity analysis deals with the values themselves, not
202 the names they may or may not be bound to.
203
204 For more information on `pure`, see [the documentation for the `pure`
205 module](module/Pure.falderal).
206
207 `constant`
208 ----------
209
210 On top of `pure` we can easily build another level of static analysis,
211 `constant`. An expression is constant if it is a literal, or if it
212 an application of a pure, constant function to constant arguments.
213
214 `constant` and `pure` actually feed back into each other, which makes
215 this even more complex: the `eval`ing of a `constant` value inside a
216 function may make that function `pure`, whereas if it is not a `constant`
217 value, there might be no way to prove this.
218
219 `total`
220 -------
221
222 A macro is total if it always terminates. In the general case, this is
223 undecidable. However, it is not too difficult to analyze a macro and
224 determine that it is primitive recursive, and all primitive recursive
225 functions are total.
226
227 `non-raising`
228 -------------
229
230 An expression is non-raising if executing it cannot possibly raise an
231 exception. (The simplest way to achieve this is to catch everything at
232 a high level, and not raise anything in the exception handler.)
233 Java does an analysis similar to this.
234
235 `consistent-export`
236 -------------------
237
238 A module has consistent exports if it does not try to `export` an unbound
239 identifier. This is more-or-less a special case of `consistent`.
+0
-144
doc/Style.markdown less more
0 Robin Style Guidelines
1 ======================
2
3 Modules
4 -------
5
6 * Modules should be deterministic. They should always export the same
7 bindings (the same names bound to the same values) each time they
8 are imported.
9
10 * Don't do input or output in a module. (Logging is a different matter,
11 or at least it will be, when Robin gets a `logging` module.)
12
13 Naming
14 ------
15
16 * Module names should be singular: `list`, not `lists`.
17
18 * Don't smoosh names together; use hyphens to seperate individual
19 words inside an identifier. `get-args`, not `getargs`.
20
21 * Use established terminology from functional programming (Scheme,
22 Haskell) when appropriate.
23
24 * Avoid atavisms like `car` and `cdr`.
25
26 * Avoid jargon unless there is no clearer option.
27
28 * Avoid bland, generic names unless your function is truly generic
29 itself. Examples: `data`, `index`, `pick`, `content`.
30
31 * Don't abbreviate unless the abbreviation is essentially unambiguous.
32
33 * Referential transparency: still working this out, and probably
34 deserves a document to itself. Robin isn't an imperative language,
35 so the convention of ending an identifier with `!` doesn't really
36 apply; but it can have side-effects. Maybe:
37
38 * No symbol at end: this function always evaluates to the same
39 value, given the same arguments.
40
41 * Ends with `>`: this function may send messages, but does not
42 receive messages, so it always evaluates to the same value *and*
43 sends the same set of outgoing messages, given the same arguments.
44
45 * Ends with `<`: this function may receive messages, but does not
46 send messages, so it always evaluates to the same value given the
47 same arguments *and* the same set of incoming messages.
48
49 * Ends with `!`: this function may send and receive messages.
50
51 For the nonce, I'm going to go with `!` indicating that the macro
52 may have side-effects. However, this should ultimately be handled at
53 a more semantic level. Functions should be able to be defined as
54 not having side-effects, and the function-definition macro should
55 check this is the case (i.e. that the function never calls anything
56 [which calls anything] which may have side-effects), and certain
57 call sites should not allow functions to be called which may have
58 side-effects.
59
60 * Identifiers for macros which take their argument, analyze its
61 structure, then either raise an exception if the structure is
62 unacceptable, or evaluate it as an expression if it is acceptable,
63 should end with `:`. So we might have:
64
65 (pure: (total: (fun (a b) (+ (list:length a) (list:length b)))))
66
67 Unfortunately, this clashes with `:` as a module seperator. Like,
68
69 (foo:pure: (bar:total: ... ))
70
71 So, we'll maybe switch to `.` as the module seperator, assuming that
72 improper lists go away:
73
74 (foo.pure: (bar.total:
75 (fun (a b)
76 (+ (list.length a) (list.length b)))))
77
78 Associative Binary Operators
79 ----------------------------
80
81 When defining a macro which implements a binary operation which is
82 associative, write three versions:
83
84 * First write the basic version; this should take two arguments and be named
85 with the natural-language word of the operation. This version is useful
86 because it has the simplest definition to which one can refer, and can be
87 used in the definition of the next two versions.
88
89 * Then write a version which takes any number of arguments. The minimum
90 number may be zero, one, or two, depending on the nature of the operation,
91 but there should be no limit to the number of arguments; the operation can
92 be applied successively to all of the arguments, two at a time. This
93 version can be named after the common mathematical symbol for the operation
94 if one exists, or, if not, the name of the first version suffixed with `*`.
95
96 There should be a macro which lets you derive this version in a higher-
97 order way from the first version, but currently that support does not
98 exist.
99
100 * Then write a version which takes a list, and applies the operation to all
101 of the arguments in the list. This version can be written by passing the
102 first version to the appropriate `fold`. Often the name of this can be
103 based on a different natural-language word than the binary operation would
104 have, but if no such word is appropriate, use the name of the first version
105 suffixed with `-list`.
106
107 Examples from the standard modules:
108
109 * `add`, `+`, and `sum`
110 * `multiply`, `*`, and `product`
111 * `and`, `and*`, and `conj`
112 * `or`, `or*`, and `disj`
113 * `gt?`, `>`, and `strictly-decreasing?`
114 * `gte?`, `>=`, and `decreasing?`
115 * `lt?`, `<`, and `strictly-increasing?`
116 * `lte?`, `<=`, and `increasing?`
117 * `equal?`, `=`, and `same?`
118
119 All three versions may take advantage of short-circuiting, but the third
120 version has a weaker form: all of the elements of the list must be evaluated
121 first in order for the list to be constructed, but the operation may not
122 examine all elements of the list to compute its result.
123
124 These details still need to be worked out:
125
126 * A sufficiently clever analyzer can convert the first into successive
127 applications of a single two-argument version of the macro, and the
128 second into this form as well if all of the members of the list are
129 known at analysis time.
130
131 * A purity analysis may be applied to check if this conversion can
132 happen. The macros so defined should be decorated with metadata which
133 associates each with the other for the purposes of analysis and
134 conversion.
135
136 Conditionals
137 ------------
138
139 * As much as possible, write `choose` structures where the branches
140 are all _disjoint_: whenever one branch is true, all other branches
141 must necessarily be false. Also comment the conditions under which
142 the `else` branch will be true. (This style guideline is in lieu
143 of a program analysis which can determine this for you.)
+0
-793
doc/module/Arithmetic.markdown less more
0 Module `arith`
1 ==============
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 ### `add` ###
6
7 `add` evaluates both of its arguments to numbers and evaluates to the sum
8 of those two numbers.
9
10 | (robin (0 1) ((arith (0 1)))
11 | (arith:add 14 23))
12 = 37
13
14 `add` expects exactly two arguments.
15
16 | (robin (0 1) ((arith (0 1) *))
17 | (add 14))
18 ? uncaught exception: (illegal-arguments (14))
19
20 | (robin (0 1) ((arith (0 1) *))
21 | (add 6 7 7))
22 ? uncaught exception: (illegal-arguments (6 7 7))
23
24 Both of the arguments to `add` must be numbers.
25
26 | (robin (0 1) ((arith (0 1) *))
27 | (add 14 #t))
28 ? uncaught exception: (expected-number #t)
29
30 | (robin (0 1) ((arith (0 1) *))
31 | (add #t 51))
32 ? uncaught exception: (expected-number #t)
33
34 ### `+` ###
35
36 `+` evaluates all of its arguments to numbers and evaluates to the sum
37 of those numbers.
38
39 | (robin (0 1) ((arith (0 1) *))
40 | (+ 14 23))
41 = 37
42
43 `+` can accept any number of arguments.
44
45 | (robin (0 1) ((arith (0 1) *))
46 | (+ 14 23 53))
47 = 90
48
49 `+` with no arguments evaluates to zero.
50
51 | (robin (0 1) ((arith (0 1) *))
52 | (+))
53 = 0
54
55 `+` with one argument is an identity function on numbers.
56
57 | (robin (0 1) ((arith (0 1) *))
58 | (+ 7))
59 = 7
60
61 All of the arguments to `+` must be numbers.
62
63 | (robin (0 1) ((arith (0 1) *))
64 | (+ 14 #t))
65 ? uncaught exception: (expected-number #t)
66
67 | (robin (0 1) ((arith (0 1) *))
68 | (+ #t 51))
69 ? uncaught exception: (expected-number #t)
70
71 ### `sum` ###
72
73 `sum` evaluates its single argument to a list of numbers. It then evaluates
74 to the sum of all of the numbers in the list.
75
76 | (robin (0 1) ((arith (0 1)) (small (0 1)))
77 | (arith:sum (small:list 77 35 128 4)))
78 = 244
79
80 `sum` of an empty list is zero.
81
82 | (robin (0 1) ((arith (0 1)))
83 | (arith:sum ()))
84 = 0
85
86 `sum` expects exactly one argument.
87
88 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
89 | (sum (list 4 5) (list 6 7)))
90 ? uncaught exception: (illegal-arguments ((list 4 5) (list 6 7)))
91
92 | (robin (0 1) ((arith (0 1) *))
93 | (sum))
94 ? uncaught exception: (illegal-arguments ())
95
96 `sum` expects its one argument to be a list.
97
98 | (robin (0 1) ((arith (0 1) *))
99 | (sum 41))
100 ? uncaught exception: (expected-list 41)
101
102 `sum` expects its list to contain only numbers.
103
104 | (robin (0 1) ((arith (0 1) *) (small (0 1)))
105 | (sum (small:list 4 5 6 #t 7 8)))
106 ? uncaught exception: (expected-number #t)
107
108 ### `-` ###
109
110 `-` evaluates both of its arguments to numbers and evaluates to the difference
111 of the second number from the first.
112
113 | (robin (0 1) ((arith (0 1) *))
114 | (- 23 10))
115 = 13
116
117 `-` expects exactly two arguments, both numbers.
118
119 | (robin (0 1) ((arith (0 1) *))
120 | (- 14))
121 ? uncaught exception: (illegal-arguments (14))
122
123 | (robin (0 1) ((arith (0 1) *))
124 | (- 14 23 57))
125 ? uncaught exception: (illegal-arguments (14 23 57))
126
127 | (robin (0 1) ((arith (0 1) *))
128 | (- 14 #t))
129 ? uncaught exception: (expected-number #t)
130
131 | (robin (0 1) ((arith (0 1) *))
132 | (- #t 51))
133 ? uncaught exception: (expected-number #t)
134
135 ### `multiply` ###
136
137 `multiply` evaluates both of its arguments to numbers and evaluates to the product
138 of those two numbers.
139
140 | (robin (0 1) ((arith (0 1)))
141 | (arith:multiply 6 7))
142 = 42
143
144 `multiply` expects exactly two arguments.
145
146 | (robin (0 1) ((arith (0 1) *))
147 | (multiply 14))
148 ? uncaught exception: (illegal-arguments (14))
149
150 | (robin (0 1) ((arith (0 1) *))
151 | (multiply 6 7 7))
152 ? uncaught exception: (illegal-arguments (6 7 7))
153
154 Both of the arguments to `multiply` must be numbers.
155
156 | (robin (0 1) ((arith (0 1) *))
157 | (multiply 14 #t))
158 ? uncaught exception: (expected-number #t)
159
160 | (robin (0 1) ((arith (0 1) *))
161 | (multiply #t 51))
162 ? uncaught exception: (expected-number #t)
163
164 ### `*` ###
165
166 `*` evaluates all of its arguments to numbers and evaluates to the product
167 of those numbers.
168
169 | (robin (0 1) ((arith (0 1) *))
170 | (* 23 10))
171 = 230
172
173 `*` can accept any number of arguments.
174
175 | (robin (0 1) ((arith (0 1) *))
176 | (* 3 4 5))
177 = 60
178
179 `*` with no arguments evaluates to one.
180
181 | (robin (0 1) ((arith (0 1) *))
182 | (*))
183 = 1
184
185 `*` with one argument is an identity function on numbers.
186
187 | (robin (0 1) ((arith (0 1) *))
188 | (* 7/8))
189 = 7/8
190
191 `*` expects all of its arguments to be numbers.
192
193 | (robin (0 1) ((arith (0 1) *))
194 | (* 14 #t))
195 ? uncaught exception: (expected-number #t)
196
197 | (robin (0 1) ((arith (0 1) *))
198 | (* #t 51))
199 ? uncaught exception: (expected-number #t)
200
201 ### `product` ###
202
203 `product` evaluates its single argument to a list of numbers. It then evaluates
204 to the product of all of the numbers in the list.
205
206 | (robin (0 1) ((arith (0 1)) (small (0 1)))
207 | (arith:product (small:list 5 7 9 3)))
208 = 945
209
210 `product` of an empty list is one.
211
212 | (robin (0 1) ((arith (0 1)))
213 | (arith:product ()))
214 = 1
215
216 `product` expects exactly one argument.
217
218 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
219 | (product (list 4 5) (list 6 7)))
220 ? uncaught exception: (illegal-arguments ((list 4 5) (list 6 7)))
221
222 | (robin (0 1) ((arith (0 1) *))
223 | (product))
224 ? uncaught exception: (illegal-arguments ())
225
226 `product` expects its one argument to be a list.
227
228 | (robin (0 1) ((arith (0 1) *))
229 | (product 7))
230 ? uncaught exception: (expected-list 7)
231
232 `product` expects its list to contain only numbers.
233
234 | (robin (0 1) ((arith (0 1) *) (small (0 1)))
235 | (product (small:list 4 5 6 #t 7 8)))
236 ? uncaught exception: (expected-number #t)
237
238 ### `/` ###
239
240 `/` evaluates both of its arguments to numbers and evaluates to the
241 first number divided by the second.
242
243 | (robin (0 1) ((arith (0 1) *))
244 | (/ 33 11))
245 = 3
246
247 `/` works on any rational numbers, not just integers.
248
249 | (robin (0 1) ((arith (0 1) *))
250 | (/ 33 4))
251 = 33/4
252
253 | (robin (0 1) ((arith (0 1) *))
254 | (/ (- 0 33) 4))
255 = -33/4
256
257 Division by zero is undefined, and an exception will be raised.
258
259 | (robin (0 1) ((arith (0 1) *))
260 | (/ 10 0))
261 ? uncaught exception: (division-by-zero 10)
262
263 `/` expects exactly two arguments, both numbers.
264
265 | (robin (0 1) ((arith (0 1) *))
266 | (/ 14))
267 ? uncaught exception: (illegal-arguments (14))
268
269 | (robin (0 1) ((arith (0 1) *))
270 | (/ 14 23 57))
271 ? uncaught exception: (illegal-arguments (14 23 57))
272
273 | (robin (0 1) ((arith (0 1) *))
274 | (/ 14 #t))
275 ? uncaught exception: (expected-number #t)
276
277 | (robin (0 1) ((arith (0 1) *))
278 | (/ #t 51))
279 ? uncaught exception: (expected-number #t)
280
281 ### `abs` ###
282
283 `abs` evaluates its single argument to a number, and evaluates to
284 the absolute value of that number (where the sign is always positive.)
285
286 | (robin (0 1) ((arith (0 1) *))
287 | (abs 5))
288 = 5
289
290 | (robin (0 1) ((arith (0 1) *))
291 | (abs (- 0 5)))
292 = 5
293
294 | (robin (0 1) ((arith (0 1) *))
295 | (abs 0))
296 = 0
297
298 `abs` expects exactly one numeric argument.
299
300 | (robin (0 1) ((arith (0 1) *))
301 | (abs))
302 ? uncaught exception: (illegal-arguments ())
303
304 | (robin (0 1) ((arith (0 1) *))
305 | (abs 14 23))
306 ? uncaught exception: (illegal-arguments (14 23))
307
308 | (robin (0 1) ((arith (0 1) *))
309 | (abs #t))
310 ? uncaught exception: (expected-number #t)
311
312 ### `frac` ###
313
314 `frac` evaluates its single argument to a number, and evaluates to
315 the fractional portion of that number (i.e., that number, minus the
316 integer portion of that number.)
317
318 | (robin (0 1) ((arith (0 1) *))
319 | (frac 6/5))
320 = 1/5
321
322 | (robin (0 1) ((arith (0 1) *))
323 | (frac 8))
324 = 0
325
326 The result of `frac` is always positive.
327
328 | (robin (0 1) ((arith (0 1) *))
329 | (frac (- 0 6/5)))
330 = 1/5
331
332 `frac` expects exactly one numeric argument.
333
334 | (robin (0 1) ((arith (0 1) *))
335 | (frac))
336 ? uncaught exception: (illegal-arguments ())
337
338 | (robin (0 1) ((arith (0 1) *))
339 | (frac 14 23))
340 ? uncaught exception: (illegal-arguments (14 23))
341
342 | (robin (0 1) ((arith (0 1) *))
343 | (frac #t))
344 ? uncaught exception: (expected-number #t)
345
346 ### `integer?` ###
347
348 `integer?` evaluates its argument, then evaluates to `#t` if that
349 argument is a number without any fractional part, and to `#f` otherwise.
350
351 | (robin (0 1) ((arith (0 1) *))
352 | (integer? 6/5))
353 = #f
354
355 | (robin (0 1) ((arith (0 1) *))
356 | (integer? 8))
357 = #t
358
359 | (robin (0 1) ((arith (0 1) *))
360 | (integer? 0))
361 = #t
362
363 | (robin (0 1) ((arith (0 1) *))
364 | (integer? (- 0 8)))
365 = #t
366
367 The argument to `integer?` must be of numeric type. TODO: this may
368 be relaxed in the future.
369
370 | (robin (0 1) ((arith (0 1) *))
371 | (integer? #t))
372 ? uncaught exception: (expected-number #t)
373
374 `integer?` expects exactly one argument.
375
376 | (robin (0 1) ((arith (0 1)))
377 | (arith:integer?))
378 ? uncaught exception: (illegal-arguments ())
379
380 | (robin (0 1) ((arith (0 1)))
381 | (arith:integer? 14 23))
382 ? uncaught exception: (illegal-arguments (14 23))
383
384 ### `natural?` ###
385
386 `natural?` evaluates its argument, then evaluates to `#t` if that argument
387 is a natural number (a non-negative integer) and to `#f` otherwise.
388
389 | (robin (0 1) ((arith (0 1) *))
390 | (natural? 6/5))
391 = #f
392
393 | (robin (0 1) ((arith (0 1) *))
394 | (natural? 8))
395 = #t
396
397 | (robin (0 1) ((arith (0 1) *))
398 | (natural? 0))
399 = #t
400
401 | (robin (0 1) ((arith (0 1) *))
402 | (natural? (- 0 8)))
403 = #f
404
405 The argument to `natural?` must be of numeric type. TODO: this may
406 be relaxed in the future.
407
408 | (robin (0 1) ((arith (0 1) *))
409 | (natural? #t))
410 ? uncaught exception: (expected-number #t)
411
412 `natural?` expects exactly one argument.
413
414 | (robin (0 1) ((arith (0 1)))
415 | (arith:natural?))
416 ? uncaught exception: (illegal-arguments ())
417
418 | (robin (0 1) ((arith (0 1)))
419 | (arith:natural? 14 23))
420 ? uncaught exception: (illegal-arguments (14 23))
421
422 ### `div` ###
423
424 `div` evaluates both of its arguments to numbers and evaluates to the
425 result of integer division of the first number by the second. Integer
426 division computes by what integer the second number can be multiplied
427 to make it as big as possible without exceeding the first number.
428
429 | (robin (0 1) ((arith (0 1) *))
430 | (div 100 3))
431 = 33
432
433 | (robin (0 1) ((arith (0 1) *))
434 | (div (- 0 100) 3))
435 = -34
436
437 | (robin (0 1) ((arith (0 1) *))
438 | (div 100 (- 0 3)))
439 = -34
440
441 | (robin (0 1) ((arith (0 1) *))
442 | (div 1001/10 3))
443 = 33
444
445 | (robin (0 1) ((arith (0 1) *))
446 | (div 100 10/3))
447 = 33
448
449 | (robin (0 1) ((arith (0 1) *))
450 | (div 10 0))
451 ? uncaught exception: (division-by-zero 10)
452
453 Division by zero is undefined, and an exception will be raised.
454
455 | (robin (0 1) ((arith (0 1)))
456 | (arith:div 10 0))
457 ? uncaught exception: (division-by-zero 10)
458
459 `div` expects exactly two arguments, both numbers.
460
461 | (robin (0 1) ((arith (0 1) *))
462 | (div 14))
463 ? uncaught exception: (illegal-arguments (14))
464
465 | (robin (0 1) ((arith (0 1) *))
466 | (div 14 23 57))
467 ? uncaught exception: (illegal-arguments (14 23 57))
468
469 | (robin (0 1) ((arith (0 1) *))
470 | (div 14 #t))
471 ? uncaught exception: (expected-number #t)
472
473 | (robin (0 1) ((arith (0 1) *))
474 | (div #t 51))
475 ? uncaught exception: (expected-number #t)
476
477 ### `rem` ###
478
479 `rem` evaluates both of its arguments to numbers and evaluates to the
480 remainder of the division of the first number by the second.
481
482 | (robin (0 1) ((arith (0 1) *))
483 | (rem 12 3))
484 = 0
485
486 | (robin (0 1) ((arith (0 1) *))
487 | (rem 11 3))
488 = 2
489
490 | (robin (0 1) ((arith (0 1) *))
491 | (rem 10 3))
492 = 1
493
494 | (robin (0 1) ((arith (0 1) *))
495 | (rem 9 3))
496 = 0
497
498 | (robin (0 1) ((arith (0 1) *))
499 | (rem (- 0 10) 3))
500 = 2
501
502 | (robin (0 1) ((arith (0 1) *))
503 | (rem 10 (- 0 3)))
504 = -2
505
506 Trying to find the remainder of a division by zero is undefined, and an
507 exception will be raised.
508
509 | (robin (0 1) ((arith (0 1) *))
510 | (rem 10 0))
511 ? uncaught exception: (division-by-zero 10)
512
513 When the arguments are not whole numbers, the remainder is still
514 a whole number. TODO: the semantics here need to be cleaned up.
515
516 | (robin (0 1) ((arith (0 1) *))
517 | (rem 10 10/3))
518 = 0
519
520 | (robin (0 1) ((arith (0 1) *))
521 | (rem 10/3 3))
522 = 1/3
523
524 `rem` expects exactly two arguments, both numbers.
525
526 | (robin (0 1) ((arith (0 1) *))
527 | (rem 14))
528 ? uncaught exception: (illegal-arguments (14))
529
530 | (robin (0 1) ((arith (0 1) *))
531 | (rem 14 23 57))
532 ? uncaught exception: (illegal-arguments (14 23 57))
533
534 | (robin (0 1) ((arith (0 1) *))
535 | (rem 14 #t))
536 ? uncaught exception: (expected-number #t)
537
538 | (robin (0 1) ((arith (0 1) *))
539 | (rem #t 51))
540 ? uncaught exception: (expected-number #t)
541
542 ### `>` ###
543
544 `>` evaluates both of its arguments to numbers, then evaluates to `#t`
545 if the first number is strictly greater than the second.
546
547 | (robin (0 1) ((arith (0 1) *))
548 | (> 6 4))
549 = #t
550
551 | (robin (0 1) ((arith (0 1) *))
552 | (> 6 8))
553 = #f
554
555 | (robin (0 1) ((arith (0 1) *))
556 | (> 6 6))
557 = #f
558
559 `>` expects exactly two arguments, both numbers.
560
561 | (robin (0 1) ((arith (0 1) *))
562 | (> 14))
563 ? uncaught exception: (illegal-arguments (14))
564
565 | (robin (0 1) ((arith (0 1) *))
566 | (> 14 23 57))
567 ? uncaught exception: (illegal-arguments (14 23 57))
568
569 | (robin (0 1) ((arith (0 1) *))
570 | (> 14 #t))
571 ? uncaught exception: (expected-number #t)
572
573 | (robin (0 1) ((arith (0 1) *))
574 | (> #t 51))
575 ? uncaught exception: (expected-number #t)
576
577 ### `<` ###
578
579 `<` evaluates both of its arguments to numbers, then evaluates to `#t`
580 if the first number is strictly less than the second.
581
582 | (robin (0 1) ((arith (0 1) *))
583 | (< 6 4))
584 = #f
585
586 | (robin (0 1) ((arith (0 1) *))
587 | (< 6 8))
588 = #t
589
590 | (robin (0 1) ((arith (0 1) *))
591 | (< 6 6))
592 = #f
593
594 `<` expects exactly two arguments, both numbers.
595
596 | (robin (0 1) ((arith (0 1) *))
597 | (< 14))
598 ? uncaught exception: (illegal-arguments (14))
599
600 | (robin (0 1) ((arith (0 1) *))
601 | (< 14 23 57))
602 ? uncaught exception: (illegal-arguments (14 23 57))
603
604 | (robin (0 1) ((arith (0 1) *))
605 | (< 14 #t))
606 ? uncaught exception: (expected-number #t)
607
608 | (robin (0 1) ((arith (0 1) *))
609 | (< #t 51))
610 ? uncaught exception: (expected-number #t)
611
612 ### `>=` ###
613
614 `>=` evaluates both of its arguments to numbers, then evaluates to `#t`
615 if the first number is greater than or equal to the second.
616
617 | (robin (0 1) ((arith (0 1) *))
618 | (>= 6 4))
619 = #t
620
621 | (robin (0 1) ((arith (0 1) *))
622 | (>= 6 8))
623 = #f
624
625 | (robin (0 1) ((arith (0 1) *))
626 | (>= 6 6))
627 = #t
628
629 `>=` expects exactly two arguments, both numbers.
630
631 | (robin (0 1) ((arith (0 1) *))
632 | (>= 14))
633 ? uncaught exception: (illegal-arguments (14))
634
635 | (robin (0 1) ((arith (0 1) *))
636 | (>= 14 23 57))
637 ? uncaught exception: (illegal-arguments (14 23 57))
638
639 | (robin (0 1) ((arith (0 1) *))
640 | (>= 14 #t))
641 ? uncaught exception: (expected-number #t)
642
643 | (robin (0 1) ((arith (0 1) *))
644 | (>= #t 51))
645 ? uncaught exception: (expected-number #t)
646
647 ### `<=` ###
648
649 `<=` evaluates both of its arguments to numbers, then evaluates to `#t`
650 if the first number is less than or equal to the second.
651
652 | (robin (0 1) ((arith (0 1) *))
653 | (<= 6 4))
654 = #f
655
656 | (robin (0 1) ((arith (0 1) *))
657 | (<= 6 8))
658 = #t
659
660 | (robin (0 1) ((arith (0 1) *))
661 | (<= 6 6))
662 = #t
663
664 `<=` expects exactly two arguments, both numbers.
665
666 | (robin (0 1) ((arith (0 1) *))
667 | (<= 14))
668 ? uncaught exception: (illegal-arguments (14))
669
670 | (robin (0 1) ((arith (0 1) *))
671 | (<= 14 23 57))
672 ? uncaught exception: (illegal-arguments (14 23 57))
673
674 | (robin (0 1) ((arith (0 1) *))
675 | (<= 14 #t))
676 ? uncaught exception: (expected-number #t)
677
678 | (robin (0 1) ((arith (0 1) *))
679 | (<= #t 51))
680 ? uncaught exception: (expected-number #t)
681
682 ### `ascending?` ###
683
684 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
685 | (ascending? (list 1 2 3)))
686 = #t
687
688 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
689 | (ascending? (list 1 2 2 3)))
690 = #t
691
692 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
693 | (ascending? (list 3 2 1)))
694 = #f
695
696 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
697 | (ascending? (list 1 2 1 3)))
698 = #f
699
700 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
701 | (ascending? ()))
702 = #t
703
704 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
705 | (ascending? (list 100)))
706 = #t
707
708 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
709 | (ascending? 44))
710 ? uncaught exception: (expected-list 44)
711
712 ### `strictly-ascending?` ###
713
714 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
715 | (strictly-ascending? (list 1 2 3)))
716 = #t
717
718 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
719 | (strictly-ascending? (list 1 2 2 3)))
720 = #f
721
722 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
723 | (strictly-ascending? (list 1 2 1 3)))
724 = #f
725
726 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
727 | (strictly-ascending? ()))
728 = #t
729
730 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
731 | (strictly-ascending? (list 100)))
732 = #t
733
734 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
735 | (strictly-ascending? 44))
736 ? uncaught exception: (expected-list 44)
737
738 ### `descending?` ###
739
740 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
741 | (descending? (list 3 2 1)))
742 = #t
743
744 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
745 | (descending? (list 3 3 3 2 2 1)))
746 = #t
747
748 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
749 | (descending? (list 1 2 3)))
750 = #f
751
752 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
753 | (descending? (list 3 2 3 1)))
754 = #f
755
756 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
757 | (descending? ()))
758 = #t
759
760 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
761 | (descending? (list 100)))
762 = #t
763
764 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
765 | (descending? 44))
766 ? uncaught exception: (expected-list 44)
767
768 ### `strictly-descending?` ###
769
770 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
771 | (strictly-descending? (list 3 2 1)))
772 = #t
773
774 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
775 | (strictly-descending? (list 3 2 2 1)))
776 = #f
777
778 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
779 | (strictly-descending? (list 3 2 3 1)))
780 = #f
781
782 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
783 | (strictly-descending? ()))
784 = #t
785
786 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
787 | (strictly-descending? (list 100)))
788 = #t
789
790 | (robin (0 1) ((arith (0 1) *) (small (0 1) *))
791 | (strictly-descending? 44))
792 ? uncaught exception: (expected-list 44)
+0
-72
doc/module/Assert.markdown less more
0 Module `assert`
1 ===============
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 ### `assert` ###
6
7 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
8 | (assert (equal? 5 5) 7))
9 = 7
10
11 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
12 | (assert (equal? 5 6) 7))
13 ? uncaught exception: (assertion-failed (equal? 5 6))
14
15 ### `assert-boolean` ###
16
17 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
18 | (assert-boolean #f 4))
19 = 4
20
21 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
22 | (assert-boolean 4 #f))
23 ? uncaught exception: (expected-boolean 4)
24
25 ### `assert-number` ###
26
27 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
28 | (assert-number 4 #f))
29 = #f
30
31 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
32 | (assert-number #f 4))
33 ? uncaught exception: (expected-number #f)
34
35 ### `assert-symbol` ###
36
37 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
38 | (assert-symbol (literal captain) (literal tennille)))
39 = tennille
40
41 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
42 | (assert-symbol 7 (literal what)))
43 ? uncaught exception: (expected-symbol 7)
44
45 ### `assert-list` ###
46
47 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
48 | (assert-list () #t))
49 = #t
50
51 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
52 | (assert-list (prepend 1 ()) #t))
53 = #t
54
55 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
56 | (assert-list #t (literal zunk)))
57 ? uncaught exception: (expected-list #t)
58
59 ### `assert-macro` ###
60
61 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
62 | (assert-macro literal (literal it-is)))
63 = it-is
64
65 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
66 | (assert-macro (macro (self args env) args) (literal it-is)))
67 = it-is
68
69 | (robin (0 1) ((small (0 1) *) (assert (0 1) *))
70 | (assert-macro 7 (literal what)))
71 ? uncaught exception: (expected-macro 7)
+0
-93
doc/module/Bind-Args.markdown less more
0 Robin - Bind-Args module (provisional)
1 ======================================
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 `bind-args` is a macro for binding the arguments of another value to
6 identifiers, as well as asserting that the correct number of arguments
7 have been given to the macro.
8
9 This macro should really be defined in `small`, and used by the other
10 macros defined in `small` (right now they don't complain if given too
11 many arguments, and complain about an `expected-list` if given too few.)
12
13 ### `bind-args` ###
14
15 `bind-args` takes a literal list of identifiers, and expresion which
16 evaluates to a literal list of expressions whose values are to be bound
17 to those identifiers, an expresion which evaluates to the environment in
18 which those expressions will be evaluated, and an expression to evaluate
19 in the new environment in which the identifiers are bound.
20
21 | (robin (0 1) ((small (0 1) *) (bind-args (0 1) *))
22 | (bind-args (a b) (literal (1 2)) (env)
23 | (list a b)))
24 = (1 2)
25
26 Expressions in the list of values are evaluated.
27
28 | (robin (0 1) ((small (0 1) *) (bind-args (0 1) *))
29 | (bind-args (a b) (literal ((subtract 5 4) (subtract 10 1))) (env)
30 | (list a b)))
31 = (1 9)
32
33 Too many or too few arguments will raise an `illegal-arguments`
34 exception.
35
36 | (robin (0 1) ((small (0 1) *) (bind-args (0 1) *))
37 | (bind-args (a b) (literal (1)) (env)
38 | (list a b)))
39 ? uncaught exception: (illegal-arguments (1))
40
41 | (robin (0 1) ((small (0 1) *) (bind-args (0 1) *))
42 | (bind-args (a b) (literal (1 2 3)) (env)
43 | (list a b)))
44 ? uncaught exception: (illegal-arguments (1 2 3))
45
46 The literal arguments are reported in the exception.
47
48 | (robin (0 1) ((small (0 1) *) (bind-args (0 1) *))
49 | (bind-args (a) (literal ((subtract 5 4) (subtract 1 0))) (env)
50 | a))
51 ? uncaught exception: (illegal-arguments ((subtract 5 4) (subtract 1 0)))
52
53 This is how it might be used in a macro definition. The reason for the
54 seemingly strange requirements of the second and third arguments should
55 become clear here: typically you would just pass the macro's `args` and
56 `env` to those arguments.
57
58 | (robin (0 1) ((small (0 1) *) (bind-args (0 1) *))
59 | (bind add (macro (self args env)
60 | (bind-args (a b) args env
61 | (subtract a (subtract 0 b))))
62 | (add 4 (add 5 6))))
63 = 15
64
65 | (robin (0 1) ((small (0 1) *) (bind-args (0 1) *))
66 | (bind add (macro (self args env)
67 | (bind-args (a b) args env
68 | (subtract a (subtract 0 b))))
69 | (bind r 7
70 | (add r r))))
71 = 14
72
73 | (robin (0 1) ((small (0 1) *) (bind-args (0 1) *))
74 | (bind add (macro (self args env)
75 | (bind-args (a b) args env
76 | (subtract a (subtract 0 b))))
77 | (add (subtract 0 0))))
78 ? uncaught exception: (illegal-arguments ((subtract 0 0)))
79
80 | (robin (0 1) ((small (0 1) *) (bind-args (0 1) *))
81 | (bind add (macro (self args env)
82 | (bind-args (a b) args env
83 | (subtract a (subtract 0 b))))
84 | (add 9 9 9)))
85 ? uncaught exception: (illegal-arguments (9 9 9))
86
87 | (robin (0 1) ((small (0 1) *) (bind-args (0 1) *))
88 | (bind add (macro (self args env)
89 | (bind-args (a b) args env
90 | (subtract a (subtract 0 b))))
91 | (add 1 n)))
92 ? uncaught exception: (unbound-identifier n)
+0
-339
doc/module/Boolean.markdown less more
0 Module `boolean`
1 ================
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 ### `and` ###
6
7 `and` evaluates both of its arguments to booleans, and evaluates to the
8 logical conjunction (boolean "and") of these two values.
9
10 | (robin (0 1) ((boolean (0 1) *))
11 | (and #t #t))
12 = #t
13
14 | (robin (0 1) ((boolean (0 1) *))
15 | (and #t #f))
16 = #f
17
18 | (robin (0 1) ((boolean (0 1) *))
19 | (and #f #t))
20 = #f
21
22 | (robin (0 1) ((boolean (0 1) *))
23 | (and #f #f))
24 = #f
25
26 `and` expects exactly two arguments.
27
28 | (robin (0 1) ((boolean (0 1) *))
29 | (and #f))
30 ? uncaught exception: (illegal-arguments (#f))
31
32 | (robin (0 1) ((boolean (0 1) *))
33 | (and #t #f #f))
34 ? uncaught exception: (illegal-arguments (#t #f #f))
35
36 `and` expects both of its arguments to be booleans.
37
38 | (robin (0 1) ((boolean (0 1)))
39 | (boolean:and 100 #t))
40 ? uncaught exception: (expected-boolean 100)
41
42 | (robin (0 1) ((boolean (0 1)))
43 | (boolean:and #t 99))
44 ? uncaught exception: (expected-boolean 99)
45
46 `and` is short-circuiting in the sense that no arguments after the first
47 `#f` argument will be evaluated. Fully testing this requires side-effects,
48 but it can be demonstrated as follows.
49
50 | (robin (0 1) ((boolean (0 1)))
51 | (boolean:and #f 100))
52 = #f
53
54 ### `and*` ###
55
56 `and*` is like `and`, but can take any number of arguments.
57
58 | (robin (0 1) ((boolean (0 1) *))
59 | (and*))
60 = #t
61
62 | (robin (0 1) ((boolean (0 1) *))
63 | (and* #f))
64 = #f
65
66 | (robin (0 1) ((boolean (0 1) *))
67 | (and* #t #t #t #t #t))
68 = #t
69
70 | (robin (0 1) ((boolean (0 1) *))
71 | (and* #t #t #t #f))
72 = #f
73
74 `and` expects its arguments to be booleans.
75
76 | (robin (0 1) ((boolean (0 1)))
77 | (boolean:and* 100))
78 ? uncaught exception: (expected-boolean 100)
79
80 `and*` is short-circuiting in the sense that no arguments after the first
81 `#f` argument will be evaluated. Fully testing this requires side-effects,
82 but it can be demonstrated as follows.
83
84 | (robin (0 1) ((boolean (0 1)))
85 | (boolean:and* #t #t #f 100))
86 = #f
87
88 ### `conj` ###
89
90 `conj` evaluates its single argument to a list of booleans, then evaluates
91 to the logical conjunction of those booleans.
92
93 | (robin (0 1) ((boolean (0 1) *))
94 | (conj ()))
95 = #t
96
97 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
98 | (conj (list #t #t #t)))
99 = #t
100
101 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
102 | (conj (list #t #t #f)))
103 = #f
104
105 `conj` expects exactly one argument.
106
107 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
108 | (conj))
109 ? uncaught exception: (illegal-arguments ())
110
111 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
112 | (conj (list #t #t) (list #f #f)))
113 ? uncaught exception: (illegal-arguments ((list #t #t) (list #f #f)))
114
115 `conj` expects its single argument to be a list.
116
117 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
118 | (conj 100))
119 ? uncaught exception: (expected-list 100)
120
121 `conj` expects its single argument to be a list of booleans.
122
123 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
124 | (conj (list #t #t 100)))
125 ? uncaught exception: (expected-boolean 100)
126
127 `conj` is short-circuiting in the sense that no elements after the first
128 `#f` in the list will be examined.
129
130 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
131 | (conj (list #f #t 100)))
132 = #f
133
134 ### `or` ###
135
136 `or` evaluates both of its arguments to booleans, and evaluates to the
137 logical disjunction (boolean "or") of these two values.
138
139 | (robin (0 1) ((boolean (0 1) *))
140 | (or #t #t))
141 = #t
142
143 | (robin (0 1) ((boolean (0 1) *))
144 | (or #t #f))
145 = #t
146
147 | (robin (0 1) ((boolean (0 1) *))
148 | (or #f #t))
149 = #t
150
151 | (robin (0 1) ((boolean (0 1) *))
152 | (or #f #f))
153 = #f
154
155 `or` expects exactly two arguments.
156
157 | (robin (0 1) ((boolean (0 1) *))
158 | (or #f))
159 ? uncaught exception: (illegal-arguments (#f))
160
161 | (robin (0 1) ((boolean (0 1) *))
162 | (or #t #f #f))
163 ? uncaught exception: (illegal-arguments (#t #f #f))
164
165 `or` expects both of its arguments to be booleans.
166
167 | (robin (0 1) ((boolean (0 1)))
168 | (boolean:or 100 #f))
169 ? uncaught exception: (expected-boolean 100)
170
171 | (robin (0 1) ((boolean (0 1)))
172 | (boolean:or #f 99))
173 ? uncaught exception: (expected-boolean 99)
174
175 `or` is short-circuiting in the sense that no arguments after the first
176 `#t` argument will be evaluated. Fully testing this requires side-effects,
177 but it can be demonstrated as follows.
178
179 | (robin (0 1) ((boolean (0 1)))
180 | (boolean:or #t 100))
181 = #t
182
183 ### `or*` ###
184
185 `or*` is like `or`, but can take any number of arguments.
186
187 | (robin (0 1) ((boolean (0 1) *))
188 | (or*))
189 = #f
190
191 | (robin (0 1) ((boolean (0 1) *))
192 | (or* #t))
193 = #t
194
195 | (robin (0 1) ((boolean (0 1) *))
196 | (or* #f #f #f #f #f))
197 = #f
198
199 | (robin (0 1) ((boolean (0 1) *))
200 | (or* #f #f #f #t))
201 = #t
202
203 `or*` expects its arguments to be booleans.
204
205 | (robin (0 1) ((boolean (0 1)))
206 | (boolean:or* 100))
207 ? uncaught exception: (expected-boolean 100)
208
209 `or*` is short-circuiting in the sense that no arguments after the first
210 `#t` argument will be evaluated. Fully testing this requires side-effects,
211 but it can be demonstrated as follows.
212
213 | (robin (0 1) ((boolean (0 1)))
214 | (boolean:or* #f #f #f #t 100))
215 = #t
216
217 ### `disj` ###
218
219 `disj` evaluates its single argument to a list of booleans, then evaluates
220 to the logical disjunction of those booleans.
221
222 | (robin (0 1) ((boolean (0 1) *))
223 | (disj ()))
224 = #f
225
226 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
227 | (disj (list #f #f #f)))
228 = #f
229
230 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
231 | (disj (list #f #t #f)))
232 = #t
233
234 `disj` expects exactly one argument.
235
236 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
237 | (disj))
238 ? uncaught exception: (illegal-arguments ())
239
240 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
241 | (disj (list #t #t) (list #f #f)))
242 ? uncaught exception: (illegal-arguments ((list #t #t) (list #f #f)))
243
244 `disj` expects its single argument to be a list.
245
246 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
247 | (disj 100))
248 ? uncaught exception: (expected-list 100)
249
250 `disj` expects its single argument to be a list of booleans.
251
252 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
253 | (disj (list #f #f 100)))
254 ? uncaught exception: (expected-boolean 100)
255
256 `disj` is short-circuiting in the sense that no elements after the first
257 `#t` in the list will be examined.
258
259 | (robin (0 1) ((boolean (0 1) *) (small (0 1) *))
260 | (disj (list #f #t 100)))
261 = #t
262
263 ### `not` ###
264
265 `not` evaluates its single argument to a boolean, then evaluates to
266 the logical negation of that boolean.
267
268 | (robin (0 1) ((boolean (0 1) *))
269 | (not #t))
270 = #f
271
272 | (robin (0 1) ((boolean (0 1) *))
273 | (not #f))
274 = #t
275
276 `not` expects exactly one argument.
277
278 | (robin (0 1) ((boolean (0 1) *))
279 | (not))
280 ? uncaught exception: (illegal-arguments ())
281
282 | (robin (0 1) ((boolean (0 1) *))
283 | (not #t #f))
284 ? uncaught exception: (illegal-arguments (#t #f))
285
286 `not` expects its single argument to be a boolean.
287
288 | (robin (0 1) ((boolean (0 1)))
289 | (boolean:not 33))
290 ? uncaught exception: (expected-boolean 33)
291
292 ### `xor` ###
293
294 `xor` evaluates both of its arguments to boolean, then evaluates to
295 the "exclusive-or" of those booleans.
296
297 | (robin (0 1) ((boolean (0 1) *))
298 | (xor #t #t))
299 = #f
300
301 | (robin (0 1) ((boolean (0 1) *))
302 | (xor #t #f))
303 = #t
304
305 | (robin (0 1) ((boolean (0 1) *))
306 | (xor #f #t))
307 = #t
308
309 | (robin (0 1) ((boolean (0 1) *))
310 | (xor #f #f))
311 = #f
312
313 `xor` expects exactly two arguments.
314
315 | (robin (0 1) ((boolean (0 1) *))
316 | (xor #f))
317 ? uncaught exception: (illegal-arguments (#f))
318
319 | (robin (0 1) ((boolean (0 1) *))
320 | (xor #t #f #f))
321 ? uncaught exception: (illegal-arguments (#t #f #f))
322
323 `xor` expects both of its arguments to be booleans.
324
325 | (robin (0 1) ((boolean (0 1)))
326 | (boolean:xor 100 #t))
327 ? uncaught exception: (expected-boolean 100)
328
329 | (robin (0 1) ((boolean (0 1)))
330 | (boolean:xor #t 99))
331 ? uncaught exception: (expected-boolean 99)
332
333 This test demonstrates that these functions really do evaluate their
334 arguments.
335
336 | (robin (0 1) ((boolean (0 1) *))
337 | (and (or (xor (and #t (not (not #t))) #f) #f) #t))
338 = #t
+0
-415
doc/module/Concurrency.markdown less more
0 Robin - Concurrency Module
1 ==========================
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 The `concurrency` module exports macros for working with concurrently-
6 executing processes which communicate with each other via message-
7 passing.
8
9 Functionality in this module is difficult to test in isolation, so
10 many of the tests make use of more than one macro from this module.
11
12 Data Types
13 ----------
14
15 ### Process Identifiers ###
16
17 A process identifier is an opaque value which identifies a process.
18
19 Also known as "pids".
20
21 Pids cannot be denoted directly in the textual S-expression format.
22 Several macros in `concurrency` evaluate to a pid, however.
23
24 Functions
25 ---------
26
27 Robin's `concurrency` module exports things for managing concurrently-
28 executing processes.
29
30 ### `myself` ###
31
32 `myself` takes no arguments and evaluates to the pid of the currently
33 running process.
34
35 `myself` expects exactly zero arguments.
36
37 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
38 | (myself 123))
39 ? uncaught exception: (illegal-arguments (123))
40
41 ### `pid?` ###
42
43 `pid?` evaluates its argument, then evaluates to `#t` if that value
44 is a process identifier, `#f` otherwise.
45
46 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
47 | (pid? (literal b)))
48 = #f
49
50 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
51 | (pid? (myself)))
52 = #t
53
54 The argument to `pid?` may naturally be of any type, but there
55 must be exactly one argument.
56
57 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
58 | (pid?))
59 ? uncaught exception: (illegal-arguments ())
60
61 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
62 | (pid? 200 500))
63 ? uncaught exception: (illegal-arguments (200 500))
64
65 ### `spawn!` ###
66
67 `spawn!` starts a concurrent process and evaluates its second argument in
68 that new process. It binds the the process identifier (pid) of the new
69 process to its first argument, which should be an identifier. It then
70 proceeds to evaluate its third argument, in the current process, with
71 that new binding.
72
73 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
74 | (spawn! worker (literal ok)
75 | (pid? worker)))
76 = #t
77
78 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
79 | (spawn! worker (literal ok)
80 | (equal? (myself) worker)))
81 = #f
82
83 `spawn!` takes exactly three arguments.
84
85 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
86 | (spawn!))
87 ? uncaught exception: (illegal-arguments ())
88
89 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
90 | (spawn! cheesecake))
91 ? uncaught exception: (illegal-arguments (cheesecake))
92
93 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
94 | (spawn! (fun (x) 0) (fun (x) 1)))
95 ? uncaught exception: (illegal-arguments ((fun (x) 0) (fun (x) 1)))
96
97 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
98 | (spawn! (fun (x) 0) (fun (x) 1)
99 | (fun (x) 2) (fun (x) 3)))
100 ? uncaught exception: (illegal-arguments ((fun (x) 0) (fun (x) 1) (fun (x) 2) (fun (x) 3)))
101
102 The first argument to `spawn!` must be a symbol.
103
104 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
105 | (spawn! #f (literal ok) 123))
106 ? uncaught exception: (illegal-arguments (#f (literal ok) 123))
107
108 ### `send!` ###
109
110 `send!` evaluates its first argument to obtain a pid, then its second
111 argument to obtain a value. It then sends that value as a message to
112 the process identified by the pid, then evaluates its third argument
113 and itself evaluates to that.
114
115 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
116 | (spawn! worker (literal ok)
117 | (send! worker (literal spam) (literal ok))))
118 = ok
119
120 `send!` expects its first argument to be a pid.
121
122 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
123 | (send! (literal eggs) (literal spam) (literal ok)))
124 ? uncaught exception: (expected-pid eggs)
125
126 `send!` expects exactly three arguments.
127
128 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
129 | (spawn! worker (literal ok)
130 | (send! worker worker)))
131 ? uncaught exception: (illegal-arguments (worker worker))
132
133 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
134 | (spawn! worker (literal ok)
135 | (send! worker worker worker worker)))
136 ? uncaught exception: (illegal-arguments (worker worker worker worker))
137
138 ### `recv!` ###
139
140 `recv!` waits for a message to arrive in the currently executing
141 process's queue, and removes it. It binds the identifier given in
142 its first argument to the value so received, and evaluates its second
143 argument, and itself evaluates to that.
144
145 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
146 | (bind parent (myself)
147 | (spawn! worker (send! parent (literal lettuce) (literal ok))
148 | (recv! message (list message message)))))
149 = (lettuce lettuce)
150
151 `recv!` expects its first argument to be an identifier to be bound. (This
152 is a case of illegal arguments, as the identifier is not an expression
153 that must evaluate to a certain type.)
154
155 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
156 | (bind parent (myself)
157 | (spawn! worker (send! parent (literal lettuce) (literal ok))
158 | (recv! (list 7) 9))))
159 ? uncaught exception: (illegal-arguments ((list 7) 9))
160
161 `recv!` expects exactly two arguments.
162
163 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
164 | (bind parent (myself)
165 | (spawn! worker (send! parent (literal lettuce) (literal ok))
166 | (recv! message))))
167 ? uncaught exception: (illegal-arguments (message))
168
169 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
170 | (bind parent (myself)
171 | (spawn! worker (send! parent (literal lettuce) (literal ok))
172 | (recv! message message message))))
173 ? uncaught exception: (illegal-arguments (message message message))
174
175 Tests for both `send!` and `recv!` follow.
176
177 A process we spawned can send our message back to us.
178
179 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
180 | (bind parent (myself)
181 | (spawn! worker (recv! message (send! parent message 123))
182 | (send! worker (literal whoopie)
183 | (recv! message message)))))
184 = whoopie
185
186 A process we spawned can receive multiple messages.
187
188 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
189 | (bind parent (myself)
190 | (spawn! worker
191 | (recv! message1
192 | (recv! message2
193 | (send! parent (list message1 message2) 0)))
194 | (send! worker (literal thats)
195 | (send! worker (literal entertainment)
196 | (recv! message message))))))
197 = (thats entertainment)
198
199 A process we spawned will terminate while waiting for a message, if the
200 main process terminates.
201
202 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
203 | (bind parent (myself)
204 | (spawn! worker
205 | (recv! message1
206 | (recv! message2
207 | (send! parent (list message1 message2) 0)))
208 | (send! worker (literal thats)
209 | (literal stop)))))
210 = stop
211
212 A spawned process can spawn processes of its own.
213
214 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
215 | (bind parent (myself)
216 | (spawn! worker
217 | (bind subparent (myself)
218 | (spawn! subworker (send! subparent (myself) 123)
219 | (recv! message (send! parent message 123))))
220 | (recv! subworker
221 | (list (pid? subworker) (equal? worker subworker))))))
222 = (#t #f)
223
224 A process can send messages to any process it knows about, not just
225 its parent.
226
227 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
228 | (bind parent (myself)
229 | (spawn! worker
230 | (spawn! subworker
231 | (send! parent (literal hello) 123) 12345)
232 | (recv! message message))))
233 = hello
234
235 If an exception is raised, but not caught, in a process, that process
236 sends a message to this effect to the process that spawned it,
237 immediately before terminating.
238
239 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
240 | (bind parent (myself)
241 | (spawn! worker
242 | (bind x (head ())
243 | (send! parent (literal hi) 0))
244 | (recv! message message))))
245 = (uncaught-exception (expected-list ()))
246
247 ### `msgs?` ###
248
249 `msgs?` evaluates to `#t` if the current process has one or more messages
250 waiting in its queue, `#f` otherwise.
251
252 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
253 | (msgs?))
254 = #f
255
256 Note: it's hard to write this test without a race condition...
257
258 X | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
259 X | (bind parent (myself)
260 X | (spawn! (send! parent (literal lettuce) (literal ok)) worker
261 X | (msgs?))))
262 X = #t
263
264 `msgs?` expects exactly zero arguments.
265
266 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
267 | (msgs? #t))
268 ? uncaught exception: (illegal-arguments (#t))
269
270 ### `call!` ###
271
272 `call!` combines `send!` and `recv!` to accomplish synchronous communication
273 with another process.
274
275 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
276 | (spawn! worker
277 | (recv! message
278 | (let ((sender (head message))
279 | (tag (head (tail message)))
280 | (payload (head (tail (tail message)))))
281 | (send! sender (list (myself)
282 | (list tag (literal reply))
283 | (list tag payload)) 0)))
284 | (call! worker this-tag (literal this-payload) reply
285 | (list (literal reply-was) reply))))
286 = (reply-was (this-tag this-payload))
287
288 The pid and tag in the return message must match, or `call!` will
289 not finish. Note: this is an awful test, because an implementation
290 may in fact hang instead of doing what our implementation does.
291
292 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
293 | (bind parent (myself) (spawn! worker
294 | (recv! message
295 | (let ((sender (head message))
296 | (tag (head (tail message)))
297 | (payload (head (tail (tail message)))))
298 | (send! sender (list parent
299 | (list tag (literal reply))
300 | (list tag payload ())) 0)))
301 | (call! worker this-tag (literal this-payload) reply
302 | (list (literal reply-was) reply)))))
303 ? thread blocked indefinitely in an MVar operation
304
305 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
306 | (bind parent (myself) (spawn! worker
307 | (recv! message
308 | (let ((sender (head message))
309 | (tag (head (tail message)))
310 | (payload (head (tail (tail message)))))
311 | (send! sender (list (myself)
312 | (list (literal some-other-tag) (literal reply))
313 | (list tag payload ())) 0)))
314 | (call! worker this-tag (literal this-payload) reply
315 | (list (literal reply-was) reply)))))
316 ? thread blocked indefinitely in an MVar operation
317
318 If `call!` receives an exception message, it will `raise` that
319 exception. Note that I'm not sure if we actually want this
320 behavior or what (it's an exception message from any process,
321 currently!) but... we'll see.
322
323 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
324 | (spawn! worker
325 | (recv! message
326 | (let ((sender (head message))
327 | (tag (head (tail message)))
328 | (payload (head (tail (tail message)))))
329 | (head (literal argh))))
330 | (call! worker this-tag (literal this-payload) reply
331 | (list (literal reply-was) reply))))
332 ? uncaught exception: (expected-list argh)
333
334 `call!` expects its first argument to be a pid.
335
336 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
337 | (call! (literal worker) this-tag (literal this-payload) reply
338 | (list (literal reply-was) reply)))
339 ? uncaught exception: (expected-pid worker)
340
341 `call!` expects its second argument to be a symbol.
342
343 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
344 | (call! (myself) #f (literal this-payload) reply
345 | (list (literal reply-was) reply)))
346 ? uncaught exception: (illegal-arguments ((myself) #f (literal this-payload) reply (list (literal reply-was) reply)))
347
348 `call!` expects its fourth argument to be an identifier.
349
350 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
351 | (call! (myself) this-tag (literal this-payload) #f
352 | (list (literal reply-was) reply)))
353 ? uncaught exception: (illegal-arguments ((myself) this-tag (literal this-payload) #f (list (literal reply-was) reply)))
354
355 ### `respond!` ###
356
357 `respond!` is the counterpart to `call!`. It assumes the curren process is
358 waiting to be call!ed by `call!` from another process, and when it receives
359 such a message, it acts like a case statement against the tag. It evaluates
360 the appropriate branch, sends a reply message to the pid that `call!`ed it,
361 and evaluates the tail of the branch.
362
363 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
364 | (spawn! worker
365 | (respond!
366 | (donkey (x) (literal kong) (literal ok))
367 | (monkey (x) (literal island) (literal ok)))
368 | (call! worker donkey () reply reply)))
369 = kong
370
371 The payload of the `call!` is available in the bound variable.
372
373 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
374 | (spawn! worker
375 | (respond!
376 | (donkey (x) (literal kong) (literal ok))
377 | (monkey (x) (list (literal island) x) (literal ok)))
378 | (call! worker monkey (literal shines) reply reply)))
379 = (island shines)
380
381 `respond!` responds to only one message.
382
383 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
384 | (spawn! worker
385 | (respond!
386 | (donkey (x) (literal kong) (literal ok))
387 | (monkey (x) (list (literal island) x) (literal ok)))
388 | (call! worker donkey () reply
389 | (call! worker monkey (literal shines) reply reply))))
390 ? thread blocked indefinitely in an MVar operation
391
392 Typically, to write a server, you would use it in a loop.
393
394 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
395 | (bind work-fun (fun (self)
396 | (respond!
397 | (donkey (x) (literal kong) (self self))
398 | (monkey (x) (list (literal island) x) (self self))
399 | (stop (x) (literal ok) (literal ok))))
400 | (spawn! worker (work-fun work-fun)
401 | (call! worker donkey () reply1
402 | (call! worker monkey (literal shines) reply2
403 | (call! worker stop 123 reply3
404 | (list reply1 reply2 reply3)))))))
405 = (kong (island shines) ok)
406
407 `respond!` evaluates to the appropriate tail.
408
409 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *))
410 | (bind parent (myself) (spawn! worker
411 | (call! parent take 71 reply (literal ok))
412 | (respond!
413 | (take (x) (literal ok) (list 55 x))))))
414 = (55 71)
+0
-698
doc/module/Core.markdown less more
0 Module `core`
1 =============
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 Robin's `core` module exports the set of intrinsic macros on top of which
6 all other Robin macros and programs are built.
7
8 ### `prepend` ###
9
10 `prepend` evaluates both of its arguments, then evaluates to a list cell
11 which contains the first value as its data and the second value as the
12 continuation of the list.
13
14 | (robin (0 1) ((core (0 1) *))
15 | (prepend () ()))
16 = (())
17
18 | (robin (0 1) ((core (0 1) *))
19 | (prepend #t (prepend #f ())))
20 = (#t #f)
21
22 The second argument to `prepend` must be a list.
23
24 | (robin (0 1) ((core (0 1) *))
25 | (prepend #t #f))
26 ? uncaught exception: (expected-list #f)
27
28 The first argument to `prepend` can be any type, but fewer than or more than
29 two arguments will raise an exception.
30
31 | (robin (0 1) ((core (0 1) *))
32 | (prepend #t))
33 ? uncaught exception: (illegal-arguments (#t))
34
35 | (robin (0 1) ((core (0 1) *))
36 | (prepend #f #t #f))
37 ? uncaught exception: (illegal-arguments (#f #t #f))
38
39 `prepend` is basically equivalent to Scheme's `cons`, except for the
40 requirement that the second argument be a list.
41
42 ### `head` ###
43
44 `head` evaluates its argument to a list, and evaluates to the first element
45 of that list.
46
47 | (robin (0 1) ((core (0 1) *))
48 | (head (prepend #t ())))
49 = #t
50
51 `head` expects its argument to be a list.
52
53 | (robin (0 1) ((core (0 1) *))
54 | (head #f))
55 ? uncaught exception: (expected-list #f)
56
57 `head` expects exactly one argument.
58
59 | (robin (0 1) ((core (0 1) *))
60 | (head (prepend #t #f) (prepend #f #t)))
61 ? uncaught exception: (illegal-arguments ((prepend #t #f) (prepend #f #t)))
62
63 | (robin (0 1) ((core (0 1) *))
64 | (head))
65 ? uncaught exception: (illegal-arguments ())
66
67 `head` is basically equivalent to Scheme's `car`.
68
69 ### `tail` ###
70
71 `tail` evaluates its argument to a list, and evaluates to the tail of that
72 list (the sublist obtained by removing the first element.)
73
74 | (robin (0 1) ((core (0 1) *))
75 | (tail (prepend #t (prepend #f ()))))
76 = (#f)
77
78 `tail` expects its argument to be a list.
79
80 | (robin (0 1) ((core (0 1) *))
81 | (tail #f))
82 ? uncaught exception: (expected-list #f)
83
84 `tail` expects exactly one argument.
85
86 | (robin (0 1) ((core (0 1) *))
87 | (tail (prepend #t #f) (prepend #f #t)))
88 ? uncaught exception: (illegal-arguments ((prepend #t #f) (prepend #f #t)))
89
90 | (robin (0 1) ((core (0 1) *))
91 | (tail))
92 ? uncaught exception: (illegal-arguments ())
93
94 `tail` is basically equivalent to Scheme's `cdr`.
95
96 ### `if` ###
97
98 `if` evaluates its first argument to a boolean value. If that value is
99 `#t`, it evaluates, and evaluates to, its second argument; or if that value
100 is `#f` it evaluates, and evaluates to, its third argument. In all cases,
101 at most two arguments are evaluated.
102
103 | (robin (0 1) ((core (0 1) *))
104 | (if #t 7 9))
105 = 7
106
107 | (robin (0 1) ((core (0 1) *))
108 | (if #f 7 9))
109 = 9
110
111 The second and third arguments can be arbitrary expressions, but `if`
112 expects its first argument to be a boolean.
113
114 | (robin (0 1) ((core (0 1) *))
115 | (if 5 7 9))
116 ? uncaught exception: (expected-boolean 5)
117
118 `if` expects exactly three arguments.
119
120 | (robin (0 1) ((core (0 1) *))
121 | (if #t 7))
122 ? uncaught exception: (illegal-arguments (#t 7))
123
124 | (robin (0 1) ((core (0 1) *))
125 | (if #t 7 8 9))
126 ? uncaught exception: (illegal-arguments (#t 7 8 9))
127
128 The identifiers named in the branch which is not evaluated need not be
129 properly bound to values in the environment.
130
131 | (robin (0 1) ((core (0 1) *))
132 | (if #t 1 (prepend fred ethel)))
133 = 1
134
135 ### `equal?` ###
136
137 `equal?` evaluates both of its arguments to arbitrary S-expressions
138 and compares them for deep equality.
139
140 `equal?` works on symbols.
141
142 | (robin (0 1) ((core (0 1) *))
143 | (equal?
144 | ((macro (s a e) (head a)) this-symbol)
145 | ((macro (s a e) (head a)) this-symbol)))
146 = #t
147
148 | (robin (0 1) ((core (0 1) *))
149 | (equal?
150 | ((macro (s a e) (head a)) this-symbol)
151 | ((macro (s a e) (head a)) that-symbol)))
152 = #f
153
154 `equal?` works on lists.
155
156 | (robin (0 1) ((core (0 1) *))
157 | (equal? (prepend 1 (prepend 2 (prepend 3 ())))
158 | (prepend 1 (prepend 2 (prepend 3 ())))))
159 = #t
160
161 Two values of different types are never equal.
162
163 | (robin (0 1) ((core (0 1) *))
164 | (equal? #t
165 | (prepend ((macro (self args env) (head args)) a) ())))
166 = #f
167
168 | (robin (0 1) ((core (0 1) *))
169 | (equal? #f
170 | ()))
171 = #f
172
173 Arguments to `equal?` can be any type, but fewer than or more than
174 two arguments will raise an exception.
175
176 | (robin (0 1) ((core (0 1) *))
177 | (equal? 7))
178 ? uncaught exception: (illegal-arguments (7))
179
180 | (robin (0 1) ((core (0 1) *))
181 | (equal? 7 8 9))
182 ? uncaught exception: (illegal-arguments (7 8 9))
183
184 ### `list?` ###
185
186 `list?` evaluates its argument, then evaluates to `#t` if it is a list,
187 `#f` otherwise.
188
189 | (robin (0 1) ((core (0 1) *))
190 | (list? ((macro (self args env) (head args)) (a b))))
191 = #t
192
193 | (robin (0 1) ((core (0 1) *))
194 | (list? ((macro (self args env) (head args)) (a b c d e f))))
195 = #t
196
197 | (robin (0 1) ((core (0 1) *))
198 | (list? (prepend 4 (prepend 5 ()))))
199 = #t
200
201 The empty list is a list.
202
203 | (robin (0 1) ((core (0 1) *))
204 | (list? ()))
205 = #t
206
207 Symbols are not lists.
208
209 | (robin (0 1) ((core (0 1) *))
210 | (list? ((macro (self args env) (head args)) b)))
211 = #f
212
213 The argument to `list?` may (naturally) be any type, but there must be
214 exactly one argument.
215
216 | (robin (0 1) ((core (0 1) *))
217 | (list? (prepend 4 ()) (prepend 6 ())))
218 ? uncaught exception: (illegal-arguments ((prepend 4 ()) (prepend 6 ())))
219
220 ### `macro?` ###
221
222 `macro?` evaluates its argument, then evaluates to `#t` if it is a macro
223 (either built-in or user-defined), or `#f` if it is not.
224
225 | (robin (0 1) ((core (0 1) *))
226 | (macro? (macro (self args env) args)))
227 = #t
228
229 | (robin (0 1) ((core (0 1) *))
230 | (macro? macro))
231 = #t
232
233 | (robin (0 1) ((core (0 1) *))
234 | (macro? ((macro (self args env) (head args)) macro)))
235 = #f
236
237 | (robin (0 1) ((core (0 1) *))
238 | (macro? 4/5))
239 = #f
240
241 The argument to `macro?` may (naturally) be any type, but there must be
242 exactly one argument.
243
244 | (robin (0 1) ((core (0 1) *))
245 | (macro? macro macro))
246 ? uncaught exception: (illegal-arguments (macro macro))
247
248 ### `symbol?` ###
249
250 `symbol?` evaluates its argument, then evaluates to `#t` if it is a symbol,
251 `#f` otherwise.
252
253 | (robin (0 1) ((core (0 1) *))
254 | (symbol? ((macro (s a e) (head a)) this-symbol)))
255 = #t
256
257 Lists are not symbols.
258
259 | (robin (0 1) ((core (0 1) *))
260 | (symbol? (prepend 1 ())))
261 = #f
262
263 The argument to `symbol?` may (naturally) be any type, but there must be
264 exactly one argument.
265
266 | (robin (0 1) ((core (0 1) *))
267 | (symbol? 77 88))
268 ? uncaught exception: (illegal-arguments (77 88))
269
270 ### `boolean?` ###
271
272 `boolean?` evaluates its argument, then evaluates to `#t` if it is a
273 boolean value, `#f` otherwise.
274
275 | (robin (0 1) ((core (0 1) *))
276 | (boolean? #t))
277 = #t
278
279 | (robin (0 1) ((core (0 1) *))
280 | (boolean? #f))
281 = #t
282
283 | (robin (0 1) ((core (0 1) *))
284 | (boolean? ()))
285 = #f
286
287 The argument to `symbol?` may (naturally) be any type, but there must be
288 exactly one argument.
289
290 | (robin (0 1) ((core (0 1) *))
291 | (boolean? #t #f))
292 ? uncaught exception: (illegal-arguments (#t #f))
293
294 ### `number?` ###
295
296 `number?` evaluates its argument, then evaluates to `#t` if it is a
297 rational number, `#f` otherwise.
298
299 | (robin (0 1) ((core (0 1) *))
300 | (number? 5/7))
301 = #t
302
303 | (robin (0 1) ((core (0 1) *))
304 | (number? 0))
305 = #t
306
307 | (robin (0 1) ((core (0 1) *))
308 | (number? ()))
309 = #f
310
311 | (robin (0 1) ((core (0 1) *))
312 | (number? #t))
313 = #f
314
315 The argument to `number?` may (naturally) be any type, but there must be
316 exactly one argument.
317
318 | (robin (0 1) ((core (0 1) *))
319 | (number? 6 4))
320 ? uncaught exception: (illegal-arguments (6 4))
321
322 ### `subtract` ###
323
324 `subtract` evaluates its first argument to a rational number, then
325 evaluates its second argument to a rational number, then evaluates
326 to the difference between the first and second numbers.
327
328 | (robin (0 1) ((core (0 1) *))
329 | (subtract 6 4))
330 = 2
331
332 | (robin (0 1) ((core (0 1) *))
333 | (subtract 16/15 1/5))
334 = 13/15
335
336 | (robin (0 1) ((core (0 1) *))
337 | (subtract 1000 8000))
338 = -7000
339
340 Addition may be accomplished by negating the second argument.
341
342 | (robin (0 1) ((core (0 1) *))
343 | (subtract 999 (subtract 0 999)))
344 = 1998
345
346 `subtract` expects both of its arguments to be numbers.
347
348 | (robin (0 1) ((core (0 1) *))
349 | (subtract #f 100))
350 ? uncaught exception: (expected-number #f)
351
352 | (robin (0 1) ((core (0 1) *))
353 | (subtract 100 ()))
354 ? uncaught exception: (expected-number ())
355
356 `subtract` expects exactly two arguments.
357
358 | (robin (0 1) ((core (0 1) *))
359 | (subtract 100 200 300))
360 ? uncaught exception: (illegal-arguments (100 200 300))
361
362 | (robin (0 1) ((core (0 1) *))
363 | (subtract))
364 ? uncaught exception: (illegal-arguments ())
365
366 ### `divide` ###
367
368 `divide` evaluates its first argument to a rational number, then
369 evaluates its second argument to a rational number, then evaluates
370 to the ratio between the first and second numbers.
371
372 | (robin (0 1) ((core (0 1) *))
373 | (divide 99 11))
374 = 9
375
376 | (robin (0 1) ((core (0 1) *))
377 | (divide 6 4))
378 = 3/2
379
380 | (robin (0 1) ((core (0 1) *))
381 | (divide 4 (subtract 0 5)))
382 = -4/5
383
384 If the second argument is zero, an exception will be raised.
385
386 Addition may be accomplished by taking the reciprocal of the second
387 argument.
388
389 | (robin (0 1) ((core (0 1) *))
390 | (divide 123 0))
391 ? uncaught exception: (division-by-zero 123)
392
393 Addition may be accomplished by taking the reciprocal of the second
394 argument.
395
396 | (robin (0 1) ((core (0 1) *))
397 | (divide 7 (divide 1 7)))
398 = 49
399
400 `divide` expects both of its arguments to be numbers.
401
402 | (robin (0 1) ((core (0 1) *))
403 | (divide #f 100))
404 ? uncaught exception: (expected-number #f)
405
406 | (robin (0 1) ((core (0 1) *))
407 | (divide 100 ()))
408 ? uncaught exception: (expected-number ())
409
410 `divide` expects exactly two arguments.
411
412 | (robin (0 1) ((core (0 1) *))
413 | (divide 100 200 300))
414 ? uncaught exception: (illegal-arguments (100 200 300))
415
416 | (robin (0 1) ((core (0 1) *))
417 | (divide))
418 ? uncaught exception: (illegal-arguments ())
419
420 ### `floor` ###
421
422 `floor` evaluates its sole argument to a rational number, then
423 evaluates to the nearest whole number not larger than that rational.
424
425 | (robin (0 1) ((core (0 1) *))
426 | (floor 26/5))
427 = 5
428
429 | (robin (0 1) ((core (0 1) *))
430 | (floor 5))
431 = 5
432
433 | (robin (0 1) ((core (0 1) *))
434 | (floor (subtract 0 1/2)))
435 = -1
436
437 | (robin (0 1) ((core (0 1) *))
438 | (floor 100 200 300))
439 ? uncaught exception: (illegal-arguments (100 200 300))
440
441 | (robin (0 1) ((core (0 1) *))
442 | (floor))
443 ? uncaught exception: (illegal-arguments ())
444
445 ### `sign` ###
446
447 `sign` evaluates its sole argument to a rational number, then
448 evaluates to 0 if that number is 0, 1 if that number is positive, or
449 -1 if that number is negative.
450
451 | (robin (0 1) ((core (0 1) *))
452 | (sign 26/5))
453 = 1
454
455 | (robin (0 1) ((core (0 1) *))
456 | (sign 0))
457 = 0
458
459 | (robin (0 1) ((core (0 1) *))
460 | (sign (subtract 0 200)))
461 = -1
462
463 `sign` expects exactly one argument.
464
465 | (robin (0 1) ((core (0 1) *))
466 | (sign 100 200 300))
467 ? uncaught exception: (illegal-arguments (100 200 300))
468
469 | (robin (0 1) ((core (0 1) *))
470 | (sign))
471 ? uncaught exception: (illegal-arguments ())
472
473 ### `eval` ###
474
475 `eval` evaluates its first argument to obtain an environment, then
476 evaluates its second argument to obtain an S-expression; it then
477 evaluates that S-expression in the given environment.
478
479 TODO: these tests use things from the `small` module; for the
480 sake of purity, that dependency should be removed (but the tests
481 will look awful.)
482
483 | (robin (0 1) ((small (0 1) *))
484 | (eval (env) (literal (prepend (literal a) (prepend (literal b) ())))))
485 = (a b)
486
487 | (robin (0 1) ((small (0 1) *))
488 | (eval () (literal (prepend (literal a) (literal b)))))
489 ? uncaught exception: (unbound-identifier prepend)
490
491 | (robin (0 1) ((small (0 1) *))
492 | (bind bindings (prepend
493 | (prepend (literal same) (prepend equal? ()))
494 | (prepend
495 | (prepend (literal x) (prepend #f ()))
496 | ()))
497 | (eval bindings (literal (same x x)))))
498 = #t
499
500 If two bindings for the same identifier are supplied in the environment
501 alist passed to `eval`, the one closer to the front of the alist takes
502 precedence.
503
504 | (robin (0 1) ((small (0 1) *))
505 | (bind bindings (prepend
506 | (prepend (literal foo) (prepend (literal yes) ()))
507 | (prepend
508 | (prepend (literal foo) (prepend (literal no) ()))
509 | ()))
510 | (eval bindings (literal foo))))
511 = yes
512
513 `eval` will happily use whatever type of value you like as the
514 environment, however, subsequent evaluation will fail when it
515 tries to look up things in that environment.
516
517 | (robin (0 1) ((small (0 1) *))
518 | (eval 103 (literal (prepend (literal a) (literal b)))))
519 ? uncaught exception: (expected-env-alist 103)
520
521 Evaluation expects the contents of the list which makes up the
522 environment to be two-element lists.
523
524 | (robin (0 1) ((small (0 1) *))
525 | (eval (prepend #f ()) (literal (prepend (literal a) (literal b)))))
526 ? uncaught exception: (expected-env-entry #f)
527
528 Evaluation expects the head of each sublist in the list which makes up the
529 environment to be a symbol.
530
531 | (robin (0 1) ((small (0 1) *))
532 | (eval (prepend (prepend 7 (prepend #f ())) ()) (literal (prepend (literal a) (literal b)))))
533 ? uncaught exception: (expected-symbol 7)
534
535 `eval` expects exactly two arguments.
536
537 | (robin (0 1) ((core (0 1) *))
538 | (eval))
539 ? uncaught exception: (illegal-arguments ())
540
541 | (robin (0 1) ((core (0 1) *))
542 | (eval 4 5 6))
543 ? uncaught exception: (illegal-arguments (4 5 6))
544
545 ### `macro` ###
546
547 `macro` takes its first argument to be a list of three formal
548 parameters, and its second argument to be an arbitrary expression,
549 and uses these two arguments to build, and evaluate to, a macro
550 value.
551
552 When this macro value is evaluated, the first formal argument will
553 be bound to the macro itself, the second will be bound to the
554 literal, unevaluated list of arguments passed to the macro, and the
555 third will be bound to an alist representing the environment in
556 effect at the point the macro value is evaluated.
557
558 These formals are conventionally called `self`, `args`, and `env`,
559 but different names can be chosen in the `macro` definition, for
560 instance to avoid shadowing.
561
562 `literal`, in fact, can be defined as a macro, and it is one of the
563 simplest possible macros that can be written:
564
565 | (robin (0 1) ((core (0 1) *))
566 | ((macro (self args env) (head args)) (why hello there)))
567 = (why hello there)
568
569 Macros have "closure" behavior; that is, bindings in force when a
570 macro is defined will still be in force when the macro is applied,
571 even if they are no longer lexically in scope.
572
573 | (robin (0 1) ((small (0 1) *))
574 | ((let
575 | ((a (literal these-are))
576 | (m (macro (self args env) (prepend a args))))
577 | m) my args))
578 = (these-are my args)
579
580 Macros can return macros.
581
582 | (robin (0 1) ((small (0 1) *))
583 | (let
584 | ((mk (macro (self argsa env)
585 | (macro (self argsb env)
586 | (prepend (head argsb) argsa))))
587 | (mk2 (mk vindaloo)))
588 | (mk2 chicken)))
589 = (chicken vindaloo)
590
591 Arguments to macros shadow any other bindings in effect.
592
593 | (robin (0 1) ((small (0 1) *))
594 | (let
595 | ((args (literal a))
596 | (b (macro (self args env) (prepend args args))))
597 | (b 7)))
598 = ((7) 7)
599
600 `self` is there to let you write recursive macros. The following
601 example demonstrates this; it evaluates `(prepend b d)` in an environment
602 where all the identifiers you list after `qqq` have been bound to 0.
603
604 TODO: these tests use things from the `small` module; for the
605 sake of purity, that dependency should be removed (but the tests
606 will look awful.)
607
608 | (robin (0 1) ((small (0 1) *))
609 | (bind qqq
610 | (macro (self args env)
611 | (if (equal? args ())
612 | (eval env (literal (prepend b (prepend d ()))))
613 | (eval (prepend (prepend (head args) (prepend 0 ())) env)
614 | (prepend self (tail args)))))
615 | (bind b 1 (bind d 4 (qqq b c d)))))
616 = (0 0)
617
618 | (robin (0 1) ((small (0 1) *))
619 | (bind qqq
620 | (macro (self args env)
621 | (if (equal? args ())
622 | (eval env (literal (prepend b (prepend d ()))))
623 | (eval (prepend (prepend (head args) (prepend 0 ())) env)
624 | (prepend self (tail args)))))
625 | (bind b 1 (bind d 4 (qqq x y z)))))
626 = (1 4)
627
628 Your recursive `macro` application doesn't have to be tail-recursive.
629
630 | (robin (0 1) ((small (0 1) *))
631 | (bind make-env
632 | (macro (self args env)
633 | (if (equal? args ())
634 | ()
635 | (prepend (prepend (head args)
636 | (prepend (eval env (head args)) ()))
637 | (eval env
638 | (prepend self (tail args))))))
639 | (bind b 1 (bind d 4 (make-env b d macro)))))
640 = ((b 1) (d 4) (macro (builtin macro)))
641
642 `macro` expects exactly two arguments.
643
644 | (robin (0 1) ((core (0 1) *))
645 | ((macro (self args env)) (why hello there)))
646 ? uncaught exception: (illegal-arguments ((self args env)))
647
648 | (robin (0 1) ((core (0 1) *))
649 | ((macro (self args env) prepend prepend) (why hello there)))
650 ? uncaught exception: (illegal-arguments ((self args env) prepend prepend))
651
652 `macro` expects its first argument to be a list of exactly three
653 symbols.
654
655 | (robin (0 1) ((core (0 1) *))
656 | ((macro 100 prepend) (why hello there)))
657 ? uncaught exception: (illegal-arguments (100 prepend))
658
659 | (robin (0 1) ((core (0 1) *))
660 | ((macro (self args) prepend) (why hello there)))
661 ? uncaught exception: (illegal-arguments ((self args) prepend))
662
663 | (robin (0 1) ((core (0 1) *))
664 | ((macro (self args env foo) prepend) (why hello there)))
665 ? uncaught exception: (illegal-arguments ((self args env foo) prepend))
666
667 | (robin (0 1) ((core (0 1) *))
668 | ((macro (self args 99) prepend) (why hello there)))
669 ? uncaught exception: (illegal-arguments ((self args 99) prepend))
670
671 ### `raise` ###
672
673 `raise` evaluates its argument to obtain a value, then raises an
674 exception with that value.
675
676 If the implementation of Robin does not support catching exceptions, or if
677 it does but no exception handlers have been installed in the execution
678 history, the Robin program will terminate with an error, ceasing execution
679 of all Robin processes immediately, returning control to the operating
680 system. For the sake of usability, the error should include a message which
681 refers to the exception that triggered it, but this is not a strict
682 requirement.
683
684 | (robin (0 1) ((core (0 1) *))
685 | (raise 999999))
686 ? uncaught exception: 999999
687
688 `raise`'s single argument may be any kind of value, but `raise` expects
689 exactly one argument.
690
691 | (robin (0 1) ((core (0 1) *))
692 | (raise))
693 ? uncaught exception: (illegal-arguments ())
694
695 | (robin (0 1) ((core (0 1) *))
696 | (raise 2 3 4))
697 ? uncaught exception: (illegal-arguments (2 3 4))
+0
-140
doc/module/CrudeIO.markdown less more
0 Module `crude-io`
1 =================
2
3 The `crude-io` module exports two processes which may be used to achieve
4 a crude form of input and output with the outside world. This module is
5 very much a "throw one away" approach to I/O, is not in the least intended
6 to solve all problems related to I/O, relies heavily on existing operating
7 system concepts and limitations about I/O, and will be superceded by a
8 more refined approach to I/O in some other module at some point.
9
10 ### `crude-output` ###
11
12 The `crude-output` identifier is bound to a process which accepts messages
13 sent to it, and outputs the content of those messages to the operating
14 system's "standard output".
15
16 Each message should be in the `call!` format, which is a list of three items:
17 the pid of the sender, the tag (which should be the symbol `write`), and
18 the payload (which is the value which we intend to output.)
19
20 The payload will be formatted as a textual S-expression, and this text will
21 be written, as a line, to the standard output. After the text has been
22 written, a confirmation message (in the standard `call!` response format)
23 consisting of the symbol `ok` will be sent back to the process that sent
24 the message.
25
26 To ensure that the text is written, the sending process should wait for
27 this confirmation message. The simplest way to do this is to use the
28 `call!` macro. If the program terminates before this confirmation message
29 is received, the text might not be written to the standard output.
30
31 -> Tests for functionality "Interpret Robin Program"
32
33 Sending a message to `crude-output` causes the contents of the message to
34 be written to the standard output, and an `ok` message sent back to the
35 sending process as a confirmation.
36
37 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
38 | (call! crude-output write (literal hello-world) reply reply))
39 = hello-world
40 = ok
41
42 -> Tests for functionality "Interpret Robin Program without output"
43
44 The sending process need not do anything with the response. The
45 implementation need not write the result of the main process to the
46 standard output.
47
48 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
49 | (call! crude-output write (literal hello-world) reply 0))
50 = hello-world
51
52 Multiple messages may be sent to `crude-output`; the content of each
53 message will be formatted as a textual S-expression, and written out on
54 its own line.
55
56 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
57 | (call! crude-output write (literal hello) x
58 | (call! crude-output write (literal (world 1 2 3)) y
59 | 0)))
60 = hello
61 = (world 1 2 3)
62
63 ### `crude-input` ###
64
65 The `crude-input` identifier is bound to a process which accepts
66 subscription messages sent to it. A subscription message is in `call!`
67 format, with the tag `subscribe`; the payload is ignored. The process
68 which sent the subscription message is the process that will be
69 subscribed to receive data from lines read on the program's "standard
70 input".
71
72 After receiving a subscription message, that pid is added to `crude-input`'s
73 list of subscribers. After a line of text has been entered, that line is
74 parsed as a textual S-expression, and the value of that expression is sent
75 to all subscribers.
76
77 `crude-input` will not send any message until an entire line has been
78 entered and parsed correctly.
79
80 -> Tests for shell command "echo 'hello' | bin/robin %(test-file)"
81
82 `crude-input` can be subscribed to, and the subscriber will receive
83 messages when input occurs.
84
85 SKIP
86 !| (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
87 !| (call! crude-input subscribe () x
88 !| (recv! entered
89 !| (list (literal i-got) entered))))
90 != (i-got hello)
91
92 -> Tests for shell command "echo '(1 2 3)' | bin/robin %(test-file)"
93
94 Arbitrary S-expressions may occur on each line; they are parsed.
95
96 SKIP
97 !| (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
98 !| (call! crude-input subscribe () x
99 !| (recv! entered
100 !| (list (literal i-got) entered))))
101 != (i-got (1 2 3))
102
103 -> Tests for shell command "/bin/echo -e '1\n2\n3\n' | bin/robin -n %(test-file)"
104
105 Multiple lines of text may be input, and multiple messages will be sent.
106
107 SKIP
108 !| (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
109 !| (bind input-loop
110 !| (fun (self)
111 !| (recv! entered
112 !| (if (equal? entered (literal eof))
113 !| #f
114 !| (call! crude-output write (list #t entered) foo
115 !| (self self)))))
116 !| (call! crude-input subscribe () x
117 !| (input-loop input-loop))))
118 != (#t 1)
119 != (#t 2)
120 != (#t 3)
121
122 -> Tests for shell command "/bin/echo -e '1\n#r\n3\n' | bin/robin -n %(test-file)"
123
124 If an S-expression on a given line cannot be parsed, no message will be
125 sent.
126
127 SKIP
128 !| (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
129 !| (bind input-loop
130 !| (fun (self)
131 !| (recv! entered
132 !| (if (equal? entered (literal eof))
133 !| #f
134 !| (call! crude-output write (list #t entered) foo
135 !| (self self)))))
136 !| (call! crude-input subscribe () x
137 !| (input-loop input-loop))))
138 != (#t 1)
139 != (#t 3)
+0
-56
doc/module/Device.markdown less more
0 Module `device`
1 ===============
2
3 The `device` module (currently non-existant) exposes functionality for
4 accessing devices on the running system. The devices so acquired may
5 be real or virtual (abstraction layers over real devices). Virtual
6 devices may include services which are not normally thought of as devices;
7 they may have no direct real-world counterpart.
8
9 The `device` module is probably going to be the sanctioned way to access
10 all devices on the running system, from Robin. Existing modules such as
11 `crude-io` and `console` may be deprecated, or at least have their status
12 changed (they may only describe the devices, not provide access to them.)
13
14 -> Tests for functionality "Interpret Robin Program"
15
16 ### `acquire!` ###
17
18 The `acquire!` macro accepts a list of device descriptors, and binds the
19 given identifiers to pids. Each pid identifies the process handling the
20 device that was requested. The devices are acquired atomically; if the
21 system was not able to acquire any of the requested devices, none of the
22 requested devices are acquired, and an exception is raised.
23
24 A device descriptor is an identifier followed by a set (unordered list)
25 of capabilities. Each capability is (for now) a symbol, which refers to
26 a required capability of the device.
27
28 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (device (0 1) *))
29 | (acquire! (console (ascii colour addressable)
30 | foo ())
31 | (list (pid? console) (pid? foo))))
32 = (#t #t)
33
34 Issues to consider: sharing of device access. In both senses: does the
35 device allow shared access, and can we copy this pid to another process
36 and can it talk to it too.
37
38 ### `release!` ###
39
40 The `release!` macro evaluates its one argument to a pid, then signals
41 the device that it will no longer be used by this process. Subsequent
42 messages sent to the device pid from this process will be ignored.
43
44 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (device (0 1) *))
45 | (acquire! (console (ascii colour addressable))
46 | (release! console
47 | 123)))
48 = 123
49
50 ### `register!` ###
51
52 The `register!` macro evaluates its arguments. The first should be a
53 pid of a running process; the second should be a set of capabilities
54 that this process supports. This allows Robin code to create new devices
55 that can be accessed through the system.
+0
-167
doc/module/Environment.markdown less more
0 Module `env`
1 ============
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 The `env` module exports macros for examining and manipulating evaluation
6 environments and, to the extent they are represented as binding alists,
7 binding alists.
8
9 ### `env?` ###
10
11 `env?` evaluates its single argument, and evaluates to `#t` if
12 and only if it is a well-formed binding alist.
13
14 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
15 | (env? (literal ((a 1) (b 2) (c 3)))))
16 = #t
17
18 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
19 | (env? (literal ((a 1) (999 2) (c 3)))))
20 = #f
21
22 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
23 | (env? (literal ((a 1) (b 2) c))))
24 = #f
25
26 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
27 | (env? 7))
28 = #f
29
30 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
31 | (env? (env)))
32 = #t
33
34 ### `unbind` ###
35
36 `unbind` removes the given identifier from the environment and evaluates its
37 second argument in that reduced environment.
38
39 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
40 | (unbind if (if #t (literal x) (literal y))))
41 ? uncaught exception: (unbound-identifier if)
42
43 If the identifier doesn't exist in the environment, no change is made to
44 the environment.
45
46 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
47 | (unbind yog-sothoth (if #t (literal x) (literal y))))
48 = x
49
50 `unbind` removes all trace of binding from the given identifier; if that
51 identifier has several definitions that are shadowed, none of them will be
52 in effect.
53
54 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
55 | (let ((x 7))
56 | (let ((x 8))
57 | (unbind x
58 | x))))
59 ? uncaught exception: (unbound-identifier x)
60
61 ### `sandbox` ###
62
63 `sandbox` takes a list of identifiers as its first argument, and evaluates
64 its second argument in an environment where all bindings *except* those
65 for the listed identifiers have been unbound.
66
67 | (robin (0 1) ((core (0 1) *) (env (0 1) *))
68 | (sandbox (prepend tail)
69 | (tail (prepend 8 (prepend 9 ())))))
70 = (9)
71
72 | (robin (0 1) ((core (0 1) *) (env (0 1) *))
73 | (sandbox (prepend tail)
74 | (head (prepend 8 (prepend 9 ())))))
75 ? uncaught exception: (unbound-identifier head)
76
77 ### `export` ###
78
79 `export` treats its arguments as a list of identifiers, and returns an
80 environment where only those identifiers are bound to values.
81
82 The original idea for `sandbox` was that it could be used in the body of
83 a module to restrict the visible identifiers to those the module wished
84 to export, which could then actually be exported with `env`. However,
85 this still required `env` to be a visible identifier (and thus exported.)
86 `export` simply evaluates to a binding alist which can be returned
87 directly.
88
89 Note: the order of the bindings in the binding alist isn't guaranteed;
90 these tests should be rewritten to search the resulting alist.
91
92 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
93 | (let ((a 1) (b 2))
94 | (export a b)))
95 = ((b 2) (a 1))
96
97 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
98 | (export head tail))
99 = ((head (builtin head)) (tail (builtin tail)))
100
101 ### `unshadow` ###
102
103 `unshadow` is similar to `unbind`, but only removes the latest binding
104 for the given identifier; previously shadowed bindings, if any exist,
105 will be visible instead.
106
107 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
108 | (unshadow yog-sothoth (if #t (literal x) (literal y))))
109 = x
110
111 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
112 | (unshadow if (if #t (literal x) (literal y))))
113 ? uncaught exception: (unbound-identifier if)
114
115 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
116 | (bind if (literal what)
117 | (unshadow if (if #t (literal x) (literal y)))))
118 = x
119
120 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
121 | (bind q 400
122 | (unshadow q q)))
123 ? uncaught exception: (unbound-identifier q)
124
125 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
126 | (bind q 200
127 | (bind q 400
128 | (unshadow q q))))
129 = 200
130
131 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
132 | (bind q 100
133 | (bind q 200
134 | (bind q 400
135 | (unshadow q (unshadow q q))))))
136 = 100
137
138 | (robin (0 1) ((small (0 1) *) (env (0 1) *))
139 | (let ((q 100)
140 | (q 200)
141 | (q 400))
142 | (unshadow q (unshadow q q))))
143 = 100
144
145 `unshadow` is something of a gimmick that shows off Robin's ability
146 to manipulate the evaluation environment. In practice, the bindings
147 can be determined lexically, and a different identifier could always
148 be chosen instead.
149
150 ### Re-exported Functions ###
151
152 Because it would be reasonable to find them here by categorization,
153 this module re-exports the macro `env` from `core`, and `bind` and `let`
154 from `small`.
155
156 | (robin (0 1) ((env (0 1)))
157 | (env:env? (env:env)))
158 = #t
159
160 | (robin (0 1) ((env (0 1)))
161 | (env:bind a 1 a))
162 = 1
163
164 | (robin (0 1) ((env (0 1)))
165 | (env:let ((a 7) (b a)) b))
166 = 7
+0
-77
doc/module/Exception.markdown less more
0 Module `exception`
1 ==================
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 This module exports macros for catching exceptions. In particular, the
6 ability to import this module means your implementation of Robin
7 supports catching exceptions.
8
9 `raise` itself is in the core, because it can be used to abort the program
10 with an error, even in an implementation which does not support catching
11 exceptions. However, because one might reasonably expect to find it in
12 this module, this module re-exports it as well.
13
14 ### `catch` ###
15
16 `catch` installs an exception handler.
17
18 If an exception is raised when evaluating the final argument of
19 `catch`, the exception value is bound to the symbol given as the
20 first argument of `catch`, and the second argument of `catch` is
21 evaluated in that new environment.
22
23 | (robin (0 1) ((small (0 1) *) (exception (0 1) *))
24 | (catch error (list error #f)
25 | (raise (literal (nasty-value 999999)))))
26 = ((nasty-value 999999) #f)
27
28 `catch` can catch exceptions raised by core macros.
29
30 | (robin (0 1) ((small (0 1) *) (exception (0 1) *))
31 | (catch error (list error 5)
32 | (head #f)))
33 = ((expected-list #f) 5)
34
35 The innermost `catch` will catch the exception.
36
37 | (robin (0 1) ((small (0 1) *) (exception (0 1) *))
38 | (catch error (list error 5)
39 | (catch error (list error 9)
40 | (head #f))))
41 = ((expected-list #f) 9)
42
43 An exception raised from within an exception handler is
44 caught by the next innermost exception handler.
45
46 | (robin (0 1) ((small (0 1) *) (exception (0 1) *))
47 | (catch error (list error 5)
48 | (catch error (list error 9)
49 | (catch error (raise (list error error))
50 | (raise 7)))))
51 = ((7 7) 9)
52
53 `catch` expects its first argument to be an identifier.
54
55 | (robin (0 1) ((small (0 1) *) (exception (0 1) *))
56 | (catch #f 23 (head #f)))
57 ? uncaught exception: (illegal-arguments (#f 23 (head #f)))
58
59 `catch` expects exactly three arguments.
60
61 | (robin (0 1) ((small (0 1) *) (exception (0 1) *))
62 | (catch error error))
63 ? uncaught exception: (illegal-arguments (error error))
64
65 | (robin (0 1) ((small (0 1) *) (exception (0 1) *))
66 | (catch error error (head #f) 23))
67 ? uncaught exception: (illegal-arguments (error error (head #f) 23))
68
69 ### Re-exported Functions ###
70
71 Because it would be reasonable to find it here by categorization, this
72 module re-exports the macro `raise` from `core`.
73
74 | (robin (0 1) ((exception (0 1)))
75 | (exception:catch error error (exception:raise 799)))
76 = 799
+0
-527
doc/module/List.markdown less more
0 Module `list`
1 =============
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 The `list` module exports macros and functions for working with data of
6 conventional list type.
7
8 ### `list` ###
9
10 `list` is a macro which evaluates each of its arguments, and evaluates to a
11 (proper) list containing each of the results, in the same order.
12
13 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
14 | (list 1 2 3 4 5))
15 = (1 2 3 4 5)
16
17 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
18 | (list (list 2 3) (list 6 7)))
19 = ((2 3) (6 7))
20
21 `list` need not have any arguments at all; the result is the empty list.
22
23 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
24 | (list))
25 = ()
26
27 ### `empty?` ###
28
29 `empty?` evaluates its single argument, and evaluates to `#t` if that value
30 is the empty list, `#f` otherwise.
31
32 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
33 | (empty? (literal symbol)))
34 = #f
35
36 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
37 | (empty? ()))
38 = #t
39
40 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
41 | (empty? (list 1 2 3)))
42 = #f
43
44 ### `map` ###
45
46 `map` evaluates its first argument to obtain a macro, and its second argument
47 to obtain a list. It then evaluates to a list which is obtained by applying
48 the macro to each element of the given list. The macro is generally assumed
49 to be a one-argument function.
50
51 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
52 | (map (fun (x) (list x)) (literal (three dog night))))
53 = ((three) (dog) (night))
54
55 While it is possible to pass a macro that is not a function, it is not
56 very productive. (Also, it exposes the implementation of `map`, so this
57 is not a very good test.)
58
59 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
60 | (map (macro (self args env) args) (literal (three dog night))))
61 = (((head li)) ((head li)) ((head li)))
62
63 ### `fold` ###
64
65 `fold` evaluates its first argument to obtain a macro, generally assumed to
66 be a two-argument function, its second argument to obtain an initial value,
67 and its third argument to obtain a list. It then applies the function to
68 successive elements of the list. Each time the function is applied, an
69 element from the list is passed as the first argument. The first time the
70 function is applied, the initial value is passed as the second argument;
71 each subsequent time, the result of the previous application is passed as
72 the second argument. `fold` evaluates to the result of the the final
73 application of the function.
74
75 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
76 | (fold (fun (x a) x) () (literal (three dog night))))
77 = night
78
79 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
80 | (fold (fun (x a) a) 541 (literal (archie moffam))))
81 = 541
82
83 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
84 | (fold (fun (x a) (list a x)) () (literal (three dog night))))
85 = (((() three) dog) night)
86
87 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
88 | (fold 1/2 (fun (x a) a) (literal (three dog night))))
89 ? uncaught exception: (inapplicable-object 1/2)
90
91 ### `reverse` ###
92
93 `reverse` evaluates its argument to a list, then evaluates to a list which
94 is the same as the given list in every respect except that the order of
95 the elements is reversed.
96
97 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
98 | (reverse (literal (1 2 3 4 5))))
99 = (5 4 3 2 1)
100
101 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
102 | (reverse (literal fairies-wear-boots)))
103 ? uncaught exception: (expected-list fairies-wear-boots)
104
105 ### `filter` ###
106
107 `filter` evaluates its first argument to obtain a macro, generally assumed
108 to be a predicate (a one-argument function which evaluates to a boolean).
109 It then evaluates its second argument to obtain a list. It then evaluates
110 to a list which contains all the elements of the given list, in the same
111 order, which satisfy the predicate.
112
113 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
114 | (filter (fun (x) (symbol? x)) (literal (1 two #f 3 () four 5 six))))
115 = (two four six)
116
117 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
118 | (filter (fun (x) x) (literal (#t #t #f banana #t #f))))
119 ? uncaught exception: (expected-boolean banana)
120
121 ### `find` ###
122
123 `find` evaluates its first argument to obtain a predicate, then evaluates
124 its second argument to obtain a list. It then evaluates to a list which
125 is either empty, if no element of the list satisfies the predicate, or
126 a list which contains exactly one element, which will be the first
127 element from the list which satisfies the predicate.
128
129 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
130 | (find (fun (x) (symbol? x)) ()))
131 = ()
132
133 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
134 | (find (fun (x) (symbol? x)) (list 1 2 3)))
135 = ()
136
137 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
138 | (find (fun (x) #t) (list 1 2 3)))
139 = (1)
140
141 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
142 | (find (fun (x) (symbol? x)) (literal (1 two #f 3 () four 5 six))))
143 = (two)
144
145 `find` could be defined in terms of `filter`, but in practice it would
146 be implemented in a way which need not examine the entire list.
147
148 ### `elem?` ###
149
150 `elem?` evaluates its first argument to a value of any type, and its
151 second argument to obtain a list. It then evaluates to `#t` if the value
152 is `equal?` to some element of the list, `#f` otherwise.
153
154 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
155 | (elem? (literal p) (literal (a p e))))
156 = #t
157
158 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
159 | (elem? (literal p) (literal (a r k))))
160 = #f
161
162 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
163 | (elem? 7 ()))
164 = #f
165
166 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
167 | (elem? 7 (list 5 (list 6 7) 8)))
168 = #f
169
170 `elem?` can be defined in terms of `find`, in a manner such as:
171
172 (not (empty? (find (fun (x) (equal? x y)) li)))
173
174 ### `append` ###
175
176 `append` evaluates both of its arguments to lists. It then
177 evaluates to a list which is the concatenation of these lists.
178
179 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
180 | (append (list 1 2 3) (list 4 5 6)))
181 = (1 2 3 4 5 6)
182
183 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
184 | (append () ()))
185 = ()
186
187 ### `length` ###
188
189 `length` evaluates its single argument to obtain a proper list, then
190 evaluates to a non-negative integer which is the length of the list
191 (the number of cells, not counting nested cells and not counting the
192 empty list at the very tail.)
193
194 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
195 | (length ()))
196 = 0
197
198 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
199 | (length (list 1 2 #t #f 3)))
200 = 5
201
202 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
203 | (length (literal whatnot)))
204 ? uncaught exception: (expected-list whatnot)
205
206 ### `index` ###
207
208 `index` evaluates its first argument to a natural number, and its
209 second argument to a list. It then evaluates to the element of the
210 list at the index given by the natural number. The index is 0-based;
211 0 refers to the element at the head of the list.
212
213 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
214 | (index 0 (literal (the girl from ipanema))))
215 = the
216
217 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
218 | (index 2 (literal (the girl from ipanema))))
219 = from
220
221 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
222 | (bind last (fun (li) (index (subtract (length li) 1) li))
223 | (last (literal (the girl from ipanema)))))
224 = ipanema
225
226 Attempting to index beyond the end of the list will raise an exception.
227
228 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
229 | (index 7 (literal (the girl from ipanema))))
230 ? uncaught exception: (expected-list ())
231
232 `index` expects its first argument to be a number.
233
234 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
235 | (index (literal goofy) (list 1 2 3 4 5)))
236 ? uncaught exception: (expected-number goofy)
237
238 `index` expects its second argument to be a list.
239
240 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
241 | (index 8 (literal whatnot)))
242 ? uncaught exception: (expected-list whatnot)
243
244 ### `take-while` ###
245
246 `take-while` evaluates its first argument to obtain a predicate and its
247 second argument to obtain a list. It then evaluates to the longest prefix
248 of the list whose elements all satisfy the predicate.
249
250 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
251 | (take-while (fun (x) (symbol? x)) (literal (one two 3 4 five 6 seven))))
252 = (one two)
253
254 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
255 | (take-while (fun (x) (symbol? x)) (literal (1 2 3 4 five six))))
256 = ()
257
258 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
259 | (take-while (fun (x) (number? x)) (literal (1 2 3 4 5 6))))
260 = (1 2 3 4 5 6)
261
262 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
263 | (take-while (fun (x) (symbol? x)) ()))
264 = ()
265
266 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
267 | (take-while (fun (x) (symbol? x)) #f))
268 ? uncaught exception: (expected-list #f)
269
270 ### `drop-while` ###
271
272 `drop-while` evaluates its first argument to obtain a predicate and its
273 second argument to obtain a list. It then evaluates to the suffix of the
274 given list, starting at the first element which does not satisfy the
275 predicate.
276
277 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
278 | (drop-while (fun (x) (symbol? x)) (literal (one two 3 4 five 6 seven))))
279 = (3 4 five 6 seven)
280
281 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
282 | (drop-while (fun (x) (symbol? x)) (literal (1 2 3 4 5 6))))
283 = (1 2 3 4 5 6)
284
285 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
286 | (drop-while (fun (x) (number? x)) (literal (1 2 3 4 5 6))))
287 = ()
288
289 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
290 | (drop-while (fun (x) (symbol? x)) ()))
291 = ()
292
293 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
294 | (drop-while (fun (x) (symbol? x)) #f))
295 ? uncaught exception: (expected-list #f)
296
297 ### `first` ###
298
299 `first` evaluates its first argument to obtain a non-negative integer,
300 considered to be a desired length, and its second argument to obtain a list.
301 It then evaluates to the prefix of the given list of the desired length.
302
303 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
304 | (first 0 (list 1 2 3 4 5)))
305 = ()
306
307 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
308 | (first 3 (list 1 2 3 4 5)))
309 = (1 2 3)
310
311 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
312 | (first 6 (list 1 2 3 4 5)))
313 ? uncaught exception: (expected-list ())
314
315 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
316 | (first 1 (literal foo)))
317 ? uncaught exception: (expected-list foo)
318
319 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
320 | (first 0 (literal foo)))
321 = ()
322
323 ### `rest` ###
324
325 `rest` evaluates its first argument to obtain a non-negative integer,
326 considered to be a desired position, and its second argument to obtain a
327 list. It then evaluates to the suffix of the given list starting at the
328 desired position. The position 0 indicates the beginning of the list.
329
330 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
331 | (rest 0 (list 1 2 3 4 5)))
332 = (1 2 3 4 5)
333
334 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
335 | (rest 3 (list 1 2 3 4 5)))
336 = (4 5)
337
338 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
339 | (rest 5 (list 1 2 3 4 5)))
340 = ()
341
342 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
343 | (rest 6 (list 1 2 3 4 5)))
344 ? uncaught exception: (expected-list ())
345
346 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
347 | (rest 1 (literal foo)))
348 ? uncaught exception: (expected-list foo)
349
350 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
351 | (rest 0 (literal foo)))
352 = foo
353
354 ### `last` ###
355
356 `last` evaluates its first argument to obtain a non-negative integer,
357 considered to be a desired length, and its second argument to obtain a
358 list. It then evaluates to the suffix of the given list of the desired
359 length.
360
361 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
362 | (last 0 (list 1 2 3 4 5)))
363 = ()
364
365 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
366 | (head (last 1 (list 1 2 3 4 5))))
367 = 5
368
369 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
370 | (last 3 (list 1 2 3 4 5)))
371 = (3 4 5)
372
373 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
374 | (last 6 (list 1 2 3 4 5)))
375 ? uncaught exception: (expected-list ())
376
377 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
378 | (last 1 (literal foo)))
379 ? uncaught exception: (expected-list foo)
380
381 Unlike `first`, `last` does care if it's not a list, even when the count
382 is zero.
383
384 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
385 | (last 0 (literal foo)))
386 ? uncaught exception: (expected-list foo)
387
388 ### `prefix?` ###
389
390 `prefix?` evaluates its first and second arguments to obtain lists.
391 It then evaluates to `#t` if the first list is a prefix of the second
392 list, `#f` otherwise. A list A is a prefix of a list B if A is `empty?`,
393 or the head of A is `equal?` to the head of B and the tail of A is a
394 prefix of the tail of B.
395
396 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
397 | (prefix? (list 1 2 3) (list 1 2 3 4 5 6)))
398 = #t
399
400 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
401 | (prefix? (list 1 2 5) (list 1 2 3 4 5 6)))
402 = #f
403
404 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
405 | (prefix? () (list 1 2 3 4 5 6)))
406 = #t
407
408 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
409 | (prefix? () (literal schpritz)))
410 = #t
411
412 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
413 | (prefix? (list 1 2 3) (list 1 2 3)))
414 = #t
415
416 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
417 | (prefix? (list 1 2 3 4) (list 1 2 3)))
418 = #f
419
420 ### `flatten` ###
421
422 `flatten` evaluates its first argument to obtain a list, then evaluates
423 to the list obtained by interpolating all elements into a single list.
424 By interpolating we mean that, if some element is itself a list, the
425 individual elements of that list will be present, in the same order, in
426 the corresponding position, in the resulting list, and that this process
427 is applied recursively to any elements in sublists which are themselves
428 sublists.
429
430 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
431 | (flatten ()))
432 = ()
433
434 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
435 | (flatten (list 1 2 3)))
436 = (1 2 3)
437
438 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
439 | (flatten (list 1 (list 2 3 4) 5)))
440 = (1 2 3 4 5)
441
442 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
443 | (flatten (list 1 (list 2 3 (list 4 4 4)) 5)))
444 = (1 2 3 4 4 4 5)
445
446 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
447 | (flatten (list 1 () 5)))
448 = (1 5)
449
450 ### `lookup` ###
451
452 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
453 | (lookup (literal b) (literal ((a 1) (b 2) (c 3)))))
454 = (2)
455
456 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
457 | (lookup (literal a) (literal ((a 1) (a 2) (a 3)))))
458 = (1)
459
460 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
461 | (lookup (literal r) (literal ((a 1) (b 2) (c 3)))))
462 = ()
463
464 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
465 | (lookup (literal q) ()))
466 = ()
467
468 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
469 | (lookup (literal q) 55))
470 ? uncaught exception: (expected-list 55)
471
472 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
473 | (lookup (literal q) (literal ((a 7) 99 (q 4)))))
474 ? uncaught exception: (expected-list 99)
475
476 ### `extend` ###
477
478 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
479 | (extend (literal b) 6 (literal ((a 1) (b 2) (c 3)))))
480 = ((b 6) (a 1) (b 2) (c 3))
481
482 The following should be true for any identifier i and alist x.
483
484 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
485 | (let ((i (literal a))
486 | (x (literal ((f 5) (g 7)))))
487 | (lookup i (extend i 1 x))))
488 = (1)
489
490 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
491 | (extend (literal b) 6 ()))
492 = ((b 6))
493
494 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
495 | (extend (literal b) 6 81))
496 ? uncaught exception: (expected-list 81)
497
498 ### `delete` ###
499
500 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
501 | (delete (literal b) (literal ((a 1) (b 2) (c 3)))))
502 = ((a 1) (c 3))
503
504 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
505 | (delete (literal b) (literal ((a 1) (b 2) (c 3) (b 4)))))
506 = ((a 1) (c 3))
507
508 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
509 | (delete (literal r) (literal ((a 1) (b 2) (c 3)))))
510 = ((a 1) (b 2) (c 3))
511
512 The following should be true for any identifier i and alist x.
513
514 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
515 | (let ((i (literal a))
516 | (x (literal ((a 5) (b 7)))))
517 | (lookup i (delete i x))))
518 = ()
519
520 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
521 | (delete (literal q) 55))
522 ? uncaught exception: (expected-list 55)
523
524 | (robin (0 1) ((small (0 1) *) (list (0 1) *))
525 | (delete (literal q) (literal ((a 7) 99 (q 4)))))
526 ? uncaught exception: (expected-list 99)
+0
-153
doc/module/Metadata.markdown less more
0 Module `metadata`
1 =================
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 Robin's `metadata` module exports macros for working with metadata. Like
6 `exception`, importing this module both asserts that the Robin implementation
7 supports metadata on values, and exposes the macros used to work with
8 metadata (`with` and `has?`.)
9
10 ### `with` ###
11
12 `with` attaches metadata to a value.
13
14 | (robin (0 1) ((metadata (0 1)))
15 | (metadata:with cromulent #t 5))
16 = 5
17
18 The name of the metadata is generally a symbol; it is not evaluated.
19
20 | (robin (0 1) ((metadata (0 1)))
21 | (metadata:with (vorp dorp) #t 5))
22 = 5
23
24 Passing values with metadata attached shouldn't break any of the core
25 macros.
26
27 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
28 | (head (with spiffy #t (prepend 1 ()))))
29 = 1
30
31 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
32 | (tail (with snazzy #t (prepend 1 ()))))
33 = ()
34
35 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
36 | (prepend (with sassy #t 1) (prepend (with snotty #t 2) ())))
37 = (1 2)
38
39 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
40 | (if (with sassy #t #t) (with snotty #t 2) (with insolent #t 3)))
41 = 2
42
43 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
44 | (if (with weight 777 #f) (with height 888 2) (with width 999 3)))
45 = 3
46
47 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
48 | (equal? (with fussy #t 4) (with picky #t 4)))
49 = #t
50
51 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
52 | (list? (with pokey #t (prepend 2 (prepend 3 ())))))
53 = #t
54
55 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
56 | (number? (with hirsute #t 3)))
57 = #t
58
59 | (robin (0 1) ((small (0 1) *) (metadata (0 1) *))
60 | (symbol? (with forgetful #t (literal x))))
61 = #t
62
63 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
64 | (macro? (with special #t (macro (self args env) args))))
65 = #t
66
67 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
68 | (boolean? (with squirrelly #t #t)))
69 = #t
70
71 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
72 | ((with moosey #t (macro (self args env) args)) foo bar baz))
73 = (foo bar baz)
74
75 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
76 | (subtract (with boris #t 0) (with natasha #f 5)))
77 = -5
78
79 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
80 | (divide (with near #t 1) (with far #f 5)))
81 = 1/5
82
83 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
84 | (sign (with graceful #t 1)))
85 = 1
86
87 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
88 | (floor (with nervous #t 3/2)))
89 = 1
90
91 Testing for equality ignores metadata.
92
93 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
94 | (equal? (with cromulent #t 4) 4))
95 = #t
96
97 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
98 | (equal? 4 (with cromulent #t 4)))
99 = #t
100
101 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
102 | (equal? (with cromulent #t 4) (with goofy #t 4)))
103 = #t
104
105 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
106 | (equal? (with cromulent #t 4) (with cromulent #t 5)))
107 = #f
108
109 Different metadata really shouldn't be put on objects which are `equal?`,
110 but you can do it.
111
112 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
113 | (equal? (with cromulent #t 4) (with cromulent #f 4)))
114 = #t
115
116 ### `has?` ###
117
118 `has?` checks if a value has a given metadata.
119
120 | (robin (0 1) ((metadata (0 1)))
121 | (metadata:has? #t 4))
122 = #f
123
124 | (robin (0 1) ((metadata (0 1)))
125 | (metadata:has? cromulent (metadata:with cromulent #t 4)))
126 = #t
127
128 | (robin (0 1) ((metadata (0 1)))
129 | (metadata:has? cromulent (metadata:with cromulent #f 4)))
130 = #t
131
132 | (robin (0 1) ((core (0 1) *) (metadata (0 1) *))
133 | (has? cromulent (head (prepend (with cromulent #t 4) (prepend 5 ())))))
134 = #t
135
136 Binding retains metadata.
137
138 | (robin (0 1) ((small (0 1) *) (metadata (0 1) *))
139 | (bind q (with gee #t 77)
140 | (has? gee q)))
141 = #t
142
143 Metadata is retained in macros.
144
145 | (robin (0 1) ((small (0 1) *) (metadata (0 1) *))
146 | (bind whee
147 | (macro (self args env)
148 | (prepend (head env)
149 | (prepend (has? gee (head (tail (head env)))) ())))
150 | (bind r (with gee 7 8)
151 | (whee))))
152 = ((r 8) #t)
+0
-45
doc/module/Miscellany.markdown less more
0 Miscellanous Module Tests
1 =========================
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 This document contains miscellaneous tests for module functionality;
6 tests that require multiple modules be loaded, and so forth.
7
8 Modules are cached, so that a module referenced by two other modules
9 is not loaded twice.
10
11 | (robin (0 1) ((core (0 1) *) (random-a (0 1) *) (random-b (0 1) *))
12 | (equal? random-a random-b))
13 = #t
14
15 Circular module imports produce an error rather than going into an infinite
16 loop.
17
18 | (robin (0 1) ((core (0 1) *) (circular-a (0 1) *))
19 | (equal? literal-a literal-b))
20 ? circular reference in module circular-a
21
22 `and*` is short-circuiting.
23
24 | (robin (0 1) ((small (0 1) *) (boolean (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
25 | (let ((true
26 | (fun () (call! crude-output write (literal t) reply #t)))
27 | (false
28 | (fun () (call! crude-output write (literal f) reply #f))))
29 | (and* (true) (false) (false) (true))))
30 = t
31 = f
32 = #f
33
34 `or*` is short-circuiting.
35
36 | (robin (0 1) ((small (0 1) *) (boolean (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
37 | (let ((true
38 | (fun () (call! crude-output write (literal t) reply #t)))
39 | (false
40 | (fun () (call! crude-output write (literal f) reply #f))))
41 | (or* (false) (true) (true) (false))))
42 = f
43 = t
44 = #t
+0
-301
doc/module/Pure.markdown less more
0 Module `pure`
1 =============
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 The `pure` module is an EXPERIMENTAL module for EXPERIMENTING with
6 static analysis, namely to determine if functions cannot possibly have
7 side-effects (are "pure") or not.
8
9 A function is considered pure if, for every set of possible particular
10 actual arguments, it always evaluates to the same particular result value.
11
12 We start by assuming most of the functions and macros in the `core` and
13 `small` modules are pure (a justified assumption), and we analyze
14 functions which are built up of those functions and macros. (We will
15 not try to analyze user-defined macros that aren't functions yet, because
16 that is franklya little more difficult.)
17
18 As described in the Style document, the only "side-effects" in Robin are
19 spawning a process, sending a message to a process, and receiving a message
20 from a process, and these can be distinguished at a lower level than simply
21 "might this have side-effects or not". But for now, for simplicitly, I'm
22 going to glom them all together under this banner.
23
24 ### Re-exports ###
25
26 `pure` re-exports everything in `core`, and a few things from `small`,
27 but marked with `pure` in the metadata (except `eval` where this is far
28 from a guarantee.)
29
30 | (robin (0 1) ((pure (0 1) *))
31 | (has? pure head))
32 = #t
33
34 | (robin (0 1) ((pure (0 1) *))
35 | (has? pure tail))
36 = #t
37
38 | (robin (0 1) ((pure (0 1) *))
39 | (has? pure prepend))
40 = #t
41
42 | (robin (0 1) ((pure (0 1) *))
43 | (has? pure if))
44 = #t
45
46 | (robin (0 1) ((pure (0 1) *))
47 | (has? pure macro))
48 = #t
49
50 | (robin (0 1) ((pure (0 1) *))
51 | (has? pure fun))
52 = #t
53
54 ### Purity Analysis ###
55
56 Purity analysis is implemented with two main predicates. The first,
57 `pure-expr?`, checks if an expression is pure -- that no side-effects
58 occur during its evaluation. The second, `pure-fun-defn?`, checks if an
59 expression evaluates to a function which is pure.
60
61 These two functions call each other in mutual recursion. An expression
62 which evaluates to an impure function can still be pure, when no side-effects
63 occur during the evaluation that results in the function. However, if an
64 expression applies a function that it defines, we need to check whether the
65 function has any side effects, to determine if the expression is pure.
66
67 Typically, user code would not call these predicates directly; instead
68 it would use `pure-fun` to define functions, which would check them for
69 purity before making them available to the rest of the program.
70
71 ### `pure-expr?` ###
72
73 The first argument is an environment. The second argument is a list
74 of symbols which are the formal parameters of the function. The third
75 argument is a literal term which is the body of the function.
76
77 | (robin (0 1) ((pure (0 1) *))
78 | (pure-expr? (env) () (literal 4)))
79 = #t
80
81 | (robin (0 1) ((pure (0 1) *))
82 | (pure-expr? (env) () (literal (subtract 4 5))))
83 = #t
84
85 | (robin (0 1) ((pure (0 1) *))
86 | (pure-expr? (env) (literal (a b)) (literal (subtract a b))))
87 = #t
88
89 | (robin (0 1) ((pure (0 1) *) (concurrency (0 1) *))
90 | (pure-expr? (env) (literal (a b)) (literal (send! (myself) 3))))
91 = #f
92
93 An otherwise pure function which simply binds something that it does not use
94 is still pure.
95
96 | (robin (0 1) ((pure (0 1) *))
97 | (pure-expr? (env) (literal (x)) (literal
98 | (bind y 23 x))))
99 = #t
100
101 An otherwise pure function which binds some pure values to names is still
102 pure.
103
104 Unfortunately, our analyzer isn't smart enough to figure that out yet.
105
106 | (robin (0 1) ((pure (0 1) *))
107 | (pure-expr? (env) (literal (x)) (literal
108 | (bind y (subtract x 23) (bind r 5 (subtract y r))))))
109 = #f
110
111 A function which evaluates to a pure built-in function is pure.
112
113 | (robin (0 1) ((pure (0 1) *))
114 | (pure-expr? (env) (literal (foo)) (literal head)))
115 = #t
116
117 A function which evaluates to a pure function is pure.
118
119 | (robin (0 1) ((pure (0 1) *))
120 | (pure-expr? (env) (literal (foo)) (literal (fun (x) x))))
121 = #t
122
123 A function which evaluates to an impure function is still pure, as long as
124 the impure function is determined entirely by the parameters to the pure
125 function.
126
127 | (robin (0 1) ((pure (0 1) *) (concurrency (0 1) *))
128 | (pure-expr? (env) () (literal
129 | (fun (x) (send! x 3)))))
130 = #t
131
132 Even if it uses a closed-over identifier.
133
134 | (robin (0 1) ((pure (0 1) *) (concurrency (0 1) *))
135 | (pure-expr? (env) (literal (pid)) (literal
136 | (fun (x) (send! pid x)))))
137 = #t
138
139 Even if it evaluates to multiple functions.
140
141 | (robin (0 1) ((pure (0 1) *) (concurrency (0 1) *))
142 | (pure-expr? (env) (literal (pid)) (literal
143 | (prepend (fun () pid)
144 | (prepend (fun (x) (send! pid x)) ())))))
145 = #t
146
147 An otherwise pure function which calls a pure function that it defines
148 within itself is pure.
149
150 Unfortunately, our analyzer isn't smart enough to figure that out yet.
151
152 | (robin (0 1) ((pure (0 1) *))
153 | (pure-expr? (env) (literal (x)) (literal
154 | ((fun (y) y) 123))))
155 = #f
156
157 (Unless of course, one of its actual arguments is not.)
158
159 | (robin (0 1) ((pure (0 1) *))
160 | (pure-expr? (env) (literal (x)) (literal
161 | ((fun (y) y) (send! x 14)))))
162 = #f
163
164 Even if it uses closed-over identifiers.
165
166 Unfortunately, our analyzer isn't smart enough to figure that out yet.
167
168 | (robin (0 1) ((pure (0 1) *))
169 | (pure-expr? (env) (literal (x)) (literal
170 | ((fun (y) x) 123))))
171 = #f
172
173 Even if it was bound to a name first.
174
175 | (robin (0 1) ((pure (0 1) *))
176 | (pure-expr? (env) (literal (x)) (literal
177 | (bind y (fun (z) z)
178 | (y 123)))))
179 = #t
180
181 Even if it was bound to a name first, and uses closed-over identifiers.
182
183 Unfortunately, our analyzer isn't smart enough to figure that out yet.
184
185 | (robin (0 1) ((pure (0 1) *))
186 | (pure-expr? (env) (literal (x)) (literal
187 | (bind y (fun (z) (prepend x z))
188 | (y 123)))))
189 = #f
190
191 An otherwise pure function which calls an impure function that it defines
192 within itself is not pure.
193
194 | (robin (0 1) ((pure (0 1) *) (concurrency (0 1) *))
195 | (pure-expr? (env) (literal (pid)) (literal
196 | ((fun (j) (send! j 3)) pid))))
197 = #f
198
199 Even if that impure function was bound to a name first.
200
201 | (robin (0 1) ((pure (0 1) *) (concurrency (0 1) *))
202 | (pure-expr? (env) (literal (pid)) (literal
203 | (bind zap! (fun (j) (send! j 3))
204 | (zap! pid)))))
205 = #f
206
207 If we bind a name to an impure expression, the function is not pure, even
208 if it doesn't use the name.
209
210 | (robin (0 1) ((pure (0 1) *) (concurrency (0 1) *))
211 | (pure-expr? (env) (literal (pid)) (literal
212 | (bind n (send! pid 3) pid))))
213 = #f
214
215 A function which applies one of its arguments is not pure, because its
216 argument might not be pure.
217
218 | (robin (0 1) ((pure (0 1) *))
219 | (pure-expr? (env) (literal (x)) (literal
220 | (x 123))))
221 = #f
222
223 ### `pure-fun-defn?` ###
224
225 TBW
226
227 | (robin (0 1) ((pure (0 1) *))
228 | (pure-fun-defn? (env) (literal
229 | (fun (a) a))))
230 = #t
231
232 We don't do macros yet.
233
234 | (robin (0 1) ((pure (0 1) *))
235 | (pure-fun-defn? (env) (literal
236 | (macro (self args env) args))))
237 = #f
238
239 | (robin (0 1) ((pure (0 1) *))
240 | (pure-fun-defn? (env) (literal
241 | head)))
242 = #t
243
244 | (robin (0 1) ((pure (0 1) *) (concurrency (0 1) *))
245 | (pure-fun-defn? (env) (literal
246 | (fun (a) (send! a a)))))
247 = #f
248
249 | (robin (0 1) ((pure (0 1) *) (concurrency (0 1) *))
250 | (pure-fun-defn? (env) (literal
251 | send!)))
252 = #f
253
254 This is actually pure, but too complex for us to analyze right now,
255 so we pessimistically say no.
256
257 | (robin (0 1) ((pure (0 1) *))
258 | (pure-fun-defn? (env) (literal
259 | ((head (prepend fun ())) (a) a))))
260 = #f
261
262 ### `pure-fun` ###
263
264 (This was copied from the Static Analysis doc and needs rewriting.)
265
266 We can define a macro called, say, `pure-fun`. It accepts the same kinds
267 of arguments as `fun`:
268
269 (bind perimeter (pure-fun (w h) (* 2 (+ w h)))
270 ...)
271
272 `pure-fun` however, examines its second argument in detail before
273 evaluating to a function value which implements this function. It looks up
274 `*` in its environment, sees that there is metadata on the value referred
275 to `*` that indicates that it is pure, and continues. It descends into the
276 term, and sees that `2`, being a literal value, is pure; it sees that `+`
277 is also pure; and it sees that `w` and `h` are arguments to the function.
278 (If these aren't pure, that's not a problem with this function per se.)
279 Having thus proven the expression to be pure, it evaluates the function
280 value in the exact same way that `fun` would, then adds metadata to that
281 value that marks it as `pure`.
282
283 Then `bind` binds the identifier `perimeter` to this value, which has
284 been marked as `pure`; so when we look up `perimeter` in this environment,
285 we know it refers to a pure function. We can use this information in
286 subsequent checks, like:
287
288 (bind perimeter (pure-fun (w h) (* 2 (+ w h)))
289 (bind psquare (pure-fun (w) (perimeter w w))
290 ...))
291
292 This is all well and good for functions, but for other macros, we may
293 need to do more work. Specifically, a macro like `fun` itself, which
294 defines a custom syntax, might need to describe what their syntax is
295 like, in their metadata, so that the purity analyzer can recognize them
296 and process them correctly.
297
298 Probably the most sensible place to start with all this is a macro which
299 defines a function if and only if it can prove that the function has no
300 side-effects. (Otherwise, it presumably raises an exception.)
+0
-19
doc/module/Random.markdown less more
0 Module `random`
1 ===============
2
3 These tests constitute sanity checks; they do not actually test that
4 the generated numbers are random.
5
6 ### `random` ###
7
8 -> Tests for functionality "Interpret Robin Program"
9
10 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (arith (0 1) *) (random (0 1) *))
11 | (call! random range (list 1 6) value
12 | (< value 7)))
13 = #t
14
15 | (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (arith (0 1) *) (random (0 1) *))
16 | (call! random range (list 1 6) value
17 | (>= value 1)))
18 = #t
+0
-403
doc/module/Small.markdown less more
0 Module `small`
1 ==============
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 The `core` module only exports macros which are necessarily, or for reasons
6 of practicality, not implemented in Robin itself. For example, in the Robin
7 reference interpreter, they are implemented in Haskell.
8
9 This small set of macros omits many abstractions to which programmers have
10 become accustomed, and is thus rather brutal to program directly in.
11
12 So to make Robin somewhat easier to program in, the `small` module exports a
13 number of macros which help bring the language up to parity with Pixley.
14
15 That is, the amount of functionality in `small` is rather modest -- only a
16 fraction of what you would find in the Haskell standard prelude, or in R5RS
17 Scheme, or in the Python core.
18
19 All of these macros can be written in core Robin, but whether they are, or
20 provided as builtins, is up to the implementation.
21
22 In addition, the `small` module re-exports everything from `core`, so that
23 it is not necessary to import both of these modules, only `small`.
24
25 Note that, for the purpose of simplicity of definition, the behavior of many
26 of these macros differ from the more usual behavior of raising an
27 `illegal-arguments` exception, when the arguments supplied in the macro
28 call are not satisfactory. In most cases, an exception will be raised,
29 but exactly which exception that is, is not specified. In some cases,
30 extra arguments to the macro will be ignored and discarded. A static
31 analyzer may be provided one day which detects these cases and raises an
32 exception, but that is a matter of static analysis, not execution.
33
34 ### `literal` ###
35
36 One of the most basic identifiers available in `small` is `literal`,
37 which evaluates to the literal content of its sole argument, which can be
38 any S-expression.
39
40 | (robin (0 1) ((small (0 1) *))
41 | (literal symbol))
42 = symbol
43
44 | (robin (0 1) ((small (0 1) *))
45 | (literal (hello (there) world)))
46 = (hello (there) world)
47
48 `literal` requires at least one argument; otherwise, an exception will
49 be raised.
50
51 | (robin (0 1) ((small (0 1) *))
52 | (literal))
53 ? uncaught exception
54
55 Any arguments beyond the first argument are simply ignored and discarded.
56
57 | (robin (0 1) ((small (0 1) *))
58 | (literal a b c))
59 = a
60
61 `literal` is basically equivalent to Scheme's `quote`.
62
63 ### `list` ###
64
65 | (robin (0 1) ((small (0 1)))
66 | (small:list 1 2 3))
67 = (1 2 3)
68
69 Unlike `literal`, `list` does evaluate its arguments, all of them.
70
71 | (robin (0 1) ((small (0 1) *))
72 | (list (literal x) (literal y)))
73 = (x y)
74
75 `list` does not require any arguments.
76
77 | (robin (0 1) ((small (0 1) *))
78 | (list))
79 = ()
80
81 ### `fun` ###
82
83 You can define functions with `fun`. They can be anonymous.
84
85 | (robin (0 1) ((small (0 1) *))
86 | ((fun (a) a) (literal whee)))
87 = whee
88
89 Function have "closure" behavior; that is, bindings in force when a
90 function is defined will still be in force when the function is applied,
91 even if they are no longer lexically in scope.
92
93 | (robin (0 1) ((small (0 1) *))
94 | ((let
95 | ((a (literal (hi)))
96 | (f (fun (x) (list x a))))
97 | f) (literal oh)))
98 = (oh (hi))
99
100 Functions can take functions.
101
102 | (robin (0 1) ((small (0 1) *))
103 | (let
104 | ((apply (fun (x) (x (literal a)))))
105 | (apply (fun (r) (list r)))))
106 = (a)
107
108 Functions can return functions.
109
110 | (robin (0 1) ((small (0 1) *))
111 | (let
112 | ((mk (fun (x) (fun (y) (prepend y x))))
113 | (mk2 (mk (literal (vindaloo)))))
114 | (mk2 (literal chicken))))
115 = (chicken vindaloo)
116
117 Arguments to functions shadow any other bindings in effect.
118
119 | (robin (0 1) ((small (0 1) *))
120 | (let
121 | ((a (literal a))
122 | (b (fun (a) (list a a))))
123 | (b 7)))
124 = (7 7)
125
126 A function may have no arguments at all.
127
128 | (robin (0 1) ((small (0 1) *))
129 | ((fun () 7)))
130 = 7
131
132 But, a function must have exactly both a body and a list of formal arguments.
133 Otherwise, an exception will be raised.
134
135 | (robin (0 1) ((small (0 1) *))
136 | ((fun ())))
137 ? uncaught exception
138
139 | (robin (0 1) ((small (0 1) *))
140 | ((fun)))
141 ? uncaught exception
142
143 | (robin (0 1) ((small (0 1) *))
144 | ((fun (a) a a)))
145 ? uncaught exception
146
147 An `illegal-arguments` exception will be raised if not enough arguments are
148 supplied to a function call.
149
150 | (robin (0 1) ((small (0 1) *))
151 | ((fun (a b) (list b a))
152 | (prepend 1 ())))
153 ? uncaught exception: (illegal-arguments
154
155 An `illegal-arguments` exception will be raised if too many arguments are
156 supplied to a function call.
157
158 | (robin (0 1) ((small (0 1) *))
159 | ((fun (a b) (list b a))
160 | 1 (prepend 2 ()) 3))
161 ? uncaught exception: (illegal-arguments
162
163 `fun` is basically equivalent to Scheme's `lambda`.
164
165 ### `bind` ###
166
167 `bind` binds a single identifier to the result of evaluating a single
168 expression, and makes that binding available in another expression which
169 it evaluates.
170
171 | (robin (0 1) ((small (0 1) *))
172 | (bind x (literal hello)
173 | (list x x)))
174 = (hello hello)
175
176 | (robin (0 1) ((small (0 1) *))
177 | (bind dup (fun (x) (list x x))
178 | (dup (literal g))))
179 = (g g)
180
181 | (robin (0 1) ((small (0 1) *))
182 | (bind dup (fun (x) (list x x))
183 | (dup (dup (literal g)))))
184 = ((g g) (g g))
185
186 | (robin (0 1) ((small (0 1) *))
187 | (bind smoosh (fun (x y) (list y x))
188 | (smoosh #t #f)))
189 = (#f #t)
190
191 | (robin (0 1) ((small (0 1) *))
192 | (bind find (fun (self alist key)
193 | (if (equal? alist (literal ())) (literal ())
194 | (if (equal? key (head (head alist)))
195 | (head alist)
196 | (self self (tail alist) key))))
197 | (find find (literal ((c d) (e f) (a b))) (literal a))))
198 = (a b)
199
200 `bind` expects exactly three arguments, or else an exception will be raised.
201
202 | (robin (0 1) ((small (0 1) *))
203 | (bind smoosh (fun (x y) (list y x))))
204 ? uncaught exception
205
206 | (robin (0 1) ((small (0 1) *))
207 | (bind smoosh))
208 ? uncaught exception
209
210 | (robin (0 1) ((small (0 1) *))
211 | (bind))
212 ? uncaught exception
213
214 `bind` is basically equivalent to Scheme's `let`, but only one
215 binding may be given.
216
217 ### `let` ###
218
219 `let` lets you bind multiple identifiers to multiple values.
220
221 An identifier can be bound to a symbol.
222
223 | (robin (0 1) ((small (0 1) *))
224 | (let ((a (literal hello))) a))
225 = hello
226
227 `let` can appear in the binding expression in a `let`.
228
229 | (robin (0 1) ((small (0 1) *))
230 | (let ((a (let ((b (literal c))) b))) a))
231 = c
232
233 `let` can bind a symbol to a function value.
234
235 | (robin (0 1) ((small (0 1) *))
236 | (let ((a (fun (x y) (prepend y x))))
237 | (a () (literal foo))))
238 = (foo)
239
240 Bindings established in a `let` remain in effect when evaluating
241 the arguments things in the body of the `let`.
242
243 | (robin (0 1) ((small (0 1) *))
244 | (let ((dup (fun (x) (list x x))))
245 | (dup (dup (literal g)))))
246 = ((g g) (g g))
247
248 Bindings established in a binding in a `let` can be seen in
249 subsequent bindings in the same `let`.
250
251 | (robin (0 1) ((small (0 1) *))
252 | (let ((a (literal hello)) (b (list a))) b))
253 = (hello)
254
255 Shadowing happens.
256
257 | (robin (0 1) ((small (0 1) *))
258 | (let ((a (literal hello))) (let ((a (literal goodbye))) a)))
259 = goodbye
260
261 `let` can have an empty list of bindings.
262
263 | (robin (0 1) ((small (0 1) *))
264 | (let () (literal hi)))
265 = hi
266
267 The list of bindings must be a list, or else an exception will be raised.
268
269 | (robin (0 1) ((small (0 1) *))
270 | (let 999 (literal hi)))
271 ? uncaught exception
272
273 Each binding in a list must be a list, or else an exception will be raised.
274
275 | (robin (0 1) ((small (0 1) *))
276 | (let (999) (literal hi)))
277 ? uncaught exception
278
279 Both the body and the list of bindings are required, or else an exception
280 will be raised.
281
282 | (robin (0 1) ((small (0 1) *))
283 | (let ()))
284 ? uncaught exception
285
286 | (robin (0 1) ((small (0 1) *))
287 | (let))
288 ? uncaught exception
289
290 Any arguments given beyond the body and list of bindings will be ignored
291 and discarded, without being evaluated.
292
293 | (robin (0 1) ((small (0 1) *))
294 | (let ((a 1)) a foo))
295 = 1
296
297 Each binding must have at least a name and a value, or else an exception
298 will be raised.
299
300 | (robin (0 1) ((small (0 1) *))
301 | (let ((a)) a))
302 ? uncaught exception
303
304 | (robin (0 1) ((small (0 1) *))
305 | (let (()) 7))
306 ? uncaught exception
307
308 Anything given in a binding beyond the name and the value will simply be
309 ignored and discarded, without being evaluated or otherwise examined.
310
311 | (robin (0 1) ((small (0 1) *))
312 | (let ((a 1 foo)) a))
313 = 1
314
315 The identifier in a binding must be a symbol.
316
317 | (robin (0 1) ((small (0 1) *))
318 | (let ((3 1)) 3))
319 ? uncaught exception: (illegal-binding (3 1))
320
321 `let` is basically equivalent to Scheme's `let*` or Haskell's `let`.
322
323 ### `choose` ###
324
325 `choose` expects to be given a list of tests. Each test is a two-element
326 list, the first element of which is a condition which should evaluate to
327 a boolean, and the second element of which is an expression, which
328 will be evaluated only if the boolean is `#t`, and `choose` will immediately
329 evaluate to that result without trying any of the subsequent tests. The
330 condition in the final test must be the literal symbol `else`; the
331 corresponding expression will be evaluated if all other tests failed.
332
333 | (robin (0 1) ((small (0 1) *))
334 | (choose (#t (literal hi)) (else (literal lo))))
335 = hi
336
337 | (robin (0 1) ((small (0 1) *))
338 | (choose (#f (literal hi)) (#t (literal med)) (else (literal lo))))
339 = med
340
341 | (robin (0 1) ((small (0 1) *))
342 | (choose (#f (literal hi)) (#f (literal med)) (else (literal lo))))
343 = lo
344
345 `choose` can have zero tests before the `else`.
346
347 | (robin (0 1) ((small (0 1) *))
348 | (choose (else (literal woo))))
349 = woo
350
351 `choose` does require an `else` branch, or else an exception will be
352 raised.
353
354 | (robin (0 1) ((small (0 1) *))
355 | (choose (#f (literal hi)) (#f (literal med))))
356 ? uncaught exception
357
358 | (robin (0 1) ((small (0 1) *))
359 | (choose))
360 ? uncaught exception
361
362 Each branch of a `choose` needs to be a two-element list, or else an
363 exception will be raised.
364
365 | (robin (0 1) ((small (0 1) *))
366 | (choose (#t) (else (literal lo))))
367 ? uncaught exception
368
369 | (robin (0 1) ((small (0 1) *))
370 | (choose (#f 66) (else)))
371 ? uncaught exception
372
373 `choose` is basically equivalent to Scheme's `cond`.
374
375 ### `env` ###
376
377 `env` evaluates to all the bindings in effect at the point of execution
378 where this form is encountered, as an alist.
379
380 | (robin (0 1) ((small (0 1) *))
381 | (bind find (fun (self alist key)
382 | (if (equal? alist (literal ())) (literal ())
383 | (if (equal? key (head (head alist)))
384 | (head alist)
385 | (self self (tail alist) key))))
386 | (prepend
387 | (find find (env) (literal boolean?)) (find find (env) (literal prepend)))))
388 = ((boolean? (builtin boolean?)) prepend (builtin prepend))
389
390 `env` expects no arguments. Any arguments supplied will be simply ignored
391 and discarded, without being evaluated.
392
393 | (robin (0 1) ((small (0 1) *))
394 | (bind find (fun (self alist key)
395 | (if (equal? alist (literal ())) (literal ())
396 | (if (equal? key (head (head alist)))
397 | (head alist)
398 | (self self (tail alist) key))))
399 | (prepend
400 | (find find (env find) (literal boolean?))
401 | (find find (env (goofah whatever)) (literal prepend)))))
402 = ((boolean? (builtin boolean?)) prepend (builtin prepend))
+0
-132
doc/module/Term.markdown less more
0 Module `term`
1 =============
2
3 -> Tests for functionality "Interpret Robin Program"
4
5 The `term` module exports macros and functions for working with
6 S-expressions as terms, that is, hierarchical trees of data.
7
8 ### `subst` ###
9
10 `subst` evaluates all three of its arguments to obtain values of any type. It
11 then returns a modification of the third value where all instances of the first
12 value (even those deeply nested within sublists) have been replaced with the
13 second value.
14
15 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
16 | (subst 4 5 4))
17 = 5
18
19 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
20 | (subst 4 5 (literal (1 2 3 4 5))))
21 = (1 2 3 5 5)
22
23 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
24 | (subst 4 5 (literal (one two three four five))))
25 = (one two three four five)
26
27 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
28 | (subst 4 5 (literal (4 1 4 1 4))))
29 = (5 1 5 1 5)
30
31 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
32 | (subst 4 5 (literal (1 4 (1 4 (4 1) 4) 4))))
33 = (1 5 (1 5 (5 1) 5) 5)
34
35 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
36 | (subst 4 () (literal (1 2 3 4))))
37 = (1 2 3 ())
38
39 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
40 | (subst (literal (turkey and cheese)) (literal (pastrami and rye))
41 | (prepend (literal (turkey and bacon)) (literal (turkey and cheese)))))
42 = ((turkey and bacon) pastrami and rye)
43
44 ### `subst-many` ###
45
46 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
47 | (subst-many (literal ((p 100) (q 200)))
48 | (literal (a d (r p q) q (p (z q) p p) p z q)))))
49 = (a d (r 100 200) 200 (100 (z 200) 100 100) 100 z 200)
50
51 ### `literal-with` ###
52
53 | (robin (0 1) ((term (0 1)))
54 | (term:literal-with ((p 100) (q 200))
55 | (a d (r p q) q (p (z q) p p) p z q)))
56 = (a d (r 100 200) 200 (100 (z 200) 100 100) 100 z 200)
57
58 Somewhat unlike `subst-many`, `literal-with` evaluates the expressions
59 given as values in the bindings.
60
61 | (robin (0 1) ((core (0 1) *) (term (0 1) *))
62 | (literal-with ((p (subtract 200 100)) (q (subtract 350 150)))
63 | (a d (r p q) q (p (z q) p p) p z q)))
64 = (a d (r 100 200) 200 (100 (z 200) 100 100) 100 z 200)
65
66 `literal-with` may be given an empty list of bindings; in this case it does
67 the same thing as `literal` would.
68
69 | (robin (0 1) ((term (0 1)))
70 | (term:literal-with ()
71 | (a d (r p q) q (p (z q) p p) p z q)))
72 = (a d (r p q) q (p (z q) p p) p z q)
73
74 ### `cast` ###
75
76 `cast` is a macro which works a lot like Scheme's `quasiquote`, except
77 that the unquote symbol is specified as the first argument of the macro.
78
79 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
80 | (bind b 44
81 | (cast $ (a b c))))
82 = (a b c)
83
84 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
85 | (bind b 44
86 | (cast $ (a ($ b) c))))
87 = (a 44 c)
88
89 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
90 | (bind b 44
91 | (cast $ (a b ($ c)))))
92 ? uncaught exception: (unbound-identifier c)
93
94 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
95 | (bind b 44
96 | (cast $ (a $ b c))))
97 = (a $ b c)
98
99 ### `subst-head` ###
100
101 `subst-head` looks for a particular term only at the beginning of a list,
102 and replaces the head of that list with a new list of terms.
103
104 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
105 | (subst-head (literal ralph) (literal (greta garbo))
106 | (literal (this (ralph person) is here))))
107 = (this (greta garbo person) is here)
108
109 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
110 | (subst-head (literal ralph) (literal (greta garbo))
111 | (literal (this (person ralph) is here))))
112 = (this (person ralph) is here)
113
114 `subst-head` can match any type of data at the head of the list.
115
116 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
117 | (subst-head 123 (literal (x))
118 | (literal (hey (123 123) 123))))
119 = (hey (x 123) 123)
120
121 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
122 | (subst-head (list 123) (literal (x))
123 | (literal (hey (123 123) 123 (123) ((123) 123)))))
124 = (hey (123 123) 123 (123) (x 123))
125
126 However, `subst-head` expects the replacement to be a list.
127
128 | (robin (0 1) ((small (0 1) *) (term (0 1) *))
129 | (subst-head (literal ralph) (literal ronald)
130 | (literal (this (ralph person) is here))))
131 ? uncaught exception: (expected-list ronald)
0 ;(require small list arith)
1
2 (reactor (line-terminal) (list 0 0) (macro (self args env)
3 (let ((event (head args))
4 (payload (head (tail args)))
5 (state (head (tail (tail args))))
6 (x (head state))
7 (y (head (tail state)))
8 (move (fun (msg dx dy state)
9 (let ((newx (add x dx))
10 (newy (add y dy))
11 (newstate (list newx newy))
12 (room (append
13 (literal ''You are in room #'')
14 (list (add newx 65) (add newy 65)))))
15 (list newstate
16 (list (literal writeln) msg)
17 (list (literal writeln) room)))))
18 (dont-understand (fun (state)
19 (list state (list (literal writeln)
20 (literal ''Please enter n, s, e, or w, or q to quit.''))))))
21 (choose
22 ((equal? event (literal init))
23 (list state (list (literal writeln)
24 (literal ''Welcome to Not Quite an Adventure!''))))
25 ((equal? event (literal eof))
26 (list state (list (literal writeln)
27 (literal ''Bye!''))))
28 ((equal? event (literal readln))
29 (if (empty? payload)
30 (dont-understand state)
31 (bind letter (list (head payload))
32 (choose
33 ((equal? letter (literal ''n''))
34 (move (literal ''North!'') 0 1 state))
35 ((equal? letter (literal ''s''))
36 (move (literal ''South!'') 0 (subtract 0 1) state))
37 ((equal? letter (literal ''e''))
38 (move (literal ''East!'') 1 0 state))
39 ((equal? letter (literal ''w''))
40 (move (literal ''West!'') (subtract 0 1) 0 state))
41 ((equal? letter (literal ''q''))
42 (list state (list (literal close) 0)))
43 (else
44 (dont-understand state))))))
45 (else
46 (list state))))))
0 (reactor (line-terminal) 0 (macro (self args env)
1 (bind event (head args)
2 (bind payload (head (tail args))
3 (if (equal? event (literal readln))
4 (list 0 (list (literal writeln) payload))
5 (list 0))))))
+0
-16
eg/console-demo.robin less more
0 (robin (0 1) ((small (0 1) *)
1 (arith (0 1) *)
2 (list (0 1) *)
3 (concurrency (0 1) *)
4 (console (0 1) *))
5 (let (
6 (loop! (fun (self x)
7 (if (equal? x 10000)
8 (call! console deactivate () result ())
9 (call! console position (list (rem x 60) (rem x 19)) result
10 (call! console display (literal ''hi'') result
11 (call! console update () result
12 (self self (+ x 1))))))))
13 )
14 (call! console activate () result
15 (loop! loop! 0))))
0 ;''
1 Deadfish in Robin 0.2 -- requires stdlib
2 ''
3 (reactor (line-terminal) 0 (macro (self args env)
4 (bind event (head args)
5 (bind payload (head (tail args))
6 (bind prev-state (head (tail (tail args)))
7 (bind state
8 (if (equal? prev-state (subtract 0 1))
9 0
10 (if (equal? prev-state 256)
11 0
12 prev-state))
13 (bind prompt (macro (self args env)
14 (bind show (eval env (head args))
15 (bind state (eval env (head (tail args)))
16 (if show
17 (list state
18 (list (literal writeln) (itoa state))
19 (list (literal writeln) (literal ''>> '')))
20 (list state
21 (list (literal writeln) (literal ''>> '')))))))
22 (choose
23 ((equal? event (literal init))
24 (prompt #f state))
25 ((equal? event (literal readln))
26 (bind letter payload
27 (choose
28 ((equal? letter (literal ''d''))
29 (prompt #f (subtract state 1)))
30 ((equal? letter (literal ''i''))
31 (prompt #f (subtract state (subtract 0 1))))
32 ((equal? letter (literal ''s''))
33 (prompt #f (multiply state state)))
34 ((equal? letter (literal ''o''))
35 (prompt #t state))
36 (else (prompt state)))))
37 (else
38 (list state))))))))))
0 (robin (0 1) ((small (0 1) *))
1 (literal hello-world))
0 (reactor (line-terminal) 0 (macro (self args env)
1 (bind event (head args)
2 (if (equal? event (literal init))
3 (list 0
4 (list (literal writeln) (literal ''Hello, world!''))
5 (list (literal close) 0))
6 (list 0)))))
+0
-170
eg/hunt-the-wumpus.robin less more
0 (robin (0 1) ((small (0 1) *)
1 (list (0 1) *)
2 (boolean (0 1) *)
3 (concurrency (0 1) *)
4 (arith (0 1) *)
5 (random (0 1) *)
6 (crude-io (0 1) *)
7 (term (0 1) *))
8 ;''Beginnings of an implementation of Hunt the Wumpus.
9 The !'s aren't quite consistent in this yet.''
10 (let
11 (
12 (caverns (literal (
13 ( 0 0 0) ;(to make it 1-based)
14 ( 2 5 8)
15 ( 1 3 10)
16 ( 2 4 12)
17 ( 3 5 14)
18 ( 1 4 6)
19 ( 5 7 15)
20 ( 6 8 17)
21 ( 1 7 9)
22 ( 8 10 18)
23 ( 2 9 11)
24 (10 12 19)
25 ( 3 11 13)
26 (12 14 20)
27 ( 4 13 15)
28 ( 6 4 16) ;(but 4 doesnt have a tunnel back here?)
29 (15 17 20)
30 ( 7 16 18)
31 ( 9 17 19)
32 (11 18 20)
33 (13 16 19)
34 )))
35 (get-random-room-r! (fun (self unacceptable)
36 (call! random range (list 1 20) room
37 (if (elem? room unacceptable)
38 (self self unacceptable)
39 room))))
40 (get-random-room! (fun (unacceptable)
41 (get-random-room-r! get-random-room-r! unacceptable)))
42 (get-n-random-rooms-r! (fun (self n acc)
43 (if (equal? n 0)
44 acc
45 (self self (subtract n 1)
46 (prepend (get-random-room! acc) acc)))))
47 (get-n-random-rooms! (fun (n acc)
48 (get-n-random-rooms-r! get-n-random-rooms-r! n acc)))
49 (initial-wumpus (get-random-room! ()))
50 (initial-bats (get-n-random-rooms! 2 ()))
51 (initial-pits (get-n-random-rooms! 2 ()))
52 (initial-room (get-random-room! (prepend initial-wumpus (append initial-bats initial-pits))))
53 (initial-arrows 5)
54 (print! (macro (self args env)
55 ;''If the thing to be printed turns out to be the empty list,
56 nothing is printed''
57 (let (
58 (subst-env
59 (map
60 (fun (binding)
61 (prepend (list (literal ?) (head binding)) (tail binding)))
62 env))
63 (subject (subst-many subst-env (head args)))
64 )
65 (if (not (equal? subject ()))
66 (call! crude-output write subject result
67 (eval env (head (tail args))))
68 (eval env (head (tail args)))))))
69 (main! (fun (self room wumpus bats pits arrows)
70 (let
71 (
72 (tunnels (index room caverns))
73 (unrecognized-command! (fun ()
74 (print! (unrecognized command --
75 try (m room) or (s room1 room2 etc))
76 (self self room wumpus bats pits arrows))))
77 (report-room (fun (room)
78 (filter (fun (x) (not (empty? x)))
79 (list
80 (if (equal? room wumpus) (literal (you smell a wumpus)) ())
81 (if (elem? room bats) (literal (fluttering of bat wings nearby)) ())
82 (if (elem? room pits) (literal (you feel a draft)) ())))))
83 (report-nearby (fun (self rooms acc)
84 (if (empty? rooms)
85 acc
86 (self self (tail rooms) (append (report-room (head rooms)) acc)))))
87 (fire (fun (self room itinerary)
88 (if (equal? room wumpus)
89 (literal hit)
90 (if (empty? itinerary)
91 (literal miss)
92 (let
93 (
94 (tunnels (index room caverns))
95 (next-dest (head itinerary))
96 )
97 (if (elem? next-dest tunnels)
98 (self self next-dest (tail itinerary))
99 (literal wall)))))))
100 (move-wumpus! (fun (arrows-now)
101 (call! random range (list 1 4) die-roll
102 (bind wumpus-now
103 (if (equal? die-roll 1)
104 wumpus
105 (print! (you hear the wumpus moving)
106 (call! random range (list 0 2) wumpus-tunnel
107 (index wumpus-tunnel (index wumpus caverns)))))
108 (if (equal? wumpus-now room)
109 (print! (oh dear the wumpus saw you and it ATE YOU UP OM NOM NOM NOM)
110 #f)
111 (self self room wumpus-now bats pits arrows-now))))))
112 )
113 (print! (you are in room (? room) with (? arrows) arrows --
114 tunnels lead to rooms (? tunnels))
115 (choose
116 ((equal? arrows 0)
117 (print! (no arrows left! how does it feel to be a sitting duck?)
118 #f))
119 ((elem? room bats)
120 (print! (ZAP super bat snatch! elsewheresville for you!)
121 (self self (get-random-room ()) wumpus bats pits arrows)))
122 ((elem? room pits)
123 (print! (YIIIEEEEEE -- fell in a bottomless pit)
124 #f))
125 ((equal? room wumpus)
126 (print! (egad the wumpus is right here)
127 (move-wumpus! arrows)))
128 (else
129 (bind whats-nearby (report-nearby report-nearby tunnels ())
130 (print! (? whats-nearby)
131 (recv! entered
132 (choose
133 ((equal? entered (literal eof))
134 (print! (gave up eh? no wumpus for you)
135 #f))
136 ((list? entered)
137 (bind command (head entered)
138 (choose
139 ((equal? command (literal m))
140 (bind dest (head (tail entered))
141 (if (elem? dest tunnels)
142 (self self dest wumpus bats pits arrows)
143 (print! (no tunnel in that direction)
144 (self self room wumpus bats pits arrows)))))
145 ((equal? command (literal s))
146 (bind itinerary (tail entered)
147 (if (> (length itinerary) 5)
148 (print! (your arrows have a maximum range of 5 rooms)
149 (self self room wumpus bats pits arrows))
150 (print! (firing an arrow into rooms (? itinerary) here we go)
151 (bind result (fire fire room itinerary)
152 (choose
153 ((equal? result (literal hit))
154 (print! (great shot! you got the wumpus!)
155 #t))
156 ((equal? result (literal miss))
157 (print! (your arrow did not hit anything)
158 (move-wumpus! (subtract arrows 1))))
159 ((equal? result (literal wall))
160 (print! (a miscalculation -- your arrow hit a wall)
161 (move-wumpus! (subtract arrows 1))))))))))
162 (else
163 (unrecognized-command!)))))
164 (else
165 (unrecognized-command!))))))))))))
166 )
167 (call! crude-input subscribe () x
168 (main! main! initial-room initial-wumpus initial-bats
169 initial-pits initial-arrows))))
+0
-4
eg/input.robin less more
0 (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
1 (call! crude-input subscribe () x
2 (recv! entered
3 (list (literal i-got) entered))))
+0
-10
eg/interactive.robin less more
0 (robin (0 1) ((small (0 1) *) (concurrency (0 1) *) (crude-io (0 1) *))
1 (bind input-loop
2 (fun (self)
3 (recv! entered
4 (if (equal? entered (literal eof))
5 #f
6 (call! crude-output write (list #t entered) foo
7 (self self)))))
8 (call! crude-input subscribe () x
9 (input-loop input-loop))))
0 (reactor (line-terminal) 0 (macro (self args env)
1 (bind event (head args)
2 (bind payload (head (tail args))
3 (if (equal? event (literal readln))
4 (list 0
5 (literal what-is-this)
6 (literal i-dont-even))
7 (list 0))))))
+0
-2
eg/purity-check.robin less more
0 (robin (0 1) ((pure (0 1) *))
1 (pure? (env) (literal (foo)) (literal (macro (self args env) foo))))
+0
-13
eg/random.robin less more
0 (robin (0 1) ((small (0 1) *)
1 (list (0 1) *)
2 (concurrency (0 1) *)
3 (crude-io (0 1) *)
4 (random (0 1) *))
5 (bind output-loop
6 (fun (self n)
7 (if (equal? n 0)
8 (literal done)
9 (call! random range (list 1 6) value
10 (call! crude-output write value response
11 (self self (subtract n 1))))))
12 (output-loop output-loop 20)))
0 (define inc (fun (a) (subtract a (subtract 0 1))))
1 (reactor (line-terminal) 0 (macro (self args env)
2 (bind event (head args)
3 (bind payload (head (tail args))
4 (if (equal? event (literal readln))
5 (list 0 (list (literal writeln) payload))
6 (list 0))))))
7 (reactor (line-terminal) 65 (macro (self args env)
8 (bind event (head args)
9 (bind payload (head (tail args))
10 (bind state (head (tail (tail args)))
11 (if (equal? state 67)
12 (list state (list (literal close) 0))
13 (if (equal? event (literal readln))
14 (list (inc state) (list (literal writeln) (list state)))
15 (list state))))))))
+0
-22
eg/repl.robin less more
0 (robin (0 1) ((small (0 1) *)
1 (exception (0 1) *)
2 (concurrency (0 1) *)
3 (crude-io (0 1) *)
4 (env (0 1) *))
5 (let (
6 (restricted-env
7 (export prepend head tail if equal? list? macro? symbol? boolean?
8 number? subtract divide floor sign eval macro raise with has?
9 literal fun bind let choose env))
10 (input-loop
11 (fun (self)
12 (recv! entered
13 (if (equal? entered (literal eof))
14 (literal bye)
15 (bind result (catch error (list (literal error) error)
16 (eval restricted-env entered))
17 (call! crude-output write result foo
18 (self self)))))))
19 )
20 (call! crude-input subscribe () x
21 (input-loop input-loop))))
0 ;''
1
2 If you just try
3
4 bin/robin eg/uses-modules.robin
5
6 you will get an error about an unbound identifier, something like:
7
8 robin: uncaught exception: (unbound-identifier let)
9
10 You need to load the modules it uses first! Try
11
12 bin/robin pkg/small.robin eg/uses-modules.robin
13
14 or if you really like minimalism,
15
16 bin/robin stdlib/literal.robin stdlib/bind.robin stdlib/let.robin \
17 stdlib/env.robin stdlib/list.robin eg/uses-modules.robin
18
19 In this case, you need to include `bind` because `let` is defined in
20 terms of it.
21
22 ''
23
24 (display
25 (let ((a (literal hi))) (env)))
26 (display (list 2 3 4 5 6))
+0
-5
fixture/config/BuiltInSmall.markdown less more
0 -> Functionality "Interpret Robin Program" is implemented by shell command
1 -> "bin/robin -m module -m fixture/module %(test-file)"
2
3 -> Functionality "Interpret Robin Program without output" is implemented by shell command
4 -> "bin/robin -m module -n %(test-file)"
+0
-5
fixture/config/SmallInRobin.markdown less more
0 -> Functionality "Interpret Robin Program" is implemented by shell command
1 -> "bin/robin -m module -B small -m fixture/module %(test-file)"
2
3 -> Functionality "Interpret Robin Program without output" is implemented by shell command
4 -> "bin/robin -m module -B small -n %(test-file)"
+0
-2
fixture/module/circular-a_0_1.robin less more
0 (robin (0 1) ((small (0 1) *) (circular-b (0 1) *))
1 (list (list (literal literal-a) literal-b)))
+0
-2
fixture/module/circular-b_0_1.robin less more
0 (robin (0 1) ((small (0 1) *) (circular-a (0 1) *))
1 (list (list (literal literal-b) literal-a)))
+0
-2
fixture/module/random-a_0_1.robin less more
0 (robin (0 1) ((small (0 1) *) (random (0 1) *))
1 (list (list (literal random-a) random)))
+0
-2
fixture/module/random-b_0_1.robin less more
0 (robin (0 1) ((small (0 1) *) (random (0 1) *))
1 (list (list (literal random-b) random)))
0 -> Functionality "Interpret core Robin Program" is implemented by shell command
1 -> "bin/robinri %(test-body-file)"
2
3 -> Functionality "Interpret Robin Program" is implemented by shell command
4 -> "bin/robinri pkg/small.robin pkg/intrinsics-wrappers.robin %(test-body-file)"
5
6 -> Functionality "Interpret Robin Program (with Small)" is implemented by shell command
7 -> "bin/robinri pkg/small.robin pkg/intrinsics-wrappers.robin %(test-body-file)"
8
9 -> Functionality "Interpret Robin Program (with Fun)" is implemented by shell command
10 -> "bin/robinri pkg/small.robin pkg/intrinsics-wrappers.robin pkg/fun.robin %(test-body-file)"
11
12 -> Functionality "Interpret Robin Program (with List)" is implemented by shell command
13 -> "bin/robinri pkg/small.robin pkg/intrinsics-wrappers.robin pkg/fun.robin pkg/list.robin %(test-body-file)"
14
15 -> Functionality "Interpret Robin Program (with Env)" is implemented by shell command
16 -> "bin/robinri pkg/small.robin pkg/intrinsics-wrappers.robin pkg/fun.robin pkg/list.robin pkg/env.robin %(test-body-file)"
17
18 -> Functionality "Interpret Robin Program (with Boolean)" is implemented by shell command
19 -> "bin/robinri pkg/small.robin pkg/intrinsics-wrappers.robin pkg/boolean.robin %(test-body-file)"
20
21 -> Functionality "Interpret Robin Program (with Arith)" is implemented by shell command
22 -> "bin/robinri pkg/small.robin pkg/intrinsics-wrappers.robin pkg/fun.robin pkg/arith.robin %(test-body-file)"
23
24 -> Functionality "Interpret Robin Program (with List-Arith)" is implemented by shell command
25 -> "bin/robinri pkg/small.robin pkg/intrinsics-wrappers.robin pkg/fun.robin pkg/list.robin pkg/arith.robin pkg/list-arith.robin %(test-body-file)"
26
27 -> Functionality "Interpret Robin Program (with Stdlib)" is implemented by shell command
28 -> "bin/robinri pkg/stdlib.robin %(test-body-file)"
0 -> Functionality "Interpret core Robin Program" is implemented by shell command
1 -> "bin/whitecap --no-builtins %(test-body-file)"
2
3 -> Functionality "Interpret Robin Program" is implemented by shell command
4 -> "bin/whitecap %(test-body-file)"
5
6 -> Functionality "Interpret Robin Program (with Small)" is implemented by shell command
7 -> "bin/whitecap %(test-body-file)"
8
9 -> Functionality "Interpret Robin Program (with Fun)" is implemented by shell command
10 -> "bin/whitecap %(test-body-file)"
11
12 -> Functionality "Interpret Robin Program (with List)" is implemented by shell command
13 -> "bin/whitecap pkg/list.robin %(test-body-file)"
14
15 -> Functionality "Interpret Robin Program (with Boolean)" is implemented by shell command
16 -> "bin/whitecap pkg/boolean.robin %(test-body-file)"
17
18 -> Functionality "Interpret Robin Program (with Env)" is implemented by shell command
19 -> "bin/whitecap pkg/list.robin pkg/env.robin %(test-body-file)"
20
21 -> Functionality "Interpret Robin Program (with Arith)" is implemented by shell command
22 -> "bin/whitecap pkg/arith.robin %(test-body-file)"
23
24 -> Functionality "Interpret Robin Program (with List-Arith)" is implemented by shell command
25 -> "bin/whitecap pkg/list.robin pkg/arith.robin pkg/list-arith.robin %(test-body-file)"
26
27 -> Functionality "Interpret Robin Program (with Stdlib)" is implemented by shell command
28 -> "bin/whitecap pkg/stdlib-for-robini.robin %(test-body-file)"
+0
-75
module/arith_0_1.robin less more
0 (robin (0 1) ((small (0 1) *) (env (0 1) *))
1 (let (
2 (add (fun (a b)
3 (subtract a (subtract 0 b))))
4 (+ (macro (self args env)
5 (if (equal? args ())
6 0
7 (add (eval env (head args))
8 (eval env (prepend self (tail args)))))))
9 (sum-r (fun (self li)
10 (if (equal? li ())
11 0
12 (+ (head li) (self self (tail li))))))
13 (sum (fun (li)
14 (sum-r sum-r li)))
15 (- (fun (a b)
16 (subtract a b)))
17 (multiply (fun (a b)
18 (if (equal? b 0) 0 (divide a (divide 1 b)))))
19 (* (macro (self args env)
20 (if (equal? args ())
21 1
22 (multiply (eval env (head args))
23 (eval env (prepend self (tail args)))))))
24 (product-r (fun (self li)
25 (if (equal? li ())
26 1
27 (* (head li) (self self (tail li))))))
28 (product (fun (li)
29 (product-r product-r li)))
30 (/ (fun (a b)
31 (divide a b)))
32 (abs (fun (a)
33 (* a (sign a))))
34 (frac (fun (a)
35 (subtract (abs a) (floor (abs a)))))
36 (integer? (fun (a)
37 (equal? (frac a) 0)))
38 (div (fun (a b)
39 (floor (/ (floor a) (floor b)))))
40 (rem (fun (a b)
41 (- a (* (div a b) b))))
42 (> (fun (a b)
43 (equal? (sign (- a b)) 1)))
44 (>= (fun (a b)
45 (if (equal? a b) #t (equal? (sign (- a b)) 1))))
46 (< (fun (a b)
47 (equal? (sign (- a b)) (- 0 1))))
48 (<= (fun (a b)
49 (if (equal? a b) #t (equal? (sign (- a b)) (- 0 1)))))
50 (cmp-list?-r (fun (self op li)
51 (if (equal? li ()) #t
52 (if (equal? (tail li) ()) #t
53 (if (op (head li) (head (tail li)))
54 (self self op (tail li))
55 #f)))))
56 (ascending? (fun (li)
57 (cmp-list?-r cmp-list?-r <= li)))
58 (strictly-ascending? (fun (li)
59 (cmp-list?-r cmp-list?-r < li)))
60 (descending? (fun (li)
61 (cmp-list?-r cmp-list?-r >= li)))
62 (strictly-descending? (fun (li)
63 (cmp-list?-r cmp-list?-r > li)))
64 (natural? (fun (a)
65 (if (equal? (frac a) 0) (>= a 0) #f)))
66 )
67 (export add + sum -
68 multiply * product /
69 div rem
70 abs frac
71 integer? natural?
72 > >= < <=
73 ascending? strictly-ascending?
74 descending? strictly-descending?)))
+0
-25
module/assert_0_1.robin less more
0 (robin (0 1) ((small (0 1) *) (env (0 1) *) (arith (0 1) *))
1 (let (
2 (assert (macro (self args env)
3 (let ((expr (head args))
4 (body (head (tail args))))
5 (if (eval env expr)
6 (eval env body)
7 (raise (list (literal assertion-failed) expr))))))
8 (mk-assert (fun (pred message)
9 (macro (self args env)
10 (let ((expr (head args))
11 (body (head (tail args))))
12 (if (pred (eval env expr))
13 (eval env body)
14 (raise (list message expr)))))))
15 (assert-boolean (mk-assert boolean? (literal expected-boolean)))
16 (assert-number (mk-assert number? (literal expected-number)))
17 (assert-symbol (mk-assert symbol? (literal expected-symbol)))
18 (assert-list (mk-assert list? (literal expected-list)))
19 (assert-macro (mk-assert macro? (literal expected-macro)))
20 (assert-integer (mk-assert integer? (literal expected-integer)))
21 (assert-natural (mk-assert natural? (literal expected-natural)))
22 )
23 (export assert assert-boolean assert-number assert-symbol
24 assert-macro assert-list)))
+0
-35
module/bind-args_0_1.robin less more
0 (robin (0 1) ((small (0 1) *))
1 ;''Should really be a part of small, but prototyping
2 it here now.''
3 (let (
4 (bind-args
5 (macro (self args env)
6 (let (
7 (id-list (head args))
8 (orig-val-list (eval env (head (tail args))))
9 (given-env (eval env (head (tail (tail args)))))
10 (expr (head (tail (tail (tail args)))))
11 (bind-args-r (macro (self args env)
12 (let (
13 (id-list (eval env (head args)))
14 (val-list (eval env (head (tail args))))
15 (env-acc (eval env (head (tail (tail args)))))
16 )
17 (if (equal? id-list ())
18 (if (equal? val-list ())
19 env-acc
20 (raise (list (literal illegal-arguments) orig-val-list)))
21 (if (equal? val-list ())
22 (raise (list (literal illegal-arguments) orig-val-list))
23 (self
24 (tail id-list) (tail val-list)
25 (prepend
26 (list (head id-list) (eval given-env (head val-list)))
27 env-acc)))))))
28 (new-env (bind-args-r id-list orig-val-list env))
29 )
30 (eval new-env expr))))
31 )
32 (list
33 (list (literal bind-args) bind-args)
34 )))
+0
-44
module/boolean_0_1.robin less more
0 (robin (0 1) ((small (0 1) *) (env (0 1) *) (list (0 1) *))
1 (let (
2 (and (macro (self args env)
3 (if (equal? (length args) 2)
4 (if (eval env (head args))
5 (if (eval env (head (tail args))) #t #f)
6 #f)
7 (raise (list (literal illegal-arguments) args)))))
8 (and* (macro (self args env)
9 (if (equal? args ())
10 #t
11 (and (eval env (head args))
12 (eval env (prepend self (tail args)))))))
13 (conj-r (fun (self li)
14 (if (equal? li ())
15 #t
16 (and (head li)
17 (self self (tail li))))))
18 (conj (fun (li)
19 (conj-r conj-r li)))
20 (or (macro (self args env)
21 (if (equal? (length args) 2)
22 (if (eval env (head args))
23 #t
24 (if (eval env (head (tail args))) #t #f))
25 (raise (list (literal illegal-arguments) args)))))
26 (or* (macro (self args env)
27 (if (equal? args ())
28 #f
29 (or (eval env (head args))
30 (eval env (prepend self (tail args)))))))
31 (disj-r (fun (self li)
32 (if (equal? li ())
33 #f
34 (or (head li)
35 (self self (tail li))))))
36 (disj (fun (li)
37 (disj-r disj-r li)))
38 (not (fun (a)
39 (if a #f #t)))
40 (xor (fun (a b)
41 (or (and a (not b)) (and (not a) b))))
42 )
43 (export and and* conj or or* disj not xor)))
+0
-41
module/env_0_1.robin less more
0 (robin (0 1) ((small (0 1) *) (list (0 1) *))
1 (let (
2 (env? (fun (li)
3 (bind env?-r (fun (self li)
4 (if (empty? li)
5 #t
6 (if (list? li)
7 (bind binding (head li)
8 (if (list? binding)
9 (if (symbol? (head binding))
10 (self self (tail li))
11 #f)
12 #f))
13 #f)))
14 (env?-r env?-r li))))
15 (unbind
16 (macro (self args env)
17 (eval (filter (fun (binding) (if (equal? (head binding) (head args)) #f #t)) env)
18 (head (tail args)))))
19 (unshadow
20 (macro (self args env)
21 (bind remove-binding-r (fun (self id li)
22 (if (empty? li)
23 li
24 (if (equal? (head (head li)) id)
25 (tail li)
26 (prepend (head li) (self self id (tail li))))))
27 (eval (remove-binding-r remove-binding-r (head args) env)
28 (head (tail args))))))
29 (sandbox
30 (macro (self args env)
31 (eval (filter (fun (binding) (elem? (head binding) (head args))) env)
32 (head (tail args)))))
33 (export
34 (macro (self args env)
35 (filter (fun (binding) (elem? (head binding) args)) env)))
36 )
37 (export env bind let env? unbind unshadow sandbox export)
38 )
39 )
40
+0
-139
module/list_0_1.robin less more
0 (robin (0 1) ((small (0 1) *))
1 (let (
2 (empty? (fun (li)
3 (equal? li ())))
4 (map (fun (app li)
5 (bind map-r
6 (fun (self app li)
7 (if (empty? li)
8 ()
9 (prepend (app (head li)) (self self app (tail li)))))
10 (map-r map-r app li))))
11 (fold (fun (app acc li)
12 (bind fold-r (fun (self app acc li)
13 (if (empty? li)
14 acc
15 (self self app (app (head li) acc) (tail li))))
16 (fold-r fold-r app acc li))))
17 (reverse (fun (li)
18 (fold prepend () li)))
19 (filter (fun (pred li)
20 (reverse (fold
21 (fun (x acc) (if (pred x) (prepend x acc) acc))
22 () li))))
23 (find (fun (pred li)
24 (bind find-r (fun (self pred li)
25 (if (empty? li)
26 ()
27 (if (pred (head li))
28 (list (head li))
29 (self self pred (tail li)))))
30 (find-r find-r pred li))))
31 (append (fun (li new-tail)
32 (bind append-r (fun (self li new-tail)
33 (if (empty? li)
34 new-tail
35 (prepend (head li) (self self (tail li) new-tail))))
36 (append-r append-r li new-tail))))
37 (elem? (fun (item li)
38 (bind elem?-r (fun (self item li)
39 (if (empty? li)
40 #f
41 (if (equal? item (head li))
42 #t
43 (self self item (tail li)))))
44 (elem?-r elem?-r item li))))
45 (length (fun (li)
46 (subtract 0 (fold (fun (x acc) (subtract acc 1)) 0 li))))
47 (index (fun (index li)
48 (bind index-r (fun (self index li)
49 (if (equal? index 0)
50 (head li)
51 (self self (subtract index 1) (tail li))))
52 (index-r index-r index li))))
53 (take-while (fun (pred li)
54 (bind take-while-r (fun (self pred li)
55 (if (empty? li)
56 ()
57 (if (pred (head li))
58 (prepend (head li) (self self pred (tail li)))
59 ())))
60 (take-while-r take-while-r pred li))))
61 (drop-while (fun (pred li)
62 (bind drop-while-r (fun (self pred li)
63 (if (empty? li)
64 ()
65 (if (pred (head li))
66 (self self pred (tail li))
67 li)))
68 (drop-while-r drop-while-r pred li))))
69 (first (fun (n li)
70 (bind first-r (fun (self n li)
71 (if (equal? n 0)
72 ()
73 (prepend (head li) (self self (subtract n 1) (tail li)))))
74 (first-r first-r n li))))
75 (rest (fun (n li)
76 (bind rest-r (fun (self n li)
77 (if (equal? n 0)
78 li
79 (self self (subtract n 1) (tail li))))
80 (rest-r rest-r n li))))
81 (last (fun (n li)
82 (reverse (first n (reverse li)))))
83 (prefix? (fun (la lb)
84 (bind prefix?-r (fun (self la lb)
85 (if (empty? la)
86 #t
87 (if (empty? lb)
88 #f
89 (if (equal? (head la) (head lb))
90 (self self (tail la) (tail lb))
91 #f))))
92 (prefix?-r prefix?-r la lb))))
93 (flatten (fun (li)
94 (bind flatten-r (fun (self li acc)
95 (if (empty? li)
96 acc
97 (if (list? (head li))
98 (self self (tail li) (self self (head li) acc))
99 (self self (tail li) (prepend (head li) acc)))))
100 (reverse (flatten-r flatten-r li ())))))
101 (lookup (fun (id alist)
102 (bind lookup-r (fun (self id alist)
103 (if (empty? alist)
104 ()
105 (if (equal? id (head (head alist)))
106 (list (head (tail (head alist))))
107 (self self id (tail alist)))))
108 (lookup-r lookup-r id alist))))
109 (extend (fun (id val alist)
110 (prepend (list id val) alist)))
111 (delete (fun (id alist)
112 (filter (fun (x) (if (equal? (head x) id) #f #t)) alist)))
113 )
114 (list
115 (list (literal list) list)
116 (list (literal empty?) empty?)
117 (list (literal map) map)
118 (list (literal fold) fold)
119 (list (literal reverse) reverse)
120 (list (literal filter) filter)
121 (list (literal find) find)
122 (list (literal append) append)
123 (list (literal elem?) elem?)
124 (list (literal length) length)
125 (list (literal index) index)
126 (list (literal take-while) take-while)
127 (list (literal drop-while) drop-while)
128 (list (literal first) first)
129 (list (literal rest) rest)
130 (list (literal last) last)
131 (list (literal prefix?) prefix?)
132 (list (literal flatten) flatten)
133 (list (literal lookup) lookup)
134 (list (literal extend) extend)
135 (list (literal delete) delete)
136 )
137 )
138 )
+0
-150
module/pure_0_1.robin less more
0 (robin (0 1) ((small (0 1) *) (list (0 1) *) (env (0 1) *) (metadata (0 1) *))
1 ;''This is an EXPERIMENTAL module for EXPERIMENTING with
2 static analysis in Robin using metadata on values.''
3 (let (
4 (head (with pure #t head))
5 (tail (with pure #t tail))
6 (prepend (with pure #t prepend))
7 (list? (with pure #t list?))
8 (symbol? (with pure #t symbol?))
9 (number? (with pure #t number?))
10 (boolean? (with pure #t boolean?))
11 (macro? (with pure #t macro?))
12 (subtract (with pure #t subtract))
13 (divide (with pure #t divide))
14 (floor (with pure #t floor))
15 (sign (with pure #t sign))
16 (macro (with definer #t (with pure #t macro)))
17 (if (with pure #t if))
18 (with (with pure #t with))
19 (has? (with pure #t has?))
20 (literal (with pure #t literal))
21 (bind (with binder #t (with pure #t bind)))
22 (env (with pure #t env))
23 (fun (with definer #t (with pure #t fun)))
24 (dummy-fun (fun (x) x))
25 (pure-fun-defn?-r (fun (self pure-expr?-r env expr)
26 ;''XXX The following is badly written.''
27 (choose
28 ((list? expr)
29 (let ((apply-expr (head expr))
30 (maybe-applier (lookup apply-expr env)))
31 (choose
32 ((equal? maybe-applier (list fun))
33 (let ((args (head (tail expr)))
34 (body (head (tail (tail expr)))))
35 (pure-expr?-r pure-expr?-r env args body)))
36 (else
37 #f))))
38 ((symbol? expr)
39 (bind maybe-val (lookup expr env)
40 (choose
41 ((equal? maybe-val ())
42 #f)
43 ((macro? (head maybe-val))
44 (has? pure (head maybe-val)))
45 (else
46 #f))))
47 (else
48 #f))))
49 ;''TODO: can we replace this with an `all` fold?''
50 ;''TODO: instead of passing `args` here we should pre-extend
51 `env` with some dummy values with appropriate metadata''
52 (pure-args?-r (fun (self pure-expr?-r env args li)
53 (choose
54 ((empty? li)
55 #t)
56 ((list? li)
57 (if (pure-expr?-r pure-expr?-r env args (head li))
58 (self self pure-expr?-r env args (tail li))
59 #f))
60 (else
61 #f))))
62 ;''TODO: instead of passing `args` here we should pre-extend
63 `env` with some dummy values with appropriate metadata''
64 (pure-expr?-r (fun (self env args expr)
65 (choose
66 ((elem? expr args) #t)
67 ((number? expr) #t)
68 ((macro? expr) (has? pure expr))
69 ((boolean? expr) #t)
70 ((empty? expr) #t)
71 ;''XXX The following is badly written.''
72 ((list? expr)
73 ;''If the head of the list is an S-expr which represents a
74 pure fun, such as 'head' or '(fun (x) x)', then this
75 expression is pure if all of the actual arguments are
76 pure. BUT -- first we must special-case some things.''
77 (let ((apply-expr (head expr))
78 (maybe-applier (lookup apply-expr env)))
79 (choose
80 ((equal? maybe-applier ())
81 #f)
82 ((has? binder (head maybe-applier))
83 ;''When analyzing a `bind` expression, we analyze the value
84 being bound to see if it, too, is pure or not. We then
85 extend the environment with a value for the bound
86 identifier; this value is a dummy value, but it does
87 carry the appropriate metadata, so it correctly detects
88 if the value is pure or not, if it subsequently used.''
89 (let
90 ((ident (head (tail expr)))
91 (bound-expr (head (tail (tail expr)))))
92 ;''If the expr being bound is pure...''
93 (if (self self env args bound-expr)
94 ;''Analyze the body in a new environment
95 in which this identifier is bound to a
96 placeholder; mark the placeholder as pure
97 iff `pure-fun-defn?` is true for the
98 bound expression.''
99 (let
100 ((bound-pure-fun
101 (pure-fun-defn?-r pure-fun-defn?-r
102 self env bound-expr))
103 (placeholder
104 (if bound-pure-fun
105 (with pure #t dummy-fun)
106 dummy-fun))
107 (new-env
108 (extend ident placeholder env))
109 (body-expr
110 (head (tail (tail (tail expr))))))
111 (self self new-env args body-expr))
112 #f)))
113 ((has? definer (head maybe-applier))
114 ;''A "definer" expression (such as `macro` or `fun`), which
115 simply evaluates to a macro value of some kind, is pure.
116
117 XXX We will still want to evaluate the body of the
118 definition, to see if it evaluates to a pure function
119 (or macro). This will be valuable in case the function
120 (or macro) is used later in the larger expression, i.e.
121 (bind x (fun ...) (x y z))''
122 (self self env args apply-expr))
123 ((pure-fun-defn?-r pure-fun-defn?-r self env apply-expr)
124 (pure-args?-r pure-args?-r self env args (tail expr)))
125 ((self self env args apply-expr)
126 ;''XXX We should only do this if the applier in question
127 is a function (or function-like.) It may be a macro
128 which does anything it wants to the args. This would
129 be harder to analyze in the general case.''
130 (pure-args?-r pure-args?-r self env args (tail expr)))
131 (else
132 #f))))
133 ((symbol? expr)
134 (bind maybe-val (lookup expr env)
135 (if (equal? maybe-val ())
136 #f
137 (self self env args (head maybe-val)))))
138 (else
139 #f))))
140 (pure-expr? (fun (env args expr) (pure-expr?-r pure-expr?-r env args expr)))
141 ;''The following is mainly for testing''
142 (pure-fun-defn? (fun (env expr)
143 (pure-fun-defn?-r pure-fun-defn?-r pure-expr?-r env expr)))
144 )
145 (export head tail prepend list? symbol? number? macro? boolean?
146 subtract divide floor sign macro if with has?
147 eval
148 literal env fun bind
149 pure-expr? pure-fun-defn?)))
+0
-89
module/small_0_1.robin less more
0 (robin (0 1) ((core (0 1) *))
1 (eval
2 (prepend
3 (prepend ((macro (self args env) (head args)) literal) (prepend (macro (self args env) (head args)) ()))
4 (prepend
5 (prepend ((macro (self args env) (head args)) bind)
6 (prepend (macro (self args env)
7 (eval
8 (prepend (prepend (head args) (prepend (eval env (head (tail args))) ())) env)
9 (head (tail (tail args))))) ()))
10 (prepend
11 (prepend ((macro (self args env) (head args)) env) (prepend (macro (self args env) env) ()))
12 ((macro (self args env) env))
13 )
14 )
15 )
16 ((macro (self args env) (head args))
17 (bind let (macro (self args env)
18 (bind bindings (head args)
19 (if (equal? bindings ())
20 (eval env (head (tail args)))
21 (bind binding (head bindings)
22 (bind name (head binding)
23 (if (symbol? name)
24 (bind value (eval env (head (tail binding)))
25 (bind newenv (prepend (prepend name (prepend value ())) env)
26 (bind newbindings (tail bindings)
27 (bind newargs (prepend newbindings (tail args))
28 (eval newenv (prepend self newargs))))))
29 (raise (prepend (literal illegal-binding) (prepend binding ())))))))))
30 (let
31 (
32 (list (macro (self args env)
33 (if (equal? args ())
34 ()
35 (prepend (eval env (head args))
36 (eval env (prepend self (tail args)))))))
37 (choose (macro (self args env)
38 (let
39 ((branch (head args))
40 (test (head branch))
41 (then (head (tail branch))))
42 (if (equal? test (literal else))
43 (eval env then)
44 (if (eval env test)
45 (eval env then)
46 (eval env (prepend self (tail args))))))))
47 (fun (macro (self args env)
48 (let ((formals (head args))
49 (body (head (tail args)))
50 (make-env (macro (self args env)
51 (let (
52 (closed-env (head args))
53 (fun-env (head (tail args)))
54 (formals (head (tail (tail args))))
55 (actuals (head (tail (tail (tail args)))))
56 )
57 (if (equal? formals ())
58 (if (equal? actuals ())
59 closed-env
60 (raise (literal (illegal-arguments))))
61 (if (equal? actuals ())
62 (raise (literal (illegal-arguments)))
63 (let (
64 (value (eval fun-env (head actuals)))
65 (new-closed-env (prepend (prepend (head formals) (prepend value ())) closed-env))
66 (new-args (prepend new-closed-env (prepend fun-env (prepend (tail formals) (prepend (tail actuals) ())))))
67 )
68 (eval env
69 (prepend self new-args))))))))
70 (make-env-wrap (macro (self args env)
71 (let (
72 (closed-env (eval env (head args)))
73 (fun-env (eval env (head (tail args))))
74 (formals (eval env (head (tail (tail args)))))
75 (actuals (eval env (head (tail (tail (tail args))))))
76 (new-args (prepend closed-env (prepend fun-env (prepend formals (prepend actuals ())))))
77 )
78 (eval env
79 (prepend make-env new-args))))))
80 (macro (fun-self actuals fun-env)
81 (eval (make-env-wrap env fun-env formals actuals) body)))))
82 )
83 (env)
84 )
85 )
86 )
87 )
88 )
+0
-75
module/term_0_1.robin less more
0 (robin (0 1) ((small (0 1) *) (list (0 1) *))
1 (let (
2 (subst (fun (src dest sexp)
3 (bind subst-r (fun (self src dest sexp)
4 (choose
5 ((equal? sexp src)
6 dest)
7 ((empty? sexp)
8 ())
9 ((list? sexp)
10 (prepend (self self src dest (head sexp))
11 (self self src dest (tail sexp))))
12 (else
13 sexp)))
14 (subst-r subst-r src dest sexp))))
15 (subst-many (fun (alist sexp)
16 (fold (fun (binding sexp)
17 (subst (head binding) (head (tail binding)) sexp)) sexp alist)))
18 (literal-with (macro (self args env)
19 (let (
20 (alist (head args))
21 (body (head (tail args)))
22 )
23 (fold (fun (binding sexp)
24 (subst (head binding) (eval env (head (tail binding))) sexp))
25 body alist))))
26 (cast (macro (self args env)
27 (bind cast-r (fun (self marker fn head-pos sexp)
28 (choose
29 ((empty? sexp)
30 ())
31 ((list? sexp)
32 (if head-pos
33 (if (equal? (head sexp) marker)
34 (fn (head (tail sexp)))
35 ;else
36 (prepend (self self marker fn #t (head sexp))
37 (self self marker fn #f (tail sexp))))
38 ;else
39 (prepend (self self marker fn #t (head sexp))
40 (self self marker fn #f (tail sexp)))))
41 (else
42 sexp)))
43 (cast-r cast-r (head args)
44 (fun (e) (eval env e))
45 #t
46 (head (tail args))))))
47 (subst-head (fun (src dest sexp)
48 (bind subst-head-r (fun (self src dest head-pos sexp)
49 (choose
50 ((empty? sexp)
51 ())
52 ((list? sexp)
53 (if head-pos
54 (if (equal? (head sexp) src)
55 (append dest (self self src dest #f (tail sexp)))
56 ;else
57 (prepend (self self src dest #t (head sexp))
58 (self self src dest #f (tail sexp))))
59 ;else
60 (prepend (self self src dest #t (head sexp))
61 (self self src dest #f (tail sexp)))))
62 (else
63 sexp)))
64 (subst-head-r subst-head-r src dest #t sexp))))
65 )
66 (list
67 (list (literal subst) subst)
68 (list (literal subst-many) subst-many)
69 (list (literal literal-with) literal-with)
70 (list (literal cast) cast)
71 (list (literal subst-head) subst-head)
72 )
73 )
74 )
0 > module Robin.Env where
1
2 > import Robin.Expr
3
4 Environments
5 ============
6
7 An environment is an alist which associates symbols with
8 values (arbitrary S-expressions).
9
10 > empty = List []
11
12 > insert s@(Symbol _) value env =
13 > append (List [List [s, value]]) env
14
15 > find s@(Symbol _) (List []) = Nothing
16 > find s@(Symbol _) (List (List [first, value]:rest))
17 > | s == first = Just value
18 > | otherwise = find s (List rest)
19
20 > fromList [] =
21 > List []
22 > fromList ((id, val):xs) =
23 > append (List [List [(Symbol id), val]]) (fromList xs)
0 > module Robin.Eval where
1
2 > import qualified Robin.Env as Env
3 > import Robin.Expr
4
5 Evaluator
6 =========
7
8 This is written in continuation-passing style.
9
10 Every evaluation function is (and takes) a continuation, which is implemented
11 as a function with signature:
12
13 Expr -> Expr -> Expr -> (Expr -> IO Expr) -> IO Expr
14
15 (This is actually the `Intrinsic` type from `Robin.Expr`.)
16
17 The first argument is the internal context, which contains things like the
18 exception handler, etc.
19
20 The second argument is the Robin environment, which is directly visible
21 (and modifiable, during `eval`) by the Robin program.
22
23 When evaluating a symbol, look it up in the environment to obtain a
24 value. Then continue the current continuation with that value.
25
26 > eval :: Intrinsic
27
28 > eval i (List []) s@(Symbol _) cc =
29 > raise i (errMsg "unbound-identifier" s)
30 > eval i (List (b@(List [id@(Symbol _), value]):env)) s@(Symbol _) cc
31 > | id == s = cc value
32 > | otherwise = eval i (List env) s cc
33 > eval i (List ((List (other:_)):env)) s@(Symbol _) cc =
34 > raise i (errMsg "expected-symbol" other)
35 > eval i (List (head:tail)) s@(Symbol _) cc =
36 > raise i (errMsg "expected-env-entry" head)
37 > eval i env s@(Symbol _) cc =
38 > raise i (errMsg "expected-env-alist" env)
39
40 Evaluating a list means we must make several evaluations. We
41 evaluate the head to obtain something to apply (which must be a
42 macro or intrinsic.) We then apply the body of the macro,
43 passing it the tail of the list.
44
45 > eval i env (List (applierExpr:actuals)) cc = do
46 > eval i env applierExpr (\applier ->
47 > case applier of
48 > m@(Macro _ _ body) -> do
49 > eval i (makeMacroEnv env (List actuals) m) body cc
50 > b@(Intrinsic _ fun) -> do
51 > fun i env (List actuals) cc
52 > other ->
53 > raise i (errMsg "inapplicable-object" other))
54
55 Everything else just evaluates to itself. Continue the current
56 continuation with that value.
57
58 > eval i env e cc = do
59 > cc e
60
61 Helper functions
62 ----------------
63
64 > errMsg msg term =
65 > List [(Symbol msg), term]
66
67 > makeMacroEnv env actuals m@(Macro closedEnv argList _) =
68 > let
69 > (List [argSelf@(Symbol _), argFormal@(Symbol _),
70 > envFormal@(Symbol _)]) = argList
71 > newEnv = Env.insert argSelf m closedEnv
72 > newEnv' = Env.insert argFormal actuals newEnv
73 > newEnv'' = Env.insert envFormal env newEnv'
74 > in
75 > newEnv''
76
77 Exception Handler
78 -----------------
79
80 > raise :: IEnv Expr -> Expr -> IO Expr
81 > raise i expr =
82 > (getExceptionHandler i) expr
83
84 Assertions
85 ----------
86
87 > assert i pred msg expr cc =
88 > case pred expr of
89 > True -> cc expr
90 > False -> raise i (errMsg msg expr)
91
92 > assertSymbol i = assert i (isSymbol) "expected-symbol"
93 > assertBoolean i = assert i (isBoolean) "expected-boolean"
94 > assertList i = assert i (isList) "expected-list"
95 > assertNumber i = assert i (isNumber) "expected-number"
96 > assertMacro i = assert i (isMacro) "expected-macro"
0 > module Robin.Expr where
1
2 > import Data.Char
3 > import Data.Int
4
5 Definitions
6 ===========
7
8 An _intrinsic_ is an object which behaves much like a macro, but is implemented
9 intrinsically (it cannot be (non-meta-circularly) defined in Robin itself.)
10
11 > type Intrinsic = IEnv Expr -> Expr -> Expr -> (Expr -> IO Expr) -> IO Expr
12 > -- internal-env env args continuation result
13
14 > data Expr = Symbol String
15 > | Boolean Bool
16 > | Number Int32
17 > | Macro Expr Expr Expr
18 > | Intrinsic String Intrinsic
19 > | List [Expr]
20
21 > instance Eq Expr where
22 > (Symbol x) == (Symbol y) = x == y
23 > (Boolean x) == (Boolean y) = x == y
24 > (Number x) == (Number y) = x == y
25 > (Macro _ _ _) == (Macro _ _ _) = False
26 > (Intrinsic x _) == (Intrinsic y _) = x == y
27 > (List x) == (List y) = x == y
28 > _ == _ = False
29
30 > instance Show Expr where
31 > show (Symbol s) = s
32 > show (Boolean True) = "#t"
33 > show (Boolean False) = "#f"
34 > show (Number n) = show n
35 > show (Macro env args body) = ("(@macro " ++ (show args) ++
36 > " " ++ (show body) ++ ")")
37 > show (Intrinsic name _) = name
38 > show (List exprs) = "(" ++ (showl exprs) ++ ")"
39
40 > showl [] = ""
41 > showl [expr] = show expr
42 > showl (expr:exprs) = (show expr) ++ " " ++ (showl exprs)
43
44 Helpers
45 -------
46
47 > append (List x) (List y) =
48 > List (x ++ y)
49
50 Predicates
51 ----------
52
53 > isSymbol (Symbol _) = True
54 > isSymbol _ = False
55
56 > isBoolean (Boolean _) = True
57 > isBoolean _ = False
58
59 > isNumber (Number _) = True
60 > isNumber _ = False
61
62 > isList (List _) = True
63 > isList _ = False
64
65 > isMacro (Macro _ _ _) = True
66 > isMacro (Intrinsic _ _) = True
67 > isMacro _ = False
68
69 Internal Environments
70 =====================
71
72 This is the evaluation environment for Robin which is entirely
73 internal; Robin programs cannot see or modify it directly. Here
74 we keep things like the continuation which is the current exception
75 handler.
76
77 > data IEnv t = IEnv (t -> IO t)
78
79 > stop expr =
80 > error ("uncaught exception: " ++ show expr)
81
82 > getExceptionHandler (IEnv handler) = handler
83 > setExceptionHandler handler (IEnv _) = (IEnv handler)
0 > module Robin.Intrinsics where
1
2 > import qualified Robin.Env as Env
3 > import Robin.Expr
4 > import Robin.Eval
5
6 Intrinsics
7 ==========
8
9 > robinHead i env (List [expr]) cc = do
10 > eval i env expr (\x ->
11 > assertList i x (\val ->
12 > case val of
13 > List (a:_) -> cc a
14 > other -> raise i (errMsg "expected-list" other)))
15
16 > robinTail i env (List [expr]) cc = do
17 > eval i env expr (\x ->
18 > assertList i x (\val ->
19 > case val of
20 > List (_:b) -> cc (List b)
21 > other -> raise i (errMsg "expected-list" other)))
22
23 > robinPrepend i env (List [e1, e2]) cc = do
24 > eval i env e1 (\x1 -> eval i env e2 (\val ->
25 > case val of
26 > List x2 -> cc $ List (x1:x2)
27 > other -> raise i (errMsg "expected-list" other)))
28
29 > equalP i env (List [e1, e2]) cc = do
30 > eval i env e1 (\x1 -> eval i env e2 (\x2 -> cc $ Boolean (x1 == x2)))
31
32 > predP pred i env (List [expr]) cc = do
33 > eval i env expr (\x -> cc $ Boolean $ pred x)
34
35 > symbolP = predP isSymbol
36 > listP = predP isList
37 > macroP = predP isMacro
38 > numberP = predP isNumber
39
40 > robinSubtract i env (List [xexpr, yexpr]) cc = do
41 > eval i env xexpr (\x ->
42 > assertNumber i x (\(Number xv) ->
43 > eval i env yexpr (\y ->
44 > assertNumber i y (\(Number yv) ->
45 > cc (Number (xv - yv))))))
46
47 > robinSign i env (List [expr]) cc = do
48 > eval i env expr (\x ->
49 > assertNumber i x (\(Number xv) ->
50 > cc $ Number $ sign xv))
51
52 > sign x = if x == 0 then 0 else if x < 0 then -1 else 1
53
54 > robinIf i env (List [test, texpr, fexpr]) cc = do
55 > eval i env test (\x ->
56 > assertBoolean i x (\(Boolean b) ->
57 > case b of
58 > True -> eval i env texpr cc
59 > False -> eval i env fexpr cc))
60
61 > robinEval i env (List [envlist, form]) cc = do
62 > eval i env envlist (\newEnv ->
63 > eval i env form (\body -> do
64 > eval i newEnv body cc))
65
66 > robinMacro i env (List [args@(List [(Symbol selfS), (Symbol argsS), (Symbol envS)]), body]) cc = do
67 > cc $ Macro env args body
68
69 > robinRaise i env (List [expr]) cc =
70 > eval i env expr (\v -> raise i v)
71
72 > robinCatch i env (List [id@(Symbol _), handler, body]) cc =
73 > let
74 > handlerContinuation = (\errvalue ->
75 > eval i (Env.insert id errvalue env) handler cc)
76 > i' = setExceptionHandler handlerContinuation i
77 > in
78 > eval i' env body cc
79
80 > robinIntrinsics = Env.fromList $ map (\(name,bif) -> (name, Intrinsic name bif))
81 > [
82 > ("@head", robinHead),
83 > ("@tail", robinTail),
84 > ("@prepend", robinPrepend),
85 > ("@list?", listP),
86 > ("@symbol?", symbolP),
87 > ("@macro?", macroP),
88 > ("@number?", numberP),
89 > ("@equal?", equalP),
90 > ("@subtract", robinSubtract),
91 > ("@sign", robinSign),
92 > ("@macro", robinMacro),
93 > ("@eval", robinEval),
94 > ("@if", robinIf),
95 > ("@raise", robinRaise),
96 > ("@catch", robinCatch)
97 > ]
0 > module Robin.Parser (parseRobin, insistParse) where
1
2 > import Data.Char
3 > import Data.Int
4
5 > import Text.ParserCombinators.Parsec
6
7 > import Robin.Expr
8
9 Parser
10 ======
11
12 The overall grammar of the language is:
13
14 Expr ::= (symbol | number | boolean | "(" {Expr} ")")
15 Program ::= {Expr}
16
17 A symbol is denoted by a string which may contain only alphanumeric
18 characters and certain other characters.
19
20 (TODO: this set of characters is provisional. It might be easier to specify
21 which characters are *not* allowed.)
22
23 > legalSymbolic = (char '*' <|> char '-' <|> char '/' <|>
24 > char '+' <|> char '<' <|> char '>' <|>
25 > char '<' <|> char '=' <|> char '?' <|>
26 > char '_' <|> char '!' <|> char '$' <|>
27 > char ':' <|> char '@')
28
29 > symbol = do
30 > c <- (letter <|> legalSymbolic)
31 > cs <- many (alphaNum <|> legalSymbolic)
32 > return (Symbol (c:cs))
33
34 TODO: document these productions.
35
36 > number = do
37 > c <- digit
38 > cs <- many digit
39 > num <- return (read (c:cs) :: Int32)
40 > return (Number num)
41
42 > boolean = do
43 > string "#"
44 > c <- (char 't' <|> char 'f')
45 > return (if c == 't' then (Boolean True) else (Boolean False))
46
47 > list = do
48 > string "("
49 > spaces
50 > many comment
51 > e <- many expr
52 > string ")"
53 > return $ List e
54
55 > stringSugar = do
56 > string "'"
57 > sentinel <- many $ satisfy (\x -> x /= '\'')
58 > string "'"
59 > contents <- many $ satisfy (\x -> x /= '\'')
60 > string "'"
61 > (try $ stringTail sentinel contents) <|> (stringCont sentinel contents)
62
63 > stringCont sentinel contents = do
64 > contents' <- many $ satisfy (\x -> x /= '\'')
65 > let contents'' = contents ++ "'" ++ contents'
66 > string "'"
67 > (try $ stringTail sentinel contents'') <|> (stringCont sentinel contents'')
68
69 > stringTail sentinel contents = do
70 > string sentinel
71 > string "'"
72 > return $ List (map charToNum contents)
73 > where
74 > charToNum x = Number (fromIntegral $ ord x)
75
76 > comment = do
77 > string ";"
78 > spaces
79 > expr
80
81 The top-level parsing function implements the overall grammar given above.
82 Note that we need to give the type of this parser here -- otherwise the
83 type inferencer freaks out for some reason.
84
85 > expr :: Parser Expr
86 > expr = do
87 > r <- (symbol <|> number <|> boolean <|> list <|> stringSugar)
88 > spaces
89 > many comment
90 > return r
91
92 > robinProgram = do
93 > spaces
94 > many comment
95 > e <- many expr
96 > return $ e
97
98 Convenience functions for parsing Robin programs.
99
100 > parseRobin = parse robinProgram ""
101
102 > insistParse programText =
103 > let
104 > Right ast = parseRobin programText
105 > in
106 > ast
0 > module Robin.Reactor where
1
2 > import qualified Data.Char as Char
3
4 > import System.IO
5
6 > import Robin.Expr
7 > import qualified Robin.Env as Env
8 > import Robin.Eval
9
10 > data Reactor = Reactor Expr Expr Expr
11 > deriving (Show, Eq)
12 > -- env state body
13 > -- body takes three arguments: event payload state
14
15 > initReactors :: [Reactor] -> IO [Reactor]
16 > initReactors reactors = do
17 > reactors'' <- handleMany reactors (Symbol "init") (Number 0)
18 > return reactors''
19
20 > eventLoop [] = return ()
21 > eventLoop reactors = do
22 > stillOpen <- hIsOpen stdin
23 > case stillOpen of
24 > True -> do
25 > eof <- hIsEOF stdin
26 > case eof of
27 > False -> cromulentEvent reactors
28 > True -> closeUpShop reactors
29 > False -> closeUpShop reactors
30
31 > cromulentEvent reactors = do
32 > inpStr <- getLine
33 > let payload = List (map (\x -> Number (fromIntegral $ Char.ord x)) inpStr)
34 > reactors' <- handleMany reactors (Symbol "readln") payload
35 > eventLoop reactors'
36
37 > closeUpShop reactors = do
38 > reactors' <- handleMany reactors (Symbol "eof") (Number 0)
39 > return ()
40
41 > handleMany [] event payload = return []
42 > handleMany (reactor@(Reactor env state body):reactors) event payload = do
43 > --print env
44 > --print body
45 > --print event
46 > --print payload
47 > retval <- eval (IEnv stop) env (List [body, event, payload, state]) (\x -> do return x)
48 > maybeNewState <- handleRetVal retval state
49 > rest <- handleMany reactors event payload
50 > case maybeNewState of
51 > Just state' -> do
52 > return (Reactor env state' body:rest)
53 > Nothing ->
54 > return rest
55
56 Returns Just the new state, or Nothing if the reactor bowed out.
57
58 > handleRetVal retval state =
59 > case retval of
60 > (List (state':responses)) -> do
61 > handleResponses state' responses
62 > _ -> do
63 > return (Just state)
64
65 Takes the state mainly so it can return Just state on success and Nothing if the reactor bowed out.
66 Also, after a close, it does not handle any more responses. The reactor bowed out, after all.
67
68 > handleResponses state [] = return (Just state)
69 > handleResponses state (List [Symbol "writeln", payload]:responses) = do
70 > let List l = payload
71 > let s = map (\(Number x) -> Char.chr $ fromIntegral $ x) l
72 > hPutStrLn stdout s
73 > handleResponses state responses
74 > handleResponses state (List [Symbol "close", payload]:responses) = do
75 > return Nothing
76 > handleResponses state (response:responses) = do
77 > hPutStrLn stderr ("malformed response " ++ show response)
78 > handleResponses state responses
0 > module Robin.TopLevel where
1
2 > import Robin.Expr
3 > import qualified Robin.Env as Env
4 > import Robin.Eval
5 > import Robin.Reactor
6
7 Top-Level S-Expressions
8 -----------------------
9
10 > execTopExprs env reactors [] = return (env, reactors)
11
12 > execTopExprs env reactors ((List [Symbol "display", expr]):rest) = do
13 > result <- eval (IEnv stop) env expr (\x -> do return x)
14 > putStrLn $ show result
15 > execTopExprs env reactors rest
16
17 > execTopExprs env reactors ((List [Symbol "define", name@(Symbol _), expr]):rest) = do
18 > case Env.find name env of
19 > Just _ -> do
20 > error ("symbol already defined: " ++ show name)
21 > Nothing -> do
22 > result <- eval (IEnv stop) env expr (\x -> do return x)
23 > execTopExprs (Env.insert name result env) reactors rest
24
25 > execTopExprs env reactors ((List [Symbol "reactor", facExpr, stateExpr, bodyExpr]):rest) = do
26 > state <- eval (IEnv stop) env stateExpr (\x -> do return x)
27 > body <- eval (IEnv stop) env bodyExpr (\x -> do return x)
28 > execTopExprs env ((Reactor env state body):reactors) rest
29
30 > execTopExprs env reactors (topExpr:rest) = do
31 > error ("illegal top-level form: " ++ show topExpr)
0 > module Whitecap.Builtins where
1
2 > import qualified Robin.Env as Env
3 > import Robin.Expr
4 > import Robin.Eval
5
6 Whitecap Builtins
7 =================
8
9 Not part of the reference interpreter!
10
11 > robinHead i env (List [expr]) cc = do
12 > eval i env expr (\x ->
13 > assertList i x (\val ->
14 > case val of
15 > List (a:_) -> cc a
16 > other -> raise i (errMsg "expected-list" other)))
17 > robinHead i env other cc = raise i (errMsg "illegal-arguments" other)
18
19 > robinTail i env (List [expr]) cc = do
20 > eval i env expr (\x ->
21 > assertList i x (\val ->
22 > case val of
23 > List (_:b) -> cc (List b)
24 > other -> raise i (errMsg "expected-list" other)))
25 > robinTail i env other cc = raise i (errMsg "illegal-arguments" other)
26
27 > robinPrepend i env (List [e1, e2]) cc = do
28 > eval i env e1 (\x1 -> eval i env e2 (\val ->
29 > case val of
30 > List x2 -> cc $ List (x1:x2)
31 > other -> raise i (errMsg "expected-list" other)))
32 > robinPrepend i env other cc = raise i (errMsg "illegal-arguments" other)
33
34 > equalP i env (List [e1, e2]) cc = do
35 > eval i env e1 (\x1 -> eval i env e2 (\x2 -> cc $ Boolean (x1 == x2)))
36 > equalP i env other cc = raise i (errMsg "illegal-arguments" other)
37
38 > predP pred i env (List [expr]) cc = do
39 > eval i env expr (\x -> cc $ Boolean $ pred x)
40 > predP pred i env other cc = raise i (errMsg "illegal-arguments" other)
41
42 > symbolP = predP isSymbol
43 > listP = predP isList
44 > macroP = predP isMacro
45 > numberP = predP isNumber
46
47 > robinSubtract i env (List [xexpr, yexpr]) cc = do
48 > eval i env xexpr (\x ->
49 > assertNumber i x (\(Number xv) ->
50 > eval i env yexpr (\y ->
51 > assertNumber i y (\(Number yv) ->
52 > cc (Number (xv - yv))))))
53 > robinSubtract i env other cc = raise i (errMsg "illegal-arguments" other)
54
55 > robinSign i env (List [expr]) cc = do
56 > eval i env expr (\x ->
57 > assertNumber i x (\(Number xv) ->
58 > cc $ Number $ sign xv))
59 > robinSign i env other cc = raise i (errMsg "illegal-arguments" other)
60
61 > sign x = if x == 0 then 0 else if x < 0 then -1 else 1
62
63 > robinIf i env (List [test, texpr, fexpr]) cc = do
64 > eval i env test (\x ->
65 > assertBoolean i x (\(Boolean b) ->
66 > case b of
67 > True -> eval i env texpr cc
68 > False -> eval i env fexpr cc))
69 > robinIf i env other cc = raise i (errMsg "illegal-arguments" other)
70
71 > robinEval i env (List [envlist, form]) cc = do
72 > eval i env envlist (\newEnv ->
73 > eval i env form (\body -> do
74 > eval i newEnv body cc))
75 > robinEval i env other cc = raise i (errMsg "illegal-arguments" other)
76
77 > robinMacro i env (List [args@(List [(Symbol selfS), (Symbol argsS), (Symbol envS)]), body]) cc = do
78 > cc $ Macro env args body
79 > robinMacro i env other cc = raise i (errMsg "illegal-arguments" other)
80
81 > robinRaise i env (List [expr]) cc =
82 > eval i env expr (\v -> raise i v)
83 > robinRaise i env other cc = raise i (errMsg "illegal-arguments" other)
84
85 > robinCatch i env (List [id@(Symbol _), handler, body]) cc =
86 > let
87 > handlerContinuation = (\errvalue ->
88 > eval i (Env.insert id errvalue env) handler cc)
89 > i' = setExceptionHandler handlerContinuation i
90 > in
91 > eval i' env body cc
92 > robinCatch i env other cc = raise i (errMsg "illegal-arguments" other)
93
94 SMALL...
95
96 This implementation of the `small` package is non-normative.
97 See the relevant files in `stdlib` for normative definitions.
98
99 > union (List []) env = env
100 > union (List (binding:rest)) env =
101 > append (List [binding]) (union (List rest) env)
102
103 > literal i env (List (expr:_)) cc =
104 > cc expr
105 > literal i env other cc = raise i (errMsg "illegal-arguments" other)
106
107 > evalAll i env [] acc cc =
108 > cc $ List $ reverse acc
109 > evalAll i env (head:tail) acc cc =
110 > eval i env head (\value ->
111 > evalAll i env tail (value:acc) cc)
112
113 > robinList i env (List exprs) cc =
114 > evalAll i env exprs [] cc
115
116 > robinEnv i env (List _) cc =
117 > cc env
118
119 > choose i env (List [(List [(Symbol "else"), branch])]) cc =
120 > eval i env branch cc
121 > choose i env (List ((List [test, branch]):rest)) cc = do
122 > eval i env test (\x ->
123 > case x of
124 > Boolean True ->
125 > eval i env branch cc
126 > Boolean False ->
127 > choose i env (List rest) cc)
128 > choose i env other cc = raise i (errMsg "illegal-arguments" other)
129
130 > bind i env (List [name@(Symbol _), expr, body]) cc =
131 > eval i env expr (\value ->
132 > eval i (Env.insert name value env) body cc)
133 > bind i env other cc = raise i (errMsg "illegal-arguments" other)
134
135 > robinLet i env (List ((List bindings):body:_)) cc =
136 > bindAll bindings env i (\env' ->
137 > eval i env' body cc)
138 > where
139 > bindAll [] env ienv cc =
140 > cc env
141 > bindAll (List (name@(Symbol _):sexpr:_):rest) env ienv cc =
142 > eval ienv env sexpr (\value ->
143 > bindAll rest (Env.insert name value env) ienv cc)
144 > bindAll (other:rest) env ienv cc =
145 > raise ienv (errMsg "illegal-binding" other)
146 > robinLet i env other cc = raise i (errMsg "illegal-arguments" other)
147
148 > -- formals actuals origActuals env i cc
149 > evalArgs [] [] _ _ _ cc = do
150 > cc Env.empty
151 > evalArgs (formal@(Symbol _):formals) (actual:actuals) origActuals env i cc = do
152 > eval i env actual (\value ->
153 > evalArgs formals actuals origActuals env i (\rest ->
154 > cc $ Env.insert formal value rest))
155 > evalArgs _ _ origActuals _ i cc = do
156 > raise i (errMsg "illegal-arguments" (List origActuals))
157
158 > robinBindArgs i env (List [(List formals), givenArgs, givenEnv, body]) cc = do
159 > eval i env givenArgs (\(List actuals) ->
160 > eval i env givenEnv (\outerEnv ->
161 > evalArgs formals actuals actuals outerEnv i (\argEnv ->
162 > eval i (union argEnv env) body cc)))
163 > robinBindArgs i env other cc = raise i (errMsg "illegal-arguments" other)
164
165 WHATEVER...
166
167 > robinFun i closedEnv (List [(List formals), body]) cc = do
168 > cc $ Intrinsic "<lambda>" fun
169 > where
170 > fun i env (List actuals) cc = do
171 > evalArgs formals actuals actuals env i (\argEnv ->
172 > eval i (union argEnv closedEnv) body cc)
173 > evalArgs [] [] _ _ _ cc = do
174 > cc Env.empty
175 > evalArgs (formal@(Symbol _):formals) (actual:actuals) origActuals env i cc = do
176 > eval i env actual (\value ->
177 > evalArgs formals actuals origActuals env i (\rest ->
178 > cc $ Env.insert formal value rest))
179 > evalArgs _ _ origActuals _ i cc = do
180 > raise i (errMsg "illegal-arguments" (List origActuals))
181 > robinFun i env other cc = raise i (errMsg "illegal-arguments" other)
182
183 > booleanP = predP isBoolean
184
185 ...
186 THE TABLE
187 ...
188
189 > whitecapBuiltins = Env.fromList $ map (\(name,bif) -> (name, Intrinsic name bif))
190 > [
191 > ("@head", robinHead),
192 > ("@tail", robinTail),
193 > ("@prepend", robinPrepend),
194 > ("@list?", listP),
195 > ("@symbol?", symbolP),
196 > ("@macro?", macroP),
197 > ("@number?", numberP),
198 > ("@equal?", equalP),
199 > ("@subtract", robinSubtract),
200 > ("@sign", robinSign),
201 > ("@macro", robinMacro),
202 > ("@eval", robinEval),
203 > ("@if", robinIf),
204 > ("@raise", robinRaise),
205 > ("@catch", robinCatch),
206
207 > ("literal", literal),
208 > ("list", robinList),
209 > ("bind", bind),
210 > ("env", robinEnv),
211 > ("let", robinLet),
212 > ("choose", choose),
213 > ("bind-args", robinBindArgs),
214 > --("boolean?", booleanP),
215 > ("fun", robinFun),
216
217 > ("head", robinHead),
218 > ("tail", robinTail),
219 > ("prepend", robinPrepend),
220 > ("list?", listP),
221 > ("symbol?", symbolP),
222 > ("macro?", macroP),
223 > ("number?", numberP),
224 > ("equal?", equalP),
225 > ("subtract", robinSubtract),
226 > ("sign", robinSign),
227 > ("macro", robinMacro),
228 > ("eval", robinEval),
229 > ("if", robinIf),
230 > ("raise", robinRaise),
231 > ("catch", robinCatch)
232 > ]
0 > module Main where
1
2 > import System.IO
3
4 > import System.Environment
5 > import System.Exit
6
7 > import Robin.Parser (parseRobin)
8 > import Robin.Intrinsics (robinIntrinsics)
9 > import Robin.TopLevel (execTopExprs)
10 > import Robin.Reactor (eventLoop, initReactors)
11
12 Command-line Entry Point
13 ------------------------
14
15 > main = do
16 > args <- getArgs
17 > case args of
18 > [] -> do
19 > putStrLn "Usage: robinri {source.robin}"
20 > exitWith $ ExitFailure 1
21 > _ -> do
22 > (env, reactors) <- processArgs robinIntrinsics [] args
23 > case reactors of
24 > [] ->
25 > exitWith ExitSuccess
26 > _ -> do
27 > reactors' <- initReactors reactors
28 > eventLoop reactors'
29
30 > processArgs env reactors [] = return (env, reactors)
31 > processArgs env reactors (filename:rest) = do
32 > program <- readFile filename
33 > case parseRobin program of
34 > Right topExprs -> do
35 > (env', reactors') <- execTopExprs env reactors topExprs
36 > processArgs env' reactors' rest
37 > Left problem -> do
38 > hPutStr stderr (show problem)
39 > exitWith $ ExitFailure 1
0 > module Main where
1
2 > import System.IO
3
4 > import System.Environment
5 > import System.Exit
6
7 > import Robin.Parser (parseRobin)
8 > import Robin.Intrinsics (robinIntrinsics)
9 > import Whitecap.Builtins (whitecapBuiltins, union)
10 > import Robin.TopLevel (execTopExprs)
11 > import Robin.Reactor (eventLoop, initReactors)
12
13 Command-line Entry Point
14 ------------------------
15
16 > main = do
17 > args <- getArgs
18 > case args of
19 > [] -> do
20 > putStrLn "Usage: whitecap [--no-builtins] {source.robin}"
21 > exitWith $ ExitFailure 1
22 > ("--no-builtins":rest) -> do
23 > (env, reactors) <- processArgs robinIntrinsics [] rest
24 > case reactors of
25 > [] ->
26 > exitWith ExitSuccess
27 > _ -> do
28 > reactors' <- initReactors reactors
29 > eventLoop reactors'
30 > _ -> do
31 > (env, reactors) <- processArgs whitecapBuiltins [] args
32 > case reactors of
33 > [] ->
34 > exitWith ExitSuccess
35 > _ -> do
36 > reactors' <- initReactors reactors
37 > eventLoop reactors'
38
39 > processArgs env reactors [] = return (env, reactors)
40 > processArgs env reactors (filename:rest) = do
41 > program <- readFile filename
42 > case parseRobin program of
43 > Right topExprs -> do
44 > (env', reactors') <- execTopExprs env reactors topExprs
45 > processArgs env' reactors' rest
46 > Left problem -> do
47 > hPutStr stderr (show problem)
48 > exitWith $ ExitFailure 1
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Arith)"
3
4 `abs` evaluates its single argument to a number, and evaluates to
5 the absolute value of that number (where the sign is always positive.)
6
7 | (display
8 | (abs 5))
9 = 5
10
11 | (display
12 | (abs (subtract 0 5)))
13 = 5
14
15 | (display
16 | (abs 0))
17 = 0
18
19 `abs` expects exactly one numeric argument.
20
21 | (display
22 | (abs))
23 ? uncaught exception: (illegal-arguments ())
24
25 | (display
26 | (abs 14 23))
27 ? uncaught exception: (illegal-arguments (14 23))
28
29 | (display
30 | (abs #t))
31 ? uncaught exception: (expected-number #t)
32
33 'XXX'
34
35 (define abs (macro (self args env)
36 (bind-args (a) args env
37 (if (equal? (sign a) 1) a (subtract 0 a)))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Arith)"
3
4 `add` evaluates both of its arguments to numbers and evaluates to the sum
5 of those two numbers.
6
7 | (display
8 | (add 14 23))
9 = 37
10
11 `add` expects exactly two arguments.
12
13 | (display
14 | (add 14))
15 ? uncaught exception: (illegal-arguments (14))
16
17 | (display
18 | (add 6 7 7))
19 ? uncaught exception: (illegal-arguments (6 7 7))
20
21 Both of the arguments to `add` must be numbers.
22
23 | (display
24 | (add 14 #t))
25 ? uncaught exception: (expected-number #t)
26
27 | (display
28 | (add #t 51))
29 ? uncaught exception: (expected-number #t)
30
31 'XXX'
32
33 (define add (macro (self args env)
34 (bind-args (a b) args env
35 (subtract a (subtract 0 b)))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Boolean)"
3
4 `and` evaluates both of its arguments to booleans, and evaluates to the
5 logical conjunction (boolean "and") of these two values.
6
7 | (display
8 | (and #t #t))
9 = #t
10
11 | (display
12 | (and #t #f))
13 = #f
14
15 | (display
16 | (and #f #t))
17 = #f
18
19 | (display
20 | (and #f #f))
21 = #f
22
23 `and` expects exactly two arguments.
24
25 (Hate to weaken this test, but I'm not a purist -- yet.)
26
27 | (display
28 | (and #f))
29 ? uncaught exception
30
31 | (display
32 | (and #t #f #f))
33 ? uncaught exception: (illegal-arguments (#t #f #f))
34
35 `and` expects both of its arguments to be booleans.
36
37 | (display
38 | (and 100 #t))
39 ? uncaught exception: (expected-boolean 100)
40
41 | (display
42 | (and #t 99))
43 ? uncaught exception: (expected-boolean 99)
44
45 `and` is short-circuiting in the sense that no arguments after the first
46 `#f` argument will be evaluated. Fully testing this requires side-effects,
47 but it can be demonstrated as follows.
48
49 | (display
50 | (and #f 100))
51 = #f
52
53 'XXX'
54
55 (define and (macro (self args env)
56 (if (equal? (tail (tail args)) ())
57 (if (eval env (head args))
58 (if (eval env (head (tail args))) #t #f)
59 #f)
60 (raise (list (literal illegal-arguments) args)))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `append` evaluates both of its arguments to lists. It then
5 evaluates to a list which is the concatenation of these lists.
6
7 | (display
8 | (append (list 1 2 3) (list 4 5 6)))
9 = (1 2 3 4 5 6)
10
11 | (display
12 | (append () ()))
13 = ()
14
15 'XXX'
16
17 (define append (fun (li new-tail)
18 (bind append-r (fun (self li new-tail)
19 (if (empty? li)
20 new-tail
21 (prepend (head li) (self self (tail li) new-tail))))
22 (append-r append-r li new-tail))))
0 (define bind-args
1 (@macro (self args env)
2 (let (
3 (id-list (@head args))
4 (orig-val-list (@eval env (@head (@tail args))))
5 (given-env (@eval env (@head (@tail (@tail args)))))
6 (expr (@head (@tail (@tail (@tail args)))))
7 (bind-args-r (@macro (self args env)
8 (let (
9 (id-list (@eval env (@head args)))
10 (val-list (@eval env (@head (@tail args))))
11 (env-acc (@eval env (@head (@tail (@tail args)))))
12 )
13 (@if (@equal? id-list ())
14 (@if (@equal? val-list ())
15 env-acc
16 (@raise (list (literal illegal-arguments) orig-val-list)))
17 (@if (@equal? val-list ())
18 (@raise (list (literal illegal-arguments) orig-val-list))
19 (self
20 (@tail id-list) (@tail val-list)
21 (@prepend
22 (list (@head id-list) (@eval given-env (@head val-list)))
23 env-acc)))))))
24 (new-env (bind-args-r id-list orig-val-list env)))
25 (@eval new-env expr))))
26
27 ;'XXX'
28
29 -> Tests for functionality "Interpret Robin Program (with Small)"
30
31 `bind-args` is a macro for binding the arguments of another value to
32 identifiers, as well as asserting that the correct number of arguments
33 have been given to the macro.
34
35 `bind-args` takes a literal list of identifiers, and expresion which
36 evaluates to a literal list of expressions whose values are to be bound
37 to those identifiers, an expresion which evaluates to the environment in
38 which those expressions will be evaluated, and an expression to evaluate
39 in the new environment in which the identifiers are bound.
40
41 | (display
42 | (bind-args (a b) (literal (1 2)) (env)
43 | (list a b)))
44 = (1 2)
45
46 Expressions in the list of values are evaluated.
47
48 | (display
49 | (bind-args (a b) (literal ((subtract 5 4) (subtract 10 1))) (env)
50 | (list a b)))
51 = (1 9)
52
53 Too many or too few arguments will raise an `illegal-arguments`
54 exception.
55
56 | (display
57 | (bind-args (a b) (literal (1)) (env)
58 | (list a b)))
59 ? uncaught exception: (illegal-arguments (1))
60
61 | (display
62 | (bind-args (a b) (literal (1 2 3)) (env)
63 | (list a b)))
64 ? uncaught exception: (illegal-arguments (1 2 3))
65
66 The literal arguments are reported in the exception.
67
68 | (display
69 | (bind-args (a) (literal ((subtract 5 4) (subtract 1 0))) (env)
70 | a))
71 ? uncaught exception: (illegal-arguments ((subtract 5 4) (subtract 1 0)))
72
73 This is how it might be used in a macro definition. The reason for the
74 seemingly strange requirements of the second and third arguments should
75 become clear here: typically you would just pass the macro's `args` and
76 `env` to those arguments.
77
78 | (display
79 | (bind add (@macro (self args env)
80 | (bind-args (a b) args env
81 | (subtract a (subtract 0 b))))
82 | (add 4 (add 5 6))))
83 = 15
84
85 | (display
86 | (bind add (@macro (self args env)
87 | (bind-args (a b) args env
88 | (subtract a (subtract 0 b))))
89 | (bind r 7
90 | (add r r))))
91 = 14
92
93 | (display
94 | (bind add (@macro (self args env)
95 | (bind-args (a b) args env
96 | (subtract a (subtract 0 b))))
97 | (add (subtract 0 0))))
98 ? uncaught exception: (illegal-arguments ((subtract 0 0)))
99
100 | (display
101 | (bind add (@macro (self args env)
102 | (bind-args (a b) args env
103 | (subtract a (subtract 0 b))))
104 | (add 9 9 9)))
105 ? uncaught exception: (illegal-arguments (9 9 9))
106
107 | (display
108 | (bind add (@macro (self args env)
109 | (bind-args (a b) args env
110 | (subtract a (subtract 0 b))))
111 | (add 1 n)))
112 ? uncaught exception: (unbound-identifier n)
113
114 'XXX'
0 (define bind (@macro (self args env)
1 (@eval
2 (@prepend
3 (@prepend (@head args) (@prepend (@eval env (@head (@tail args)))
4 ())) env)
5 (@head (@tail (@tail args))))))
6
7 ;'XXX'
8
9 -> Tests for functionality "Interpret Robin Program (with Small)"
10
11 `bind` binds a single identifier to the result of evaluating a single
12 expression, and makes that binding available in another expression which
13 it evaluates.
14
15 | (display
16 | (bind x (literal hello)
17 | (list x x)))
18 = (hello hello)
19
20 | (display
21 | (bind dup (@macro (self args env)
22 | (list (@head args) (@head args)))
23 | (dup g)))
24 = (g g)
25
26 | (display
27 | (bind dup (@macro (self args env)
28 | (bind x (@eval env (@head args))
29 | (list x x)))
30 | (dup (literal g))))
31 = (g g)
32
33 | (display
34 | (bind dup (@macro (self args env)
35 | (bind x (@eval env (@head args))
36 | (list x x)))
37 | (dup (dup (literal g)))))
38 = ((g g) (g g))
39
40 | (display
41 | (bind find (@macro (self args env)
42 | (bind-args (alist key) args env
43 | (@if (@equal? alist (literal ())) (literal ())
44 | (@if (@equal? key (@head (@head alist)))
45 | (@head alist)
46 | (self (@tail alist) key)))))
47 | (find (literal ((c d) (e f) (a b))) (literal a))))
48 = (a b)
49
50 `bind` expects exactly three arguments, or else an exception will be raised.
51
52 | (display
53 | (bind smoosh (fun (x y) (list y x))))
54 ? uncaught exception
55
56 | (display
57 | (bind smoosh))
58 ? uncaught exception
59
60 | (display
61 | (bind))
62 ? uncaught exception
63
64 `bind` is basically equivalent to Scheme's `let`, but only one
65 binding may be given.
66
67 'XXX'
0 (define boolean? (@macro (self args env)
1 (bind-args (b) args env
2 (@if (@equal? b #t)
3 #t
4 (@if (@equal? b #f)
5 #t
6 #f)))))
7
8 ;'XXX'
9
10 -> Tests for functionality "Interpret Robin Program (with Boolean)"
11
12 `boolean?` evaluates its argument, then evaluates to `#t` if it is a
13 boolean value, `#f` otherwise.
14
15 | (display
16 | (boolean? #t))
17 = #t
18
19 | (display
20 | (boolean? (@head (@prepend #f ()))))
21 = #t
22
23 | (display
24 | (boolean? ()))
25 = #f
26
27 The argument to `boolean?` may (naturally) be any type, but there must be
28 exactly one argument.
29
30 | (display
31 | (boolean? #t #f))
32 ? uncaught exception: (illegal-arguments (#t #f))
33
34 | (display
35 | (boolean?))
36 ? uncaught exception: (illegal-arguments ())
37
38 'XXX'
0 (define catch (@macro (self args macro-env)
1 (choose
2 ((@equal? args ())
3 (@raise (list (literal illegal-arguments) args)))
4 ((@equal? (@tail args) ())
5 (@raise (list (literal illegal-arguments) args)))
6 ((@equal? (@tail (@tail args)) ())
7 (@raise (list (literal illegal-arguments) args)))
8 ((@equal? (@tail (@tail (@tail args))) ())
9 (@if (symbol? (@head args))
10 (@eval (env) (list (literal @catch)
11 (@head args)
12 (@head (@tail args))
13 (@head (@tail (@tail args)))))
14 (@raise (list (literal illegal-arguments) args))))
15 (else
16 (@raise (list (literal illegal-arguments) args))))))
17
18 ;'XXX'
19
20 -> Tests for functionality "Interpret Robin Program (with Small)"
21
22 `catch` is a wrapper for the `@catch` intrinsic, for which it provides
23 predictable failure modes. In non-failure modes, `catch` should have
24 semantics identical to `@catch`.
25
26 `catch` expects its first argument to be a symbol.
27
28 | (display
29 | (catch #f 23 (head #f)))
30 ? uncaught exception: (illegal-arguments (#f 23 (head #f)))
31
32 `catch` expects exactly three arguments.
33
34 | (display
35 | (catch error error))
36 ? uncaught exception: (illegal-arguments (error error))
37
38 | (display
39 | (catch error error (head #f) 23))
40 ? uncaught exception: (illegal-arguments (error error (head #f) 23))
41
42 `catch` can catch exceptions raised by builtin wrappers.
43
44 | (display
45 | (catch error (list error 5)
46 | (head #f)))
47 = ((expected-list #f) 5)
48
49 'XXX'
0 (define choose (@macro (self args env)
1 (bind branch (@head args)
2 (bind test (@head branch)
3 (bind then (@head (@tail branch))
4 (@if (@equal? test (literal else))
5 (@eval env then)
6 (@if (@eval env test)
7 (@eval env then)
8 (@eval env (@prepend self (@tail args))))))))))
9
10 ;'XXX'
11
12 -> Tests for functionality "Interpret Robin Program (with Small)"
13
14 | (display
15 | (choose (#t (literal hi)) (else (literal lo))))
16 = hi
17
18 | (display
19 | (choose (#f (literal hi)) (#t (literal med)) (else (literal lo))))
20 = med
21
22 | (display
23 | (choose (#f (literal hi)) (#f (literal med)) (else (literal lo))))
24 = lo
25
26 `choose` can have zero tests before the `else`.
27
28 | (display
29 | (choose (else (literal woo))))
30 = woo
31
32 `choose` does require an `else` branch, or else an exception will be
33 raised.
34
35 | (display
36 | (choose (#f (literal hi)) (#f (literal med))))
37 ? uncaught exception
38
39 | (display
40 | (choose))
41 ? uncaught exception
42
43 Each branch of a `choose` needs to be a two-element list, or else an
44 exception will be raised.
45
46 | (display
47 | (choose (#t) (else (literal lo))))
48 ? uncaught exception
49
50 | (display
51 | (choose (#f 66) (else)))
52 ? uncaught exception
53
54 `choose` is basically equivalent to Scheme's `cond`.
55
56 'XXX'
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Arith)"
3
4 ### `>` ###
5
6 `>` evaluates both of its arguments to numbers, then evaluates to `#t`
7 if the first number is strictly greater than the second.
8
9 | (display
10 | (> 6 4))
11 = #t
12
13 | (display
14 | (> 6 8))
15 = #f
16
17 | (display
18 | (> 6 6))
19 = #f
20
21 `>` expects exactly two arguments, both numbers.
22
23 | (display
24 | (> 14))
25 ? uncaught exception: (illegal-arguments (14))
26
27 | (display
28 | (> 14 23 57))
29 ? uncaught exception: (illegal-arguments (14 23 57))
30
31 | (display
32 | (> 14 #t))
33 ? uncaught exception: (expected-number #t)
34
35 | (display
36 | (> #t 51))
37 ? uncaught exception: (expected-number #t)
38
39 ### `<` ###
40
41 `<` evaluates both of its arguments to numbers, then evaluates to `#t`
42 if the first number is strictly less than the second.
43
44 | (display
45 | (< 6 4))
46 = #f
47
48 | (display
49 | (< 6 8))
50 = #t
51
52 | (display
53 | (< 6 6))
54 = #f
55
56 `<` expects exactly two arguments, both numbers.
57
58 | (display
59 | (< 14))
60 ? uncaught exception: (illegal-arguments (14))
61
62 | (display
63 | (< 14 23 57))
64 ? uncaught exception: (illegal-arguments (14 23 57))
65
66 | (display
67 | (< 14 #t))
68 ? uncaught exception: (expected-number #t)
69
70 | (display
71 | (< #t 51))
72 ? uncaught exception: (expected-number #t)
73
74 ### `>=` ###
75
76 `>=` evaluates both of its arguments to numbers, then evaluates to `#t`
77 if the first number is greater than or equal to the second.
78
79 | (display
80 | (>= 6 4))
81 = #t
82
83 | (display
84 | (>= 6 8))
85 = #f
86
87 | (display
88 | (>= 6 6))
89 = #t
90
91 `>=` expects exactly two arguments, both numbers.
92
93 | (display
94 | (>= 14))
95 ? uncaught exception: (illegal-arguments (14))
96
97 | (display
98 | (>= 14 23 57))
99 ? uncaught exception: (illegal-arguments (14 23 57))
100
101 | (display
102 | (>= 14 #t))
103 ? uncaught exception: (expected-number #t)
104
105 | (display
106 | (>= #t 51))
107 ? uncaught exception: (expected-number #t)
108
109 ### `<=` ###
110
111 `<=` evaluates both of its arguments to numbers, then evaluates to `#t`
112 if the first number is less than or equal to the second.
113
114 | (display
115 | (<= 6 4))
116 = #f
117
118 | (display
119 | (<= 6 8))
120 = #t
121
122 | (display
123 | (<= 6 6))
124 = #t
125
126 `<=` expects exactly two arguments, both numbers.
127
128 | (display
129 | (<= 14))
130 ? uncaught exception: (illegal-arguments (14))
131
132 | (display
133 | (<= 14 23 57))
134 ? uncaught exception: (illegal-arguments (14 23 57))
135
136 | (display
137 | (<= 14 #t))
138 ? uncaught exception: (expected-number #t)
139
140 | (display
141 | (<= #t 51))
142 ? uncaught exception: (expected-number #t)
143
144 'XXX'
145
146 (define > (macro (self args env)
147 (bind-args (a b) args env
148 (equal? (sign (subtract a b)) 1))))
149 (define >= (macro (self args env)
150 (bind-args (a b) args env
151 (if (equal? a b) #t (equal? (sign (subtract a b)) 1)))))
152 (define < (macro (self args env)
153 (bind-args (a b) args env
154 (equal? (sign (subtract a b)) (subtract 0 1)))))
155 (define <= (macro (self args env)
156 (bind-args (a b) args env
157 (if (equal? a b) #t (equal? (sign (subtract a b)) (subtract 0 1))))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 | (display
5 | (delete (literal b) (literal ((a 1) (b 2) (c 3)))))
6 = ((a 1) (c 3))
7
8 | (display
9 | (delete (literal b) (literal ((a 1) (b 2) (c 3) (b 4)))))
10 = ((a 1) (c 3))
11
12 | (display
13 | (delete (literal r) (literal ((a 1) (b 2) (c 3)))))
14 = ((a 1) (b 2) (c 3))
15
16 The following should be true for any identifier i and alist x.
17
18 | (display
19 | (let ((i (literal a))
20 | (x (literal ((a 5) (b 7)))))
21 | (lookup i (delete i x))))
22 = ()
23
24 | (display
25 | (delete (literal q) 55))
26 ? uncaught exception: (expected-list 55)
27
28 | (display
29 | (delete (literal q) (literal ((a 7) 99 (q 4)))))
30 ? uncaught exception: (expected-list 99)
31
32 'XXX'
33
34 (define delete (fun (id alist)
35 (filter (fun (x) (if (equal? (head x) id) #f #t)) alist)))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Arith)"
3
4 `divide` evaluates both of its arguments to numbers and evaluates to the
5 result of integer division of the first number by the second. Integer
6 division computes by what integer the second number can be multiplied
7 to make it as big as possible without exceeding the first number.
8
9 | (display
10 | (divide 100 3))
11 = 33
12
13 | (display
14 | (divide (subtract 0 100) 3))
15 = -34
16
17 | (display
18 | (divide 100 (subtract 0 3)))
19 = -34
20
21 | (display
22 | (divide 33 33))
23 = 1
24
25 | (display
26 | (divide 33 34))
27 = 0
28
29 | (display
30 | (divide 10 0))
31 ? uncaught exception: (division-by-zero 10)
32
33 Division by zero is undefined, and an exception will be raised.
34
35 | (display
36 | (divide 10 0))
37 ? uncaught exception: (division-by-zero 10)
38
39 `div` expects exactly two arguments, both numbers.
40
41 | (display
42 | (divide 14))
43 ? uncaught exception: (illegal-arguments (14))
44
45 | (display
46 | (divide 14 23 57))
47 ? uncaught exception: (illegal-arguments (14 23 57))
48
49 | (display
50 | (divide 14 #t))
51 ? uncaught exception: (expected-number #t)
52
53 | (display
54 | (divide #t 51))
55 ? uncaught exception: (expected-number #t)
56
57 'XXX'
58
59 ;(d is positive)
60 (define divide-r-pos (fun (self n d acc)
61 (if (> d n)
62 acc
63 (self self (subtract n d) d (add 1 acc)))))
64
65 ;(d is negative)
66 (define divide-r-neg (fun (self n d acc)
67 (if (> (abs d) n)
68 (subtract 0 (add 1 acc))
69 (self self (add n d) d (add 1 acc)))))
70
71 (define divide (macro (self args env)
72 (bind-args (n d) args env
73 (if (equal? d 0)
74 (raise (list (literal division-by-zero) n))
75 (if (< n 0)
76 (self (subtract 0 n) (subtract 0 d))
77 (if (> d 0)
78 (divide-r-pos divide-r-pos n d 0)
79 (divide-r-neg divide-r-neg n d 0)))))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `drop-while` evaluates its first argument to obtain a predicate and its
5 second argument to obtain a list. It then evaluates to the suffix of the
6 given list, starting at the first element which does not satisfy the
7 predicate.
8
9 | (display
10 | (drop-while (fun (x) (symbol? x)) (literal (one two 3 4 five 6 seven))))
11 = (3 4 five 6 seven)
12
13 | (display
14 | (drop-while (fun (x) (symbol? x)) (literal (1 2 3 4 5 6))))
15 = (1 2 3 4 5 6)
16
17 | (display
18 | (drop-while (fun (x) (number? x)) (literal (1 2 3 4 5 6))))
19 = ()
20
21 | (display
22 | (drop-while (fun (x) (symbol? x)) ()))
23 = ()
24
25 | (display
26 | (drop-while (fun (x) (symbol? x)) #f))
27 ? uncaught exception: (expected-list #f)
28
29 'XXX'
30
31 (define drop-while (fun (pred li)
32 (bind drop-while-r (fun (self pred li)
33 (if (empty? li)
34 ()
35 (if (pred (head li))
36 (self self pred (tail li))
37 li)))
38 (drop-while-r drop-while-r pred li))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `elem?` evaluates its first argument to a value of any type, and its
5 second argument to obtain a list. It then evaluates to `#t` if the value
6 is `equal?` to some element of the list, `#f` otherwise.
7
8 | (display
9 | (elem? (literal p) (literal (a p e))))
10 = #t
11
12 | (display
13 | (elem? (literal p) (literal (a r k))))
14 = #f
15
16 | (display
17 | (elem? 7 ()))
18 = #f
19
20 | (display
21 | (elem? 7 (list 5 (list 6 7) 8)))
22 = #f
23
24 `elem?` can be defined in terms of `find`, in a manner such as:
25
26 (not (empty? (find (fun (x) (equal? x y)) li)))
27
28 'XXX'
29
30 (define elem? (fun (item li)
31 (bind elem?-r (fun (self item li)
32 (if (empty? li)
33 #f
34 (if (equal? item (head li))
35 #t
36 (self self item (tail li)))))
37 (elem?-r elem?-r item li))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `empty?` evaluates its single argument, and evaluates to `#t` if that value
5 is the empty list, `#f` otherwise.
6
7 | (display
8 | (empty? (literal symbol)))
9 = #f
10
11 | (display
12 | (empty? ()))
13 = #t
14
15 | (display
16 | (empty? (list 1 2 3)))
17 = #f
18
19 'XXX'
20
21 (define empty? (fun (li)
22 (equal? li ())))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Env)"
3
4 `env?` evaluates its single argument, and evaluates to `#t` if
5 and only if it is a well-formed binding alist.
6
7 | (display
8 | (env? (literal ((a 1) (b 2) (c 3)))))
9 = #t
10
11 | (display
12 | (env? (literal ((a 1) (999 2) (c 3)))))
13 = #f
14
15 | (display
16 | (env? (literal ((a 1) (b 2) c))))
17 = #f
18
19 | (display
20 | (env? 7))
21 = #f
22
23 | (display
24 | (env? (env)))
25 = #t
26
27 'XXX'
28
29 (define env? (fun (li)
30 (bind env?-r (fun (self li)
31 (if (empty? li)
32 #t
33 (if (list? li)
34 (bind binding (head li)
35 (if (list? binding)
36 (if (symbol? (head binding))
37 (self self (tail li))
38 #f)
39 #f))
40 #f)))
41 (env?-r env?-r li))))
0 (define env (@macro (self args env) env))
1
2 ;'XXX'
3
4 -> Tests for functionality "Interpret Robin Program (with Small)"
5
6 `env` evaluates to all the bindings in effect at the point of execution
7 where this form is encountered, as an alist.
8
9 | (display
10 | (bind find (@macro (self args env)
11 | (bind-args (alist key) args env
12 | (@if (@equal? alist (literal ())) (literal ())
13 | (@if (@equal? key (@head (@head alist)))
14 | (@head alist)
15 | (self (@tail alist) key)))))
16 | (@prepend
17 | (find (env) (literal @symbol?)) (find (env) (literal @prepend)))))
18 = ((@symbol? @symbol?) @prepend @prepend)
19
20 `env` expects no arguments. Any arguments supplied will be simply ignored
21 and discarded, without being evaluated.
22
23 | (display
24 | (bind find (@macro (self args env)
25 | (bind-args (alist key) args env
26 | (@if (@equal? alist (literal ())) (literal ())
27 | (@if (@equal? key (@head (@head alist)))
28 | (@head alist)
29 | (self (@tail alist) key)))))
30 | (@prepend
31 | (find (env find) (literal @symbol?))
32 | (find (env (goofah whatever)) (literal @prepend)))))
33 = ((@symbol? @symbol?) @prepend @prepend)
34
35 'XXX'
0 (define equal? (@macro (self args env)
1 (bind-args (lhs rhs) args env
2 (@equal? lhs rhs))))
3
4 ;'XXX'
5
6 -> Tests for functionality "Interpret Robin Program (with Small)"
7
8 `equal?` is a wrapper for the `@equal?` intrinsic, for which it provides
9 predictable failure modes. In non-failure modes, `equal?` should have
10 semantics identical to `@equal?`.
11
12 Arguments to `equal?` can be any type, but fewer than or more than
13 two arguments will raise an exception.
14
15 | (display
16 | (equal? 7))
17 ? uncaught exception: (illegal-arguments (7))
18
19 | (display
20 | (equal? 7 8 9))
21 ? uncaught exception: (illegal-arguments (7 8 9))
22
23 'XXX'
0 (define eval (macro (self args macro-env)
1 (@if (@equal? args ())
2 (@raise (list (literal illegal-arguments) args))
3 (@if (@equal? (@tail args) ())
4 (@raise (list (literal illegal-arguments) args))
5 (@if (@equal? (@tail (@tail args)) ())
6 (@eval macro-env
7 (list (literal @eval)
8 (@head args)
9 (@head (@tail args))))
10 (@raise (list (literal illegal-arguments) args)))))))
11
12 ;'XXX'
13
14 -> Tests for functionality "Interpret Robin Program (with Small)"
15
16 `eval` is a wrapper for the `@eval` intrinsic, for which it provides
17 predictable failure modes. In non-failure modes, `eval` should have
18 semantics identical to `@eval`.
19
20 `eval` evaluates its first argument to obtain an environment, then
21 evaluates its second argument to obtain an S-expression; it then
22 evaluates that S-expression in the given environment.
23
24 | (display
25 | (eval (env) (literal
26 | (@prepend (literal a)
27 | (@prepend (literal b) ())))))
28 = (a b)
29
30 | (display
31 | (eval () (literal
32 | (@prepend (literal a)
33 | (@prepend (literal b) ())))))
34 ? uncaught exception: (unbound-identifier @prepend)
35
36 Something fairly complicated that uses `bind`...?
37
38 | (display
39 | (bind bindings (@prepend
40 | (@prepend (literal same) (@prepend @equal? ()))
41 | (@prepend
42 | (@prepend (literal x) (@prepend #f ()))
43 | ()))
44 | (eval bindings (literal (same x x)))))
45 = #t
46
47 If two bindings for the same identifier are supplied in the environment
48 alist passed to `eval`, the one closer to the front of the alist takes
49 precedence.
50
51 | (display
52 | (bind bindings (@prepend
53 | (@prepend (literal foo) (@prepend (literal yes) ()))
54 | (@prepend
55 | (@prepend (literal foo) (@prepend (literal no) ()))
56 | ()))
57 | bindings))
58 = ((foo yes) (foo no))
59
60 | (display
61 | (bind bindings (@prepend
62 | (@prepend (literal foo) (@prepend (literal yes) ()))
63 | (@prepend
64 | (@prepend (literal foo) (@prepend (literal no) ()))
65 | ()))
66 | (eval bindings (literal foo))))
67 = yes
68
69 `eval` will happily use whatever type of value you like as the
70 environment, however, subsequent evaluation will fail when it
71 tries to look up things in that environment.
72
73 | (display
74 | (eval 103 (literal
75 | (prepend (literal a)
76 | (prepend (literal b) ())))))
77 ? uncaught exception: (expected-env-alist 103)
78
79 Evaluation expects the contents of the list which makes up the
80 environment to be two-element lists.
81
82 | (display
83 | (eval (prepend #f ()) (literal
84 | (prepend (literal a)
85 | (prepend (literal b) ())))))
86 ? uncaught exception: (expected-env-entry #f)
87
88 Evaluation expects the head of each sublist in the list which makes up the
89 environment to be a symbol.
90
91 | (display
92 | (eval (prepend (prepend 7 (prepend #f ())) ()) (literal
93 | (prepend (literal a)
94 | (prepend (literal b) ())))))
95 ? uncaught exception: (expected-symbol 7)
96
97 `eval` expects exactly two arguments.
98
99 | (display
100 | (eval))
101 ? uncaught exception: (illegal-arguments ())
102
103 | (display
104 | (eval 4 5 6))
105 ? uncaught exception: (illegal-arguments (4 5 6))
106
107 'XXX'
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Env)"
3
4 `export` treats its arguments as a list of identifiers, and returns an
5 environment where only those identifiers are bound to values.
6
7 The original idea for `sandbox` was that it could be used in the body of
8 a module to restrict the visible identifiers to those the module wished
9 to export, which could then actually be exported with `env`. However,
10 this still required `env` to be a visible identifier (and thus exported.)
11 `export` simply evaluates to a binding alist which can be returned
12 directly.
13
14 Note: the order of the bindings in the binding alist isn't guaranteed;
15 thus these tests are written to search the resulting alist.
16
17 | (display
18 | (let ((a 1) (b 6))
19 | (length (export a b))))
20 = 2
21
22 | (display
23 | (let ((a 1) (b 6))
24 | (lookup (literal a) (export a b))))
25 = (1)
26
27 | (display
28 | (let ((a 1) (b 6))
29 | (lookup (literal b) (export a b))))
30 = (6)
31
32 | (display
33 | (lookup (literal @head) (export @head @tail)))
34 = (@head)
35
36 | (display
37 | (lookup (literal @prepend) (export @head @tail)))
38 = ()
39
40 'XXX'
41
42 (define export
43 (macro (self args env)
44 (filter (fun (binding) (elem? (head binding) args)) env)))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 | (display
5 | (extend (literal b) 6 (literal ((a 1) (b 2) (c 3)))))
6 = ((b 6) (a 1) (b 2) (c 3))
7
8 The following should be true for any identifier i and alist x.
9
10 | (display
11 | (let ((i (literal a))
12 | (x (literal ((f 5) (g 7)))))
13 | (lookup i (extend i 1 x))))
14 = (1)
15
16 | (display
17 | (extend (literal b) 6 ()))
18 = ((b 6))
19
20 | (display
21 | (extend (literal b) 6 81))
22 ? uncaught exception: (expected-list 81)
23
24 'XXX'
25
26 (define extend (fun (id val alist)
27 (prepend (list id val) alist)))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `filter` evaluates its first argument to obtain a macro, generally assumed
5 to be a predicate (a one-argument function which evaluates to a boolean).
6 It then evaluates its second argument to obtain a list. It then evaluates
7 to a list which contains all the elements of the given list, in the same
8 order, which satisfy the predicate.
9
10 | (display
11 | (filter (fun (x) (symbol? x)) (literal (1 two #f 3 () four 5 six))))
12 = (two four six)
13
14 | (display
15 | (filter (fun (x) x) (literal (#t #t #f banana #t #f))))
16 ? uncaught exception: (expected-boolean banana)
17
18 'XXX'
19
20 (define filter (fun (pred li)
21 (reverse (fold
22 (fun (x acc) (if (pred x) (prepend x acc) acc))
23 () li))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `find` evaluates its first argument to obtain a predicate, then evaluates
5 its second argument to obtain a list. It then evaluates to a list which
6 is either empty, if no element of the list satisfies the predicate, or
7 a list which contains exactly one element, which will be the first
8 element from the list which satisfies the predicate.
9
10 | (display
11 | (find (fun (x) (symbol? x)) ()))
12 = ()
13
14 | (display
15 | (find (fun (x) (symbol? x)) (list 1 2 3)))
16 = ()
17
18 | (display
19 | (find (fun (x) #t) (list 1 2 3)))
20 = (1)
21
22 | (display
23 | (find (fun (x) (symbol? x)) (literal (1 two #f 3 () four 5 six))))
24 = (two)
25
26 `find` could be defined in terms of `filter`, but in practice it would
27 be implemented in a way which need not examine the entire list.
28
29 'XXX'
30
31 (define find (fun (pred li)
32 (bind find-r (fun (self pred li)
33 (if (empty? li)
34 ()
35 (if (pred (head li))
36 (list (head li))
37 (self self pred (tail li)))))
38 (find-r find-r pred li))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `first` evaluates its first argument to obtain a non-negative integer,
5 considered to be a desired length, and its second argument to obtain a list.
6 It then evaluates to the prefix of the given list of the desired length.
7
8 | (display
9 | (first 0 (list 1 2 3 4 5)))
10 = ()
11
12 | (display
13 | (first 3 (list 1 2 3 4 5)))
14 = (1 2 3)
15
16 | (display
17 | (first 6 (list 1 2 3 4 5)))
18 ? uncaught exception: (expected-list ())
19
20 | (display
21 | (first 1 (literal foo)))
22 ? uncaught exception: (expected-list foo)
23
24 | (display
25 | (first 0 (literal foo)))
26 = ()
27
28 'XXX'
29
30 (define first (fun (n li)
31 (bind first-r (fun (self n li)
32 (if (equal? n 0)
33 ()
34 (prepend (head li) (self self (subtract n 1) (tail li)))))
35 (first-r first-r n li))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `flatten` evaluates its first argument to obtain a list, then evaluates
5 to the list obtained by interpolating all elements into a single list.
6 By interpolating we mean that, if some element is itself a list, the
7 individual elements of that list will be present, in the same order, in
8 the corresponding position, in the resulting list, and that this process
9 is applied recursively to any elements in sublists which are themselves
10 sublists.
11
12 | (display
13 | (flatten ()))
14 = ()
15
16 | (display
17 | (flatten (list 1 2 3)))
18 = (1 2 3)
19
20 | (display
21 | (flatten (list 1 (list 2 3 4) 5)))
22 = (1 2 3 4 5)
23
24 | (display
25 | (flatten (list 1 (list 2 3 (list 4 4 4)) 5)))
26 = (1 2 3 4 4 4 5)
27
28 | (display
29 | (flatten (list 1 () 5)))
30 = (1 5)
31
32 'XXX'
33
34 (define flatten (fun (li)
35 (bind flatten-r (fun (self li acc)
36 (if (empty? li)
37 acc
38 (if (list? (head li))
39 (self self (tail li) (self self (head li) acc))
40 (self self (tail li) (prepend (head li) acc)))))
41 (reverse (flatten-r flatten-r li ())))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `fold` evaluates its first argument to obtain a macro, generally assumed to
5 be a two-argument function, its second argument to obtain an initial value,
6 and its third argument to obtain a list. It then applies the function to
7 successive elements of the list. Each time the function is applied, an
8 element from the list is passed as the first argument. The first time the
9 function is applied, the initial value is passed as the second argument;
10 each subsequent time, the result of the previous application is passed as
11 the second argument. `fold` evaluates to the result of the the final
12 application of the function.
13
14 | (display
15 | (fold (fun (x a) x) () (literal (three dog night))))
16 = night
17
18 | (display
19 | (fold (fun (x a) a) 541 (literal (archie moffam))))
20 = 541
21
22 | (display
23 | (fold (fun (x a) (list a x)) () (literal (three dog night))))
24 = (((() three) dog) night)
25
26 | (display
27 | (fold 99 (fun (x a) a) (literal (three dog night))))
28 ? uncaught exception: (inapplicable-object 99)
29
30 'XXX'
31
32 ;(requires empty?)
33 (define fold (fun (app acc li)
34 (bind fold-r (fun (self app acc li)
35 (if (empty? li)
36 acc
37 (self self app (app (head li) acc) (tail li))))
38 (fold-r fold-r app acc li))))
0 (define fun (macro (self args env)
1 (bind extend-with-args (macro (self args env)
2 (bind-args (env-to-extend formals actuals env-for-actuals) args env
3 (if (equal? formals ())
4 (if (equal? actuals ())
5 env-to-extend
6 (raise (list (literal illegal-arguments) (head (tail (tail args))))))
7 (if (equal? actuals ())
8 (raise (list (literal illegal-arguments) (head (tail (tail args)))))
9 (let (
10 (formal (head formals))
11 (actual (head actuals))
12 (rest-formals (tail formals))
13 (rest-actuals (tail actuals))
14 (evaled-actual (eval env-for-actuals actual))
15 (binding (list formal evaled-actual))
16 (extended-env (prepend binding env-to-extend))
17 )
18 (self extended-env rest-formals rest-actuals env-for-actuals))))))
19 (macro (iself iargs ienv)
20 (eval (extend-with-args env (head args) iargs ienv) (head (tail args)))))))
21
22 ;'XXX'
23
24 -> Tests for functionality "Interpret Robin Program (with Fun)"
25
26 You can define functions with `fun`. They can be anonymous.
27
28 | (display
29 | ((fun (a) a) (literal whee)))
30 = whee
31
32 Function have "closure" behavior; that is, bindings in force when a
33 function is defined will still be in force when the function is applied,
34 even if they are no longer lexically in scope.
35
36 | (display
37 | ((let
38 | ((a (literal (hi)))
39 | (f (fun (x) (list x a))))
40 | f) (literal oh)))
41 = (oh (hi))
42
43 Functions can take functions.
44
45 | (display
46 | (let
47 | ((apply (fun (x) (x (literal a)))))
48 | (apply (fun (r) (list r)))))
49 = (a)
50
51 Functions can return functions.
52
53 | (display
54 | (let
55 | ((mk (fun (x) (fun (y) (prepend y x))))
56 | (mk2 (mk (literal (vindaloo)))))
57 | (mk2 (literal chicken))))
58 = (chicken vindaloo)
59
60 Arguments to functions shadow any other bindings in effect.
61
62 | (display
63 | (let
64 | ((a (literal a))
65 | (b (fun (a) (list a a))))
66 | (b 7)))
67 = (7 7)
68
69 A function may have no arguments at all.
70
71 | (display
72 | ((fun () 7)))
73 = 7
74
75 But, a function must have exactly both a body and a list of formal arguments.
76 Otherwise, an exception will be raised.
77
78 | (display
79 | ((fun ())))
80 ? uncaught exception
81
82 | (display
83 | ((fun)))
84 ? uncaught exception
85
86 | (display
87 | ((fun (a) a a)))
88 ? uncaught exception
89
90 An `illegal-arguments` exception will be raised if not enough arguments are
91 supplied to a function call.
92
93 | (display
94 | ((fun (a b) (list b a))
95 | (prepend 1 ())))
96 ? uncaught exception: (illegal-arguments
97
98 An `illegal-arguments` exception will be raised if too many arguments are
99 supplied to a function call.
100
101 | (display
102 | ((fun (a b) (list b a))
103 | 1 (prepend 2 ()) 3))
104 ? uncaught exception: (illegal-arguments
105
106 `fun` is basically equivalent to Scheme's `lambda`.
107
108 'XXX'
0 (define head (@macro (self args env)
1 (bind-args (l) args env
2 (@head l))))
3
4 ;'XXX'
5
6 -> Tests for functionality "Interpret Robin Program (with Small)"
7
8 `head` is a wrapper for the `@head` intrinsic, for which it provides
9 predictable failure modes. In non-failure modes, `head` should have
10 semantics identical to `@head`.
11
12 `head` expects its argument to be a list.
13
14 | (display
15 | (head #f))
16 ? uncaught exception: (expected-list #f)
17
18 `head` expects exactly one argument.
19
20 | (display
21 | (head (@prepend #t ()) (@prepend #f ())))
22 ? uncaught exception: (illegal-arguments ((@prepend #t ()) (@prepend #f ())))
23
24 | (display
25 | (head))
26 ? uncaught exception: (illegal-arguments ())
27
28 'XXX'
0 (define if (@macro (self args macro-env)
1 (choose
2 ((@equal? args ())
3 (@raise (list (literal illegal-arguments) args)))
4 ((@equal? (@tail args) ())
5 (@raise (list (literal illegal-arguments) args)))
6 ((@equal? (@tail (@tail args)) ())
7 (@raise (list (literal illegal-arguments) args)))
8 ((@equal? (@tail (@tail (@tail args))) ())
9 (@eval macro-env (list (literal @if)
10 (@head args)
11 (@head (@tail args))
12 (@head (@tail (@tail args))))))
13 (else
14 (@raise (list (literal illegal-arguments) args))))))
15
16 ;'XXX'
17
18 -> Tests for functionality "Interpret Robin Program (with Small)"
19
20 `if` is a wrapper for the `@if` intrinsic, for which it provides predictable
21 failure modes. In non-failure modes, `if` should have semantics identical
22 to `@if`.
23
24 The second and third arguments can be arbitrary expressions, but `if`
25 expects its first argument to be a boolean.
26
27 | (display
28 | (if 5 7 9))
29 ? uncaught exception: (expected-boolean 5)
30
31 `if` expects exactly three arguments.
32
33 | (display
34 | (if #t 7))
35 ? uncaught exception: (illegal-arguments (#t 7))
36
37 | (display
38 | (if #t 7 8 9))
39 ? uncaught exception: (illegal-arguments (#t 7 8 9))
40
41 'XXX'
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `index` evaluates its first argument to a natural number, and its
5 second argument to a list. It then evaluates to the element of the
6 list at the index given by the natural number. The index is 0-based;
7 0 refers to the element at the head of the list.
8
9 | (display
10 | (index 0 (literal (the girl from ipanema))))
11 = the
12
13 | (display
14 | (index 2 (literal (the girl from ipanema))))
15 = from
16
17 | (display
18 | (bind last (fun (li) (index (subtract (length li) 1) li))
19 | (last (literal (the girl from ipanema)))))
20 = ipanema
21
22 Attempting to index beyond the end of the list will raise an exception.
23
24 | (display
25 | (index 7 (literal (the girl from ipanema))))
26 ? uncaught exception: (expected-list ())
27
28 `index` expects its first argument to be a number.
29
30 | (display
31 | (index (literal goofy) (list 1 2 3 4 5)))
32 ? uncaught exception: (expected-number goofy)
33
34 `index` expects its second argument to be a list.
35
36 | (display
37 | (index 8 (literal whatnot)))
38 ? uncaught exception: (expected-list whatnot)
39
40 'XXX'
41
42 (define index (fun (index li)
43 (bind index-r (fun (self index li)
44 (if (equal? index 0)
45 (head li)
46 (self self (subtract index 1) (tail li))))
47 (index-r index-r index li))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Stdlib)"
3
4 `itoa` evaluates its sole argument to an integer, then evaluates to
5 a string representing that integer in decimal.
6
7 | (display
8 | (itoa 100))
9 = (49 48 48)
10
11 | (display
12 | (itoa 99))
13 = (57 57)
14
15 | (display
16 | (itoa 0))
17 = (48)
18
19 | (display
20 | (itoa (subtract 0 1)))
21 = (45 49)
22
23 | (display
24 | (itoa (subtract 0 765)))
25 = (45 55 54 53)
26
27 | (display
28 | (itoa (literal m)))
29 ? uncaught exception: (expected-number m)
30
31 'XXX'
32
33 (define itoa (macro (self args env)
34 (bind itoa-r (macro (self args env)
35 (bind-args (val) args env
36 (if (equal? val 0)
37 ()
38 (let ((digit (remainder val 10))
39 (rest (divide val 10)))
40 (prepend (add 48 digit) (self rest))))))
41 (bind-args (val) args env
42 (if (equal? val 0)
43 (list 48)
44 (if (< val 0)
45 (prepend 45 (reverse (itoa-r (subtract 0 val))))
46 (reverse (itoa-r val))))))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `last` evaluates its first argument to obtain a non-negative integer,
5 considered to be a desired length, and its second argument to obtain a
6 list. It then evaluates to the suffix of the given list of the desired
7 length.
8
9 | (display
10 | (last 0 (list 1 2 3 4 5)))
11 = ()
12
13 | (display
14 | (head (last 1 (list 1 2 3 4 5))))
15 = 5
16
17 | (display
18 | (last 3 (list 1 2 3 4 5)))
19 = (3 4 5)
20
21 | (display
22 | (last 6 (list 1 2 3 4 5)))
23 ? uncaught exception: (expected-list ())
24
25 | (display
26 | (last 1 (literal foo)))
27 ? uncaught exception: (expected-list foo)
28
29 Unlike `first`, `last` does care if it's not a list, even when the count
30 is zero.
31
32 | (display
33 | (last 0 (literal foo)))
34 ? uncaught exception: (expected-list foo)
35
36 'XXX'
37
38 (define last (fun (n li)
39 (reverse (first n (reverse li)))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `length` evaluates its single argument to obtain a proper list, then
5 evaluates to a non-negative integer which is the length of the list
6 (the number of cells, not counting nested cells and not counting the
7 empty list at the very tail.)
8
9 | (display
10 | (length ()))
11 = 0
12
13 | (display
14 | (length (list 1 2 #t #f 3)))
15 = 5
16
17 | (display
18 | (length (literal whatnot)))
19 ? uncaught exception: (expected-list whatnot)
20
21 'XXX'
22
23 (define length (fun (li)
24 (subtract 0 (fold (fun (x acc) (subtract acc 1)) 0 li))))
0 (define let (@macro (self args env)
1 (bind bindings (@head args)
2 (@if (@equal? bindings ())
3 (@eval env (@head (@tail args)))
4 (bind binding (@head bindings)
5 (bind name (@head binding)
6 (@if (@symbol? name)
7 (bind value (@eval env (@head (@tail binding)))
8 (bind newenv (@prepend (@prepend name (@prepend value ())) env)
9 (bind newbindings (@tail bindings)
10 (bind newargs (@prepend newbindings (@tail args))
11 (@eval newenv (@prepend self newargs))))))
12 (@raise (@prepend (literal illegal-binding) (@prepend binding ()))))))))))
13
14 ;'XXX'
15
16 -> Tests for functionality "Interpret Robin Program (with Small)"
17
18 `let` lets you bind multiple identifiers to multiple values.
19
20 An identifier can be bound to a symbol.
21
22 | (display
23 | (let ((a (literal hello))) a))
24 = hello
25
26 `let` can appear in the binding expression in a `let`.
27
28 | (display
29 | (let ((a (let ((b (literal c))) b))) a))
30 = c
31
32 `let` can bind a symbol to a macro.
33
34 | (display
35 | (let ((a (@macro (self args env)
36 | (let ((x (@eval env (@head args)))
37 | (y (@eval env (@head (@tail args)))))
38 | (prepend y x)))))
39 | (a () (literal foo))))
40 = (foo)
41
42 Bindings established in a `let` remain in effect when evaluating
43 the arguments things in the body of the `let`.
44
45 | (display
46 | (let ((dup (@macro (self args env)
47 | (bind x (@eval env (@head args))
48 | (list x x)))))
49 | (dup (dup (literal g)))))
50 = ((g g) (g g))
51
52 Bindings established in a binding in a `let` can be seen in
53 subsequent bindings in the same `let`.
54
55 | (display
56 | (let ((a (literal hello)) (b (list a))) b))
57 = (hello)
58
59 Shadowing happens.
60
61 | (display
62 | (let ((a (literal hello))) (let ((a (literal goodbye))) a)))
63 = goodbye
64
65 `let` can have an empty list of bindings.
66
67 | (display
68 | (let () (literal hi)))
69 = hi
70
71 The list of bindings must be a list, or else an exception will be raised.
72
73 | (display
74 | (let 999 (literal hi)))
75 ? uncaught exception
76
77 Each binding in a list must be a list, or else an exception will be raised.
78
79 | (display
80 | (let (999) (literal hi)))
81 ? uncaught exception
82
83 Both the body and the list of bindings are required, or else an exception
84 will be raised.
85
86 | (display
87 | (let ()))
88 ? uncaught exception
89
90 | (display
91 | (let))
92 ? uncaught exception
93
94 Any arguments given beyond the body and list of bindings will be ignored
95 and discarded, without being evaluated.
96
97 | (display
98 | (let ((a 1)) a foo))
99 = 1
100
101 Each binding must have at least a name and a value, or else an exception
102 will be raised.
103
104 | (display
105 | (let ((a)) a))
106 ? uncaught exception
107
108 | (display
109 | (let (()) 7))
110 ? uncaught exception
111
112 Anything given in a binding beyond the name and the value will simply be
113 ignored and discarded, without being evaluated or otherwise examined.
114
115 | (display
116 | (let ((a 1 foo)) a))
117 = 1
118
119 The identifier in a binding must be a symbol.
120
121 | (display
122 | (let ((3 1)) 3))
123 ? uncaught exception: (illegal-binding (3 1))
124
125 `let` is basically equivalent to Scheme's `let*` or Haskell's `let`.
126
127 'XXX'
0 (define list? (@macro (self args env)
1 (bind-args (l) args env
2 (@list? l))))
3
4 ;'XXX'
5
6 -> Tests for functionality "Interpret Robin Program (with Small)"
7
8 `list?` is a wrapper for the `@list?` intrinsic, for which it provides
9 predictable failure modes. In non-failure modes, `list?` should have
10 semantics identical to `@list?`.
11
12 The argument to `list?` may (naturally) be any type, but there must be
13 exactly one argument.
14
15 | (display
16 | (list? (prepend 4 ()) (prepend 6 ())))
17 ? uncaught exception: (illegal-arguments ((prepend 4 ()) (prepend 6 ())))
18
19 | (display
20 | (list?))
21 ? uncaught exception: (illegal-arguments ())
22
23 'XXX'
0 (define list (@macro (self args env)
1 (@if (@equal? args ())
2 ()
3 (@prepend (@eval env (@head args))
4 (@eval env (@prepend self (@tail args)))))))
5
6 ;'XXX'
7
8 -> Tests for functionality "Interpret Robin Program (with Small)"
9
10 `list` is a macro which evaluates each of its arguments, and evaluates to a
11 (proper) list containing each of the results, in the same order.
12
13 | (display
14 | (list 1 2 3 4 5))
15 = (1 2 3 4 5)
16
17 | (display
18 | (list (list 2 3) (list 6 7)))
19 = ((2 3) (6 7))
20
21 `list` need not have any arguments at all; the result is the empty list.
22
23 | (display
24 | (list))
25 = ()
26
27 Unlike `literal`, `list` does evaluate its arguments, all of them.
28
29 | (display
30 | (list (literal x) (literal y)))
31 = (x y)
32
33 `list` does not require any arguments.
34
35 | (display
36 | (list))
37 = ()
38
39 'XXX'
0 (define literal (@macro (self args env) (@head args)))
1
2 ;'XXX'
3
4 -> Tests for functionality "Interpret Robin Program (with Small)"
5
6 One of the most basic identifiers available in `small` is `literal`,
7 which evaluates to the literal content of its sole argument, which can be
8 any S-expression.
9
10 | (display
11 | (literal symbol))
12 = symbol
13
14 | (display
15 | (literal (hello (there) world)))
16 = (hello (there) world)
17
18 `literal` requires at least one argument; otherwise, an exception will
19 be raised.
20
21 | (display
22 | (literal))
23 ? uncaught exception
24
25 TODO Unlike other things in `stdlib`, this does not use builtin wrappers
26
27 Any arguments beyond the first argument are simply ignored and discarded.
28
29 | (display
30 | (literal a b c))
31 = a
32
33 `literal` is basically equivalent to Scheme's `quote`.
34
35 'XXX'
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 | (display
5 | (lookup (literal b) (literal ((a 1) (b 2) (c 3)))))
6 = (2)
7
8 | (display
9 | (lookup (literal a) (literal ((a 1) (a 2) (a 3)))))
10 = (1)
11
12 | (display
13 | (lookup (literal r) (literal ((a 1) (b 2) (c 3)))))
14 = ()
15
16 | (display
17 | (lookup (literal q) ()))
18 = ()
19
20 | (display
21 | (lookup (literal q) 55))
22 ? uncaught exception: (expected-list 55)
23
24 | (display
25 | (lookup (literal q) (literal ((a 7) 99 (q 4)))))
26 ? uncaught exception: (expected-list 99)
27
28 'XXX'
29
30 (define lookup (fun (id alist)
31 (bind lookup-r (fun (self id alist)
32 (if (empty? alist)
33 ()
34 (if (equal? id (head (head alist)))
35 (list (head (tail (head alist))))
36 (self self id (tail alist)))))
37 (lookup-r lookup-r id alist))))
0 (define macro? (@macro (self args env)
1 (bind-args (m) args env
2 (@macro? m))))
3
4 ;'XXX'
5
6 -> Tests for functionality "Interpret Robin Program (with Small)"
7
8 `macro?` is a wrapper for the `@macro?` intrinsic, for which it provides
9 predictable failure modes. In non-failure modes, `macro?` should have
10 semantics identical to `@macro?`.
11
12 The argument to `macro?` may (naturally) be any type, but there must be
13 exactly one argument.
14
15 | (display
16 | (macro? @macro @macro))
17 ? uncaught exception: (illegal-arguments (@macro @macro))
18
19 | (display
20 | (macro?))
21 ? uncaught exception: (illegal-arguments ())
22
23 'XXX'
0 (define macro (@macro (self args macro-env)
1 (choose
2 ((@equal? args ())
3 (@raise (list (literal illegal-arguments) args)))
4 ((@equal? (@tail args) ())
5 (@raise (list (literal illegal-arguments) args)))
6 ((@equal? (@tail (@tail args)) ())
7 (bind param-list (@head args)
8 (choose
9 ((@equal? #f (list? param-list))
10 (@raise (list (literal illegal-arguments) args)))
11 ((@equal? param-list ())
12 (@raise (list (literal illegal-arguments) args)))
13 ((@equal? (@tail param-list) ())
14 (@raise (list (literal illegal-arguments) args)))
15 ((@equal? (@tail (@tail param-list)) ())
16 (@raise (list (literal illegal-arguments) args)))
17 ((@equal? (@tail (@tail (@tail param-list))) ())
18 (@if (symbol? (@head param-list))
19 (@if (symbol? (@head (@tail param-list)))
20 (@if (symbol? (@head (@tail (@tail param-list))))
21 (@eval macro-env
22 (list (literal @macro) (@head args) (@head (@tail args))))
23 (@raise (list (literal illegal-arguments) args)))
24 (@raise (list (literal illegal-arguments) args)))
25 (@raise (list (literal illegal-arguments) args))))
26 (else
27 (@raise (list (literal illegal-arguments) args))))))
28 (else
29 (@raise (list (literal illegal-arguments) args))))))
30
31 ;'XXX'
32
33 -> Tests for functionality "Interpret Robin Program (with Small)"
34
35 `macro` is a wrapper for the `@macro` intrinsic, for which it provides
36 predictable failure modes. In non-failure modes, `macro` should have
37 semantics identical to `@macro`.
38
39 Macros have "closure" behavior; that is, bindings in force when a
40 macro is defined will still be in force when the macro is applied,
41 even if they are no longer lexically in scope. (Please try to ignore
42 the heavy `define`s that are used in this test...)
43
44 | (display
45 | ((let
46 | ((a (literal these-are))
47 | (m (macro (self args env) (@prepend a args))))
48 | m) my args))
49 = (these-are my args)
50
51 Macros can return macros.
52
53 | (display
54 | (let
55 | ((mk (macro (self argsa env)
56 | (macro (self argsb env)
57 | (@prepend (@head argsb) argsa))))
58 | (mk2 (mk vindaloo)))
59 | (mk2 chicken)))
60 = (chicken vindaloo)
61
62 Arguments to macros shadow any other bindings in effect.
63
64 | (display
65 | (let
66 | ((args (literal a))
67 | (b (macro (self args env) (@prepend args args))))
68 | (b 7)))
69 = ((7) 7)
70
71 `self` is there to let you write recursive macros. The following
72 example demonstrates this; it evaluates `(prepend b d)` in an environment
73 where all the identifiers you list after `qqq` have been bound to 0.
74
75 | (display
76 | (bind qqq
77 | (macro (self args env)
78 | (@if (@equal? args ())
79 | (@eval env (literal (@prepend b (@prepend d ()))))
80 | (@eval (@prepend (@prepend (@head args) (@prepend 0 ())) env)
81 | (@prepend self (@tail args)))))
82 | (bind b 1 (bind d 4 (qqq b c d)))))
83 = (0 0)
84
85 | (display
86 | (bind qqq
87 | (macro (self args env)
88 | (@if (@equal? args ())
89 | (@eval env (literal (@prepend b (@prepend d ()))))
90 | (@eval (@prepend (@prepend (@head args) (@prepend 0 ())) env)
91 | (@prepend self (@tail args)))))
92 | (bind b 1 (bind d 4 (qqq x y z)))))
93 = (1 4)
94
95 Your recursive `macro` application doesn't have to be tail-recursive.
96
97 | (display
98 | (bind make-env
99 | (macro (self args env)
100 | (@if (@equal? args ())
101 | ()
102 | (@prepend (@prepend (@head args)
103 | (@prepend (@eval env (@head args)) ()))
104 | (@eval env
105 | (@prepend self (@tail args))))))
106 | (bind b 1 (bind d 4 (make-env b d @tail)))))
107 = ((b 1) (d 4) (@tail @tail))
108
109 `macro` expects exactly two arguments.
110
111 | (display
112 | ((macro (self args env)) (why hello there)))
113 ? uncaught exception: (illegal-arguments ((self args env)))
114
115 | (display
116 | ((macro (self args env) prepend prepend) (why hello there)))
117 ? uncaught exception: (illegal-arguments ((self args env) prepend prepend))
118
119 `macro` expects its first argument to be a list of exactly three
120 symbols.
121
122 | (display
123 | ((macro 100 prepend) (why hello there)))
124 ? uncaught exception: (illegal-arguments (100 prepend))
125
126 | (display
127 | ((macro (self args) prepend) (why hello there)))
128 ? uncaught exception: (illegal-arguments ((self args) prepend))
129
130 | (display
131 | ((macro (self args env foo) prepend) (why hello there)))
132 ? uncaught exception: (illegal-arguments ((self args env foo) prepend))
133
134 | (display
135 | ((macro (self args 99) prepend) (why hello there)))
136 ? uncaught exception: (illegal-arguments ((self args 99) prepend))
137
138 'XXX'
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `map` evaluates its first argument to obtain a macro, and its second argument
5 to obtain a list. It then evaluates to a list which is obtained by applying
6 the macro to each element of the given list. The macro is generally assumed
7 to be a one-argument function.
8
9 | (display
10 | (map (fun (x) (list x)) (literal (three dog night))))
11 = ((three) (dog) (night))
12
13 While it is possible to pass a macro that is not a function, it is not
14 very productive. (Also, it exposes the implementation of `map`, so this
15 is not a very good test.)
16
17 | (display
18 | (map (macro (self args env) args) (literal (three dog night))))
19 = (((head li)) ((head li)) ((head li)))
20
21 'XXX'
22
23 ;(requires empty?)
24 (define map (fun (app li)
25 (bind map-r
26 (fun (self app li)
27 (if (empty? li)
28 ()
29 (prepend (app (head li)) (self self app (tail li)))))
30 (map-r map-r app li))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Arith)"
3
4 `multiply` evaluates both of its arguments to numbers and evaluates to the product
5 of those two numbers.
6
7 | (display
8 | (multiply 6 7))
9 = 42
10
11 | (display
12 | (multiply (subtract 0 6) 7))
13 = -42
14
15 | (display
16 | (multiply 6 (subtract 0 7)))
17 = -42
18
19 | (display
20 | (multiply (subtract 0 6) (subtract 0 7)))
21 = -42
22
23 `multiply` expects exactly two arguments.
24
25 | (display
26 | (multiply 14))
27 ? uncaught exception: (illegal-arguments (14))
28
29 | (display
30 | (multiply 6 7 7))
31 ? uncaught exception: (illegal-arguments (6 7 7))
32
33 Both of the arguments to `multiply` must be numbers.
34
35 | (display
36 | (multiply 14 #t))
37 ? uncaught exception: (expected-number #t)
38
39 | (display
40 | (multiply #t 51))
41 ? uncaught exception: (expected-number #t)
42
43 'XXX'
44
45 (define multiply (macro (self args env)
46 (bind multiply-r (fun (self a b) ;(b must be positive)
47 (if (equal? b 1)
48 a
49 (add a (self self a (subtract b 1)))))
50 (bind-args (a b) args env
51 (if (equal? b 0) 0
52 (if (< b 0)
53 (if (< a 0)
54 (multiply-r multiply-r a (subtract 0 b))
55 (subtract 0 (multiply-r multiply-r a (subtract 0 b))))
56 (multiply-r multiply-r a b)))))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Boolean)"
3
4 `not` evaluates its single argument to a boolean, then evaluates to
5 the logical negation of that boolean.
6
7 | (display
8 | (not #t))
9 = #f
10
11 | (display
12 | (not #f))
13 = #t
14
15 `not` expects exactly one argument.
16
17 | (display
18 | (not))
19 ? uncaught exception: (illegal-arguments ())
20
21 | (display
22 | (not #t #f))
23 ? uncaught exception: (illegal-arguments (#t #f))
24
25 `not` expects its single argument to be a boolean.
26
27 | (display
28 | (not 33))
29 ? uncaught exception: (expected-boolean 33)
30
31 'XXX'
32
33 (define not (macro (self args env)
34 (bind-args (a) args env
35 (if a #f #t))))
0 (define number? (@macro (self args env)
1 (bind-args (n) args env
2 (@number? n))))
3
4 ;'XXX'
5
6 -> Tests for functionality "Interpret Robin Program (with Small)"
7
8 `number?` is a wrapper for the `@number?` intrinsic, for which it provides
9 predictable failure modes. In non-failure modes, `number?` should have
10 semantics identical to `@number?`.
11
12 The argument to `number?` may (naturally) be any type, but there must be
13 exactly one argument.
14
15 | (display
16 | (number? 6 4))
17 ? uncaught exception: (illegal-arguments (6 4))
18
19 | (display
20 | (number?))
21 ? uncaught exception: (illegal-arguments ())
22
23 'XXX'
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Boolean)"
3
4 `or` evaluates both of its arguments to booleans, and evaluates to the
5 logical disjunction (boolean "or") of these two values.
6
7 | (display
8 | (or #t #t))
9 = #t
10
11 | (display
12 | (or #t #f))
13 = #t
14
15 | (display
16 | (or #f #t))
17 = #t
18
19 | (display
20 | (or #f #f))
21 = #f
22
23 `or` expects exactly two arguments.
24
25 (Hate to weaken this test, but I'm not a purist -- yet.)
26
27 | (display
28 | (or #f))
29 ? uncaught exception
30
31 | (display
32 | (or #t #f #f))
33 ? uncaught exception: (illegal-arguments (#t #f #f))
34
35 `or` expects both of its arguments to be booleans.
36
37 | (display
38 | (or 100 #f))
39 ? uncaught exception: (expected-boolean 100)
40
41 | (display
42 | (or #f 99))
43 ? uncaught exception: (expected-boolean 99)
44
45 `or` is short-circuiting in the sense that no arguments after the first
46 `#t` argument will be evaluated. Fully testing this requires side-effects,
47 but it can be demonstrated as follows.
48
49 | (display
50 | (or #t 100))
51 = #t
52
53 'XXX'
54
55 (define or (macro (self args env)
56 (if (equal? (tail (tail args)) ())
57 (if (eval env (head args))
58 #t
59 (if (eval env (head (tail args))) #t #f))
60 (raise (list (literal illegal-arguments) args)))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `prefix?` evaluates its first and second arguments to obtain lists.
5 It then evaluates to `#t` if the first list is a prefix of the second
6 list, `#f` otherwise. A list A is a prefix of a list B if A is `empty?`,
7 or the head of A is `equal?` to the head of B and the tail of A is a
8 prefix of the tail of B.
9
10 | (display
11 | (prefix? (list 1 2 3) (list 1 2 3 4 5 6)))
12 = #t
13
14 | (display
15 | (prefix? (list 1 2 5) (list 1 2 3 4 5 6)))
16 = #f
17
18 | (display
19 | (prefix? () (list 1 2 3 4 5 6)))
20 = #t
21
22 | (display
23 | (prefix? () (literal schpritz)))
24 = #t
25
26 | (display
27 | (prefix? (list 1 2 3) (list 1 2 3)))
28 = #t
29
30 | (display
31 | (prefix? (list 1 2 3 4) (list 1 2 3)))
32 = #f
33
34 'XXX'
35
36 (define prefix? (fun (la lb)
37 (bind prefix?-r (fun (self la lb)
38 (if (empty? la)
39 #t
40 (if (empty? lb)
41 #f
42 (if (equal? (head la) (head lb))
43 (self self (tail la) (tail lb))
44 #f))))
45 (prefix?-r prefix?-r la lb))))
0 (define prepend (@macro (self args env)
1 (bind-args (h t) args env
2 (@prepend h t))))
3
4 ;'XXX'
5
6 -> Tests for functionality "Interpret Robin Program (with Small)"
7
8 `prepend` is a wrapper for the `@prepend` intrinsic, for which it provides
9 predictable failure modes. In non-failure modes, `prepend` should have
10 semantics identical to `@prepend`.
11
12 The second argument to `prepend` must be a list.
13
14 | (display
15 | (prepend #t #f))
16 ? uncaught exception: (expected-list #f)
17
18 The first argument to `prepend` can be any type, but fewer than or more than
19 two arguments will raise an exception.
20
21 | (display
22 | (prepend #t))
23 ? uncaught exception: (illegal-arguments (#t))
24
25 | (display
26 | (prepend #f #t #f))
27 ? uncaught exception: (illegal-arguments (#f #t #f))
28
29 'XXX'
0 (define raise (@macro (self args env)
1 (bind-args (e) args env
2 (@raise e))))
3
4 ;'XXX'
5
6 -> Tests for functionality "Interpret Robin Program (with Small)"
7
8 `raise` is a wrapper for the `@raise` intrinsic, for which it provides
9 predictable failure modes. In non-failure modes, `raise` should have
10 semantics identical to `@raise`.
11
12 `@raise`'s single argument may be any kind of value, but `raise` expects
13 exactly one argument.
14
15 | (display
16 | (raise))
17 ? uncaught exception: (illegal-arguments ())
18
19 | (display
20 | (raise 2 3 4))
21 ? uncaught exception: (illegal-arguments (2 3 4))
22
23 'XXX'
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Arith)"
3
4 `remainder` evaluates both of its arguments to numbers and evaluates to the
5 remainder of the division of the first number by the second.
6
7 | (display
8 | (remainder 12 3))
9 = 0
10
11 | (display
12 | (remainder 11 3))
13 = 2
14
15 | (display
16 | (remainder 10 3))
17 = 1
18
19 | (display
20 | (remainder 9 3))
21 = 0
22
23 The remainder is *always positive*.
24
25 | (display
26 | (remainder (subtract 0 10) 3))
27 = 2
28
29 | (display
30 | (remainder 10 (subtract 0 3)))
31 = 2
32
33 Trying to find the remainder of a division by zero is undefined, and an
34 exception will be raised.
35
36 | (display
37 | (remainder 10 0))
38 ? uncaught exception: (division-by-zero 10)
39
40 `remainder` expects exactly two arguments, both numbers.
41
42 | (display
43 | (remainder 14))
44 ? uncaught exception: (illegal-arguments (14))
45
46 | (display
47 | (remainder 14 23 57))
48 ? uncaught exception: (illegal-arguments (14 23 57))
49
50 | (display
51 | (remainder 14 #t))
52 ? uncaught exception: (expected-number #t)
53
54 | (display
55 | (remainder #t 51))
56 ? uncaught exception: (expected-number #t)
57
58 'XXX'
59
60 ;(d is positive)
61 (define remainder-r-pos (fun (self n d acc)
62 (if (> d n)
63 n
64 (self self (subtract n d) d (add 1 acc)))))
65
66 ;(d is negative)
67 (define remainder-r-neg (fun (self n d acc)
68 (if (> (abs d) n)
69 (add 1 n)
70 (self self (add n d) d (add 1 acc)))))
71
72 (define remainder (macro (self args env)
73 (bind-args (n d) args env
74 (if (equal? d 0)
75 (raise (list (literal division-by-zero) n))
76 (if (< n 0)
77 (self (subtract 0 n) (subtract 0 d))
78 (if (> d 0)
79 (remainder-r-pos remainder-r-pos n d 0)
80 (remainder-r-neg remainder-r-neg n d 0)))))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `rest` evaluates its first argument to obtain a non-negative integer,
5 considered to be a desired position, and its second argument to obtain a
6 list. It then evaluates to the suffix of the given list starting at the
7 desired position. The position 0 indicates the beginning of the list.
8
9 | (display
10 | (rest 0 (list 1 2 3 4 5)))
11 = (1 2 3 4 5)
12
13 | (display
14 | (rest 3 (list 1 2 3 4 5)))
15 = (4 5)
16
17 | (display
18 | (rest 5 (list 1 2 3 4 5)))
19 = ()
20
21 | (display
22 | (rest 6 (list 1 2 3 4 5)))
23 ? uncaught exception: (expected-list ())
24
25 | (display
26 | (rest 1 (literal foo)))
27 ? uncaught exception: (expected-list foo)
28
29 | (display
30 | (rest 0 (literal foo)))
31 = foo
32
33 'XXX'
34
35 (define rest (fun (n li)
36 (bind rest-r (fun (self n li)
37 (if (equal? n 0)
38 li
39 (self self (subtract n 1) (tail li))))
40 (rest-r rest-r n li))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `reverse` evaluates its argument to a list, then evaluates to a list which
5 is the same as the given list in every respect except that the order of
6 the elements is reversed.
7
8 | (display
9 | (reverse (literal (1 2 3 4 5))))
10 = (5 4 3 2 1)
11
12 | (display
13 | (reverse (literal fairies-wear-boots)))
14 ? uncaught exception: (expected-list fairies-wear-boots)
15
16 'XXX'
17 (define reverse (fun (li)
18 (fold prepend () li)))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Env)"
3
4 `sandbox` takes a list of identifiers as its first argument, and evaluates
5 its second argument in an environment where all bindings *except* those
6 for the listed identifiers have been unbound.
7
8 | (display
9 | (sandbox (prepend tail)
10 | (tail (prepend 8 (prepend 9 ())))))
11 = (9)
12
13 | (display
14 | (sandbox (prepend tail)
15 | (head (prepend 8 (prepend 9 ())))))
16 ? uncaught exception: (unbound-identifier head)
17
18 'XXX'
19
20 (define sandbox
21 (macro (self args env)
22 (eval (filter (fun (binding) (elem? (head binding) (head args))) env)
23 (head (tail args)))))
0 (define sign (@macro (self args env)
1 (bind-args (n) args env
2 (@sign n))))
3
4 ;'XXX'
5
6 `sign` is a wrapper for the `@sign` intrinsic, for which it provides
7 predictable failure modes. In non-failure modes, `sign` should have
8 semantics identical to `@sign`.
9
10 -> Tests for functionality "Interpret Robin Program (with Small)"
11
12 `sign` expects a number.
13
14 | (display
15 | (sign #f))
16 ? uncaught exception: (expected-number #f)
17
18 | (display
19 | (sign (literal k)))
20 ? uncaught exception: (expected-number k)
21
22 `sign` expects exactly one argument.
23
24 | (display
25 | (sign 100 200 300))
26 ? uncaught exception: (illegal-arguments (100 200 300))
27
28 | (display
29 | (sign))
30 ? uncaught exception: (illegal-arguments ())
31
32 'XXX'
0 (define subtract (@macro (self args env)
1 (bind-args (lhs rhs) args env
2 (@subtract lhs rhs))))
3
4 ;'XXX'
5
6 -> Tests for functionality "Interpret Robin Program (with Small)"
7
8 `subtract` is a wrapper for the `@suibtract` intrinsic, for which it provides
9 predictable failure modes. In non-failure modes, `subtract` should have
10 semantics identical to `@subtract`.
11
12 `subtract` expects both of its arguments to be numbers.
13
14 | (display
15 | (subtract #f 100))
16 ? uncaught exception: (expected-number #f)
17
18 | (display
19 | (subtract 100 ()))
20 ? uncaught exception: (expected-number ())
21
22 `subtract` expects exactly two arguments.
23
24 | (display
25 | (subtract 100 200 300))
26 ? uncaught exception: (illegal-arguments (100 200 300))
27
28 | (display
29 | (subtract))
30 ? uncaught exception: (illegal-arguments ())
31
32 'XXX'
0 (define symbol? (@macro (self args env)
1 (bind-args (s) args env
2 (@symbol? s))))
3
4 ;'XXX'
5
6 -> Tests for functionality "Interpret Robin Program (with Small)"
7
8 `symbol?` is a wrapper for the `@symbol?` intrinsic, for which it provides
9 predictable failure modes. In non-failure modes, `symbol?` should have
10 semantics identical to `@symbol?`.
11
12 The argument to `symbol?` may (naturally) be any type, but there must be
13 exactly one argument.
14
15 | (display
16 | (symbol? 77 88))
17 ? uncaught exception: (illegal-arguments (77 88))
18
19 | (display
20 | (symbol?))
21 ? uncaught exception: (illegal-arguments ())
22
23 'XXX'
0 (define tail (@macro (self args env)
1 (bind-args (l) args env
2 (@tail l))))
3
4 ;'XXX'
5
6 -> Tests for functionality "Interpret Robin Program (with Small)"
7
8 `tail` is a wrapper for the `@tail` intrinsic, for which it provides predictable
9 failure modes. In non-failure modes, `tail` should have semantics identical
10 to `@tail`.
11
12 `tail` expects its argument to be a list.
13
14 | (display
15 | (tail #f))
16 ? uncaught exception: (expected-list #f)
17
18 `tail` expects exactly one argument.
19
20 | (display
21 | (tail (@prepend #t ()) (@prepend #f ())))
22 ? uncaught exception: (illegal-arguments ((@prepend #t ()) (@prepend #f ())))
23
24 | (display
25 | (tail))
26 ? uncaught exception: (illegal-arguments ())
27
28 'XXX'
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with List)"
3
4 `take-while` evaluates its first argument to obtain a predicate and its
5 second argument to obtain a list. It then evaluates to the longest prefix
6 of the list whose elements all satisfy the predicate.
7
8 | (display
9 | (take-while (fun (x) (symbol? x)) (literal (one two 3 4 five 6 seven))))
10 = (one two)
11
12 | (display
13 | (take-while (fun (x) (symbol? x)) (literal (1 2 3 4 five six))))
14 = ()
15
16 | (display
17 | (take-while (fun (x) (number? x)) (literal (1 2 3 4 5 6))))
18 = (1 2 3 4 5 6)
19
20 | (display
21 | (take-while (fun (x) (symbol? x)) ()))
22 = ()
23
24 | (display
25 | (take-while (fun (x) (symbol? x)) #f))
26 ? uncaught exception: (expected-list #f)
27
28 'XXX'
29
30 (define take-while (fun (pred li)
31 (bind take-while-r (fun (self pred li)
32 (if (empty? li)
33 ()
34 (if (pred (head li))
35 (prepend (head li) (self self pred (tail li)))
36 ())))
37 (take-while-r take-while-r pred li))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Env)"
3
4 `unbind` removes the given identifier from the environment and evaluates its
5 second argument in that reduced environment.
6
7 | (display
8 | (unbind if (if #t (literal x) (literal y))))
9 ? uncaught exception: (unbound-identifier if)
10
11 If the identifier doesn't exist in the environment, no change is made to
12 the environment.
13
14 | (display
15 | (unbind yog-sothoth (if #t (literal x) (literal y))))
16 = x
17
18 `unbind` removes all trace of binding from the given identifier; if that
19 identifier has several definitions that are shadowed, none of them will be
20 in effect.
21
22 | (display
23 | (let ((x 7))
24 | (let ((x 8))
25 | (unbind x
26 | x))))
27 ? uncaught exception: (unbound-identifier x)
28
29 'XXX'
30
31 (define unbind
32 (macro (self args env)
33 (eval (filter (fun (binding) (if (equal? (head binding) (head args)) #f #t)) env)
34 (head (tail args)))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Env)"
3
4 `unshadow` is similar to `unbind`, but only removes the latest binding
5 for the given identifier; previously shadowed bindings, if any exist,
6 will be visible instead.
7
8 | (display
9 | (unshadow yog-sothoth (if #t (literal x) (literal y))))
10 = x
11
12 | (display
13 | (unshadow if (if #t (literal x) (literal y))))
14 ? uncaught exception: (unbound-identifier if)
15
16 | (display
17 | (bind if (literal what)
18 | (unshadow if (if #t (literal x) (literal y)))))
19 = x
20
21 | (display
22 | (bind q 400
23 | (unshadow q q)))
24 ? uncaught exception: (unbound-identifier q)
25
26 | (display
27 | (bind q 200
28 | (bind q 400
29 | (unshadow q q))))
30 = 200
31
32 | (display
33 | (bind q 100
34 | (bind q 200
35 | (bind q 400
36 | (unshadow q (unshadow q q))))))
37 = 100
38
39 | (display
40 | (let ((q 100)
41 | (q 200)
42 | (q 400))
43 | (unshadow q (unshadow q q))))
44 = 100
45
46 `unshadow` is something of a gimmick that shows off Robin's ability
47 to manipulate the evaluation environment. In practice, the bindings
48 can be determined lexically, and a different identifier could always
49 be chosen instead.
50
51 'XXX'
52
53 (define unshadow
54 (macro (self args env)
55 (bind remove-binding-r (fun (self id li)
56 (if (empty? li)
57 li
58 (if (equal? (head (head li)) id)
59 (tail li)
60 (prepend (head li) (self self id (tail li))))))
61 (eval (remove-binding-r remove-binding-r (head args) env)
62 (head (tail args))))))
0 ;'XXX'
1
2 -> Tests for functionality "Interpret Robin Program (with Boolean)"
3
4 `xor` evaluates both of its arguments to boolean, then evaluates to
5 the "exclusive-or" of those booleans.
6
7 | (display
8 | (xor #t #t))
9 = #f
10
11 | (display
12 | (xor #t #f))
13 = #t
14
15 | (display
16 | (xor #f #t))
17 = #t
18
19 | (display
20 | (xor #f #f))
21 = #f
22
23 `xor` expects exactly two arguments.
24
25 | (display
26 | (xor #f))
27 ? uncaught exception: (illegal-arguments (#f))
28
29 | (display
30 | (xor #t #f #f))
31 ? uncaught exception: (illegal-arguments (#t #f #f))
32
33 `xor` expects both of its arguments to be booleans.
34
35 | (display
36 | (xor 100 #t))
37 ? uncaught exception: (expected-boolean 100)
38
39 | (display
40 | (xor #t 99))
41 ? uncaught exception: (expected-boolean 99)
42
43 This test demonstrates that these functions really do evaluate their
44 arguments.
45
46 | (display
47 | (and (or (xor (and #t (not (not #t))) #f) #f) #t))
48 = #t
49
50 'XXX'
51
52 (define xor (macro (self args env)
53 (bind-args (a b) args env
54 (or (and a (not b)) (and (not a) b)))))
00 #!/bin/sh
11
2 if [ ! -e bin/robin -a ! -e bin/robin.exe ]; then
3 ./build.sh || exit 1
2 ./build.sh || exit 1
3
4 TESTDOCS1="
5 doc/Robin.markdown
6 doc/Intrinsics.markdown
7 doc/Reactor.markdown
8 "
9
10 if [ "${FIXTURE}x" = "x" ]; then
11 FIXTURE=fixture/whitecap.markdown
412 fi
13 echo "Using fixture $FIXTURE..."
514
6 FILES="doc/Fundamental_Semantics.markdown \
7 doc/module/Core.markdown \
8 doc/module/Small.markdown \
9 doc/module/Exception.markdown \
10 doc/module/Concurrency.markdown \
11 doc/module/Metadata.markdown \
12 doc/module/List.markdown \
13 doc/module/Term.markdown \
14 doc/module/Environment.markdown \
15 doc/module/Boolean.markdown \
16 doc/module/Arithmetic.markdown \
17 doc/module/Random.markdown \
18 doc/module/Assert.markdown \
19 doc/module/Pure.markdown \
20 doc/module/CrudeIO.markdown \
21 doc/module/Miscellany.markdown \
22 doc/module/Bind-Args.markdown"
15 echo "Running tests on core semantics..."
16 falderal -b $FIXTURE $TESTDOCS1 || exit 1
2317
24 FILES_NO_BUILTIN_SMALL="doc/module/Small.markdown"
18 for PACKAGE in small intrinsics-wrappers fun boolean arith list env misc; do
19 echo "Running tests on '$PACKAGE' package..."
20 falderal -b $FIXTURE pkg/$PACKAGE.robin || exit 1
21 done
2522
26 falderal test -b fixture/config/BuiltInSmall.markdown ${FILES}
27 falderal test -b fixture/config/SmallInRobin.markdown ${FILES_NO_BUILTIN_SMALL}
23 rm -f config.markdown