git @ Cat's Eye Technologies Robin / 6d51b9b
No need for Either in World results. Chris Pressey 5 years ago
3 changed file(s) with 12 addition(s) and 19 deletion(s). Raw diff Collapse all Expand all
2626 Left problem -> do
2727 setProp resultElem "textContent" $ show $ problem
2828 showResults results =
29 (foldl (\a x -> x ++ "\n" ++ a) "" (map (showResult) results))
30 showResult (Right result) = show result
31 showResult (Left result) = "uncaught exception: " ++ (show result)
29 (foldl (\a x -> x ++ "\n" ++ a) "" (map (show) results))
44 import System.IO
55 import System.Exit
66
7 import Language.Robin.Expr (Expr(List, Symbol))
7 import Language.Robin.Expr (Expr(List, Symbol, Abort))
88 import Language.Robin.Parser (parseToplevel, parseExpr)
99 import Language.Robin.Intrinsics (robinIntrinsics)
1010 import Language.Robin.TopLevel (initialWorld, destructureWorld, collect, secondaryDefs)
4949
5050
5151 writeResults [] = return ()
52 writeResults ((Right result):results) = do
52 writeResults (expr@(Abort _):results) =
53 abortWith $ show expr
54 writeResults (result:results) = do
5355 putStrLn $ show result
5456 writeResults results
55 writeResults ((Left expr):results) =
56 abortWith $ show expr
00 module Language.Robin.TopLevel where
11
2 import Prelude (show, id, fromIntegral, length, ($), (++), Bool(False), Maybe(Just, Nothing), Either(Left, Right))
2 import Prelude (show, id, fromIntegral, length, ($), (++), Bool(False), Maybe(Just, Nothing))
33
44 import Language.Robin.Expr
55 import Language.Robin.Env (Env, find, insert, empty)
1111 env :: Env,
1212 secondaryDefs :: Env,
1313 reactors :: [Reactor.Reactor],
14 results :: [Either Expr Expr]
14 results :: [Expr]
1515 }
1616
1717 assertionFailed expr =
3232 collect [] result = result
3333
3434 collect ((List [Symbol "display", expr]):rest) world@World{ env=env, results=results } =
35 let
36 result = case eval env expr id of
37 Abort expr -> Left (Abort expr)
38 other -> Right other
39 in
40 collect rest world{ results=(result:results) }
35 collect rest world{ results=((eval env expr id):results) }
4136
4237 collect ((List [Symbol "assert", expr]):rest) world@World{ env=env, results=results } =
4338 case eval env expr id of
4439 Abort expr ->
45 world{ results=((Left (Abort expr)):results) }
40 world{ results=((Abort expr):results) }
4641 Boolean False ->
47 world{ results=((Left (Abort $ assertionFailed expr)):results) }
42 world{ results=((Abort $ assertionFailed expr):results) }
4843 _ ->
4944 collect rest world
5045
5146 collect ((List [Symbol "require", sym@(Symbol s)]):rest) world@World{ env=env, results=results } =
5247 case find s env of
5348 Nothing ->
54 world{ results=((Left (Abort $ assertionFailed (List [Symbol "bound?", sym]))):results) }
49 world{ results=((Abort $ assertionFailed (List [Symbol "bound?", sym])):results) }
5550 _ ->
5651 collect rest world
5752
7772 collect rest world{ reactors=(newReactor:reactors) }
7873
7974 collect (expr:rest) world@World{ results=results } =
80 world{ results=((Left (Abort $ illegalTopLevel expr)):results) }
75 world{ results=((Abort $ illegalTopLevel expr):results) }