git @ Cat's Eye Technologies Robin / 6118af4
Add (crude and built-in for now) `random` module. Cat's Eye Technologies 13 years ago
6 changed file(s) with 58 addition(s) and 7 deletion(s). Raw diff Collapse all Expand all
1616 > import Robin.Concurrency
1717 > import Robin.Exception
1818 > import Robin.CrudeIO
19 > import Robin.Random
1920
2021 Module Loading
2122 --------------
2526 > (("small",0,1), moduleSmall),
2627 > (("concurrency",0,1), moduleConcurrency),
2728 > (("exception",0,1), moduleException),
28 > (("crude-io",0,1), moduleCrudeIO)
29 > (("crude-io",0,1), moduleCrudeIO),
30 > (("random",0,1), moduleRandom)
2931 > ]
3032
3133 > loadModule :: [String] -> String -> Integer -> Integer -> IO Expr
135135 * Document the `env` module, and add some more macros to it,
136136 particularly `binding-for` and `unshadow`.
137137
138 * Write a `random` module which exports a process which can be asked
139 (via a message) to send back a random number in a given range.
140
141138 * Write a `timer` module which exports a process which can be asked
142139 (via a message) to send back a message after a given time has passed.
143140 This could be used to build a version of `recv` which can time out.
6969 > robinTrunc env ienv (Pair expr Null) cc = do
7070 > eval env ienv expr (\x ->
7171 > case x of
72 > Number xv -> cc $ Number (((numerator xv) `div` (denominator xv)) % 1)
72 > Number xv -> cc $ Number (trunc xv % 1)
7373 > other -> raise ienv (Pair (Symbol "expected-number") other))
7474 > robinTrunc env ienv other cc = raise ienv (Pair (Symbol "illegal-arguments") other)
75
76 > trunc x = numerator x `div` denominator x
7577
7678 > robinSign env ienv (Pair expr Null) cc = do
7779 > eval env ienv expr (\x ->
00 > module Robin.CrudeIO where
11
2 > import Control.Concurrent (forkIO, myThreadId)
32 > import Robin.Chan
4
53 > import Robin.Expr
64 > import qualified Robin.Env as Env
75 > import Robin.Parser
0 > module Robin.Random where
1
2 > import Data.Ratio
3 > import System.Random (randomRIO)
4
5 > import Robin.Chan
6 > import Robin.Expr
7 > import qualified Robin.Env as Env
8
9 > import Robin.Core (trunc)
10 > import Robin.Concurrency (spawn, getChan)
11
12 Random
13 ======
14
15 This module could be written in Robin, but solely for my convenience,
16 it is written in Haskell for now.
17
18 > handler :: Chan Expr -> IO ()
19
20 > handler chan = do
21 > message <- readChan chan
22 > let (Pair sender (Pair (Number low) (Pair (Number high) Null))) = message
23 > x <- randomRIO ((trunc low), (trunc high))
24 > writeChan (getChan sender) $ Number (x % 1)
25 > handler chan
26
27 Module Definition
28 -----------------
29
30 > moduleRandom :: IO Expr
31
32 TODO: only start the thread if it hasn't been started already.
33 This is where we could use module caching.
34
35 > moduleRandom = do
36 > randomPid <- spawn handler
37 > return $ Env.fromList (
38 > [
39 > ("random", randomPid)
40 > ])
0 (robin (0 . 1) (small (0 . 1) list (0 . 1) concurrency (0 . 1) crude-io (0 . 1) random (0 . 1))
1 (bind output-loop
2 (fun (self n)
3 (if (equal? n 0)
4 (literal done)
5 (send random (list (myself) 1 6)
6 (recv value
7 (send crude-output (pair (myself) value)
8 (recv response
9 (self self (subtract n 1))))))))
10 (output-loop output-loop 20)))