forked from kanaka/mal
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathstepA_mal.hs
225 lines (185 loc) · 7.84 KB
/
stepA_mal.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
import System.IO (hFlush, stdout)
import System.Environment (getArgs)
import Control.Monad ((<=<))
import Control.Monad.Except (runExceptT)
import Control.Monad.Trans (liftIO)
import Data.Foldable (foldlM, foldrM)
import Readline (addHistory, readline, load_history)
import Types
import Reader (read_str)
import Printer (_pr_str)
import Env (env_new, env_bind, env_get, env_set)
import Core (ns)
-- read
mal_read :: String -> IOThrows MalVal
mal_read = read_str
-- eval
-- starts-with is replaced with pattern matching.
qqIter :: Env -> MalVal -> [MalVal] -> IOThrows [MalVal]
qqIter env (MalSeq _ (Vect False) [MalSymbol "splice-unquote", x]) acc = do
evaluated <- eval env x
case evaluated of
MalSeq _ (Vect False) xs -> return $ xs ++ acc
_ -> throwStr "invalid splice-unquote argument"
qqIter _ (MalSeq _ (Vect False) (MalSymbol "splice-unquote" : _)) _ = throwStr "invalid splice-unquote"
qqIter env x acc = (: acc) <$> quasiquote x env
quasiquote :: MalVal -> Env -> IOThrows MalVal
quasiquote (MalSeq _ (Vect False) [MalSymbol "unquote", x]) env = eval env x
-- FIXME This line
quasiquote (MalSeq m _ ys) env = MalSeq m (Vect False) <$> foldrM (qqIter env) [] ys
-- is adapted to broken tests. It should be:
-- quasiquote (MalSeq m v ys) env = MalSeq m v <$> foldrM (qqIter env) [] ys
quasiquote ast _ = return ast
-- is-macro-call is replaced with pattern matching.
macroexpand :: Env -> MalVal -> IOThrows MalVal
macroexpand env ast@(MalSeq _ (Vect False) (MalSymbol a0 : args)) = do
maybeMacro <- liftIO $ env_get env a0
case maybeMacro of
Just (MalFunction {fn=f, macro=True}) -> macroexpand env =<< f args
_ -> return ast
macroexpand _ ast = return ast
-- eval_ast is replaced with pattern matching.
let_bind :: Env -> [MalVal] -> IOThrows ()
let_bind _ [] = return ()
let_bind env (MalSymbol b : e : xs) = do
liftIO . env_set env b =<< eval env e
let_bind env xs
let_bind _ _ = throwStr "invalid let*"
unWrapSymbol :: MalVal -> IOThrows String
unWrapSymbol (MalSymbol s) = return s
unWrapSymbol _ = throwStr "fn* parameter must be symbols"
newFunction :: MalVal -> Env -> [String] -> MalVal
newFunction a env p = MalFunction {f_ast=a, f_params=p, macro=False, meta=Nil,
fn=(\args -> do
fn_env <- liftIO $ env_new env
ok <- liftIO $ env_bind fn_env p args
case ok of
True -> eval fn_env a
False -> throwStr $ "actual parameters do not match signature " ++ show p)}
apply_ast :: [MalVal] -> Env -> IOThrows MalVal
apply_ast [] _ = return $ toList []
apply_ast [MalSymbol "def!", MalSymbol a1, a2] env = do
evd <- eval env a2
liftIO $ env_set env a1 evd
return evd
apply_ast (MalSymbol "def!" : _) _ = throwStr "invalid def!"
apply_ast [MalSymbol "let*", MalSeq _ _ params, a2] env = do
let_env <- liftIO $ env_new env
let_bind let_env params
eval let_env a2
apply_ast (MalSymbol "let*" : _) _ = throwStr "invalid let*"
apply_ast [MalSymbol "quote", a1] _ = return a1
apply_ast (MalSymbol "quote" : _) _ = throwStr "invalid quote"
apply_ast [MalSymbol "quasiquote", a1] env = quasiquote a1 env
apply_ast (MalSymbol "quasiquote" : _) _ = throwStr "invalid quasiquote"
apply_ast [MalSymbol "defmacro!", MalSymbol a1, a2] env = do
func <- eval env a2
case func of
MalFunction {macro=False} -> do
let m = func {macro=True}
liftIO $ env_set env a1 m
return m
_ -> throwStr "defmacro! on non-function"
apply_ast (MalSymbol "defmacro!" : _) _ = throwStr "invalid defmacro!"
apply_ast [MalSymbol "macroexpand", a1] env = macroexpand env a1
apply_ast (MalSymbol "macroexpand" : _) _ = throwStr "invalid macroexpand"
apply_ast [MalSymbol "try*", a1] env = eval env a1
apply_ast [MalSymbol "try*", a1, MalSeq _ (Vect False) [MalSymbol "catch*", MalSymbol a21, a22]] env = do
res <- liftIO $ runExceptT $ eval env a1
case res of
Right val -> return val
Left exc -> do
try_env <- liftIO $ env_new env
liftIO $ env_set try_env a21 exc
eval try_env a22
apply_ast (MalSymbol "try*" : _) _ = throwStr "invalid try*"
apply_ast (MalSymbol "do" : args) env = foldlM (const $ eval env) Nil args
apply_ast [MalSymbol "if", a1, a2, a3] env = do
cond <- eval env a1
eval env $ case cond of
Nil -> a3
MalBoolean False -> a3
_ -> a2
apply_ast [MalSymbol "if", a1, a2] env = do
cond <- eval env a1
case cond of
Nil -> return Nil
MalBoolean False -> return Nil
_ -> eval env a2
apply_ast (MalSymbol "if" : _) _ = throwStr "invalid if"
apply_ast [MalSymbol "fn*", MalSeq _ _ params, ast] env = newFunction ast env <$> mapM unWrapSymbol params
apply_ast (MalSymbol "fn*" : _) _ = throwStr "invalid fn*"
apply_ast ast env = do
evd <- mapM (eval env) ast
case evd of
MalFunction {fn=f, macro=False} : args -> f args
_ -> throwStr . (++) "invalid apply: " =<< liftIO (Printer._pr_str True (toList ast))
eval :: Env -> MalVal -> IOThrows MalVal
eval env ast = do
newAst <- macroexpand env ast
case newAst of
MalSymbol sym -> do
maybeVal <- liftIO $ env_get env sym
case maybeVal of
Nothing -> throwStr $ "'" ++ sym ++ "' not found"
Just val -> return val
MalSeq _ (Vect False) xs -> apply_ast xs env
MalSeq m (Vect True) xs -> MalSeq m (Vect True) <$> mapM (eval env) xs
MalHashMap m xs -> MalHashMap m <$> mapM (eval env) xs
_ -> return newAst
-- print
mal_print :: MalVal -> IOThrows String
mal_print = liftIO. Printer._pr_str True
-- repl
rep :: Env -> String -> IOThrows String
rep env = mal_print <=< eval env <=< mal_read
repl_loop :: Env -> IO ()
repl_loop env = do
line <- readline "user> "
case line of
Nothing -> return ()
Just "" -> repl_loop env
Just str -> do
addHistory str
res <- runExceptT $ rep env str
out <- case res of
Left mv -> (++) "Error: " <$> liftIO (Printer._pr_str True mv)
Right val -> return val
putStrLn out
hFlush stdout
repl_loop env
-- Read and evaluate a line. Ignore successful results, but crash in
-- case of error. This is intended for the startup procedure.
re :: Env -> String -> IO ()
re repl_env line = do
res <- runExceptT $ eval repl_env =<< mal_read line
case res of
Left mv -> error . (++) "Startup failed: " <$> Printer._pr_str True mv
Right _ -> return ()
defBuiltIn :: Env -> (String, Fn) -> IO ()
defBuiltIn env (sym, f) =
env_set env sym $ MalFunction {fn=f, f_ast=Nil, f_params=[], macro=False, meta=Nil}
evalFn :: Env -> Fn
evalFn env [ast] = eval env ast
evalFn _ _ = throwStr "illegal call of eval"
main :: IO ()
main = do
args <- getArgs
load_history
repl_env <- env_new []
-- core.hs: defined using Haskell
mapM_ (defBuiltIn repl_env) Core.ns
defBuiltIn repl_env ("eval", evalFn repl_env)
-- core.mal: defined using the language itself
re repl_env "(def! *host-language* \"haskell\")"
re repl_env "(def! not (fn* (a) (if a false true)))"
re repl_env "(def! load-file (fn* (f) (eval (read-string (str \"(do \" (slurp f) \"\nnil)\")))))"
re repl_env "(defmacro! cond (fn* (& xs) (if (> (count xs) 0) (list 'if (first xs) (if (> (count xs) 1) (nth xs 1) (throw \"odd number of forms to cond\")) (cons 'cond (rest (rest xs)))))))"
case args of
script : scriptArgs -> do
env_set repl_env "*ARGV*" $ toList $ MalString <$> scriptArgs
re repl_env $ "(load-file \"" ++ script ++ "\")"
[] -> do
env_set repl_env "*ARGV*" $ toList []
re repl_env "(println (str \"Mal [\" *host-language* \"]\"))"
repl_loop repl_env