diff options
-rw-r--r-- | bin/Main.hs | 8 | ||||
-rw-r--r-- | lisk.cabal | 1 | ||||
-rw-r--r-- | src/Environment.hs | 4 | ||||
-rw-r--r-- | src/Error/Base.hs | 2 | ||||
-rw-r--r-- | src/Evaluator.hs | 3 | ||||
-rw-r--r-- | src/Operators.hs | 2 | ||||
-rw-r--r-- | src/Parser.hs | 29 |
7 files changed, 13 insertions, 36 deletions
diff --git a/bin/Main.hs b/bin/Main.hs index 18e1c53..3d9fad4 100644 --- a/bin/Main.hs +++ b/bin/Main.hs | |||
@@ -1,5 +1,6 @@ | |||
1 | module Main where | 1 | module Main where |
2 | 2 | ||
3 | import Base (Expr (..)) | ||
3 | import Control.Monad (liftM) | 4 | import Control.Monad (liftM) |
4 | import Control.Monad.Except (liftIO, runExceptT, throwError) | 5 | import Control.Monad.Except (liftIO, runExceptT, throwError) |
5 | import Environment | 6 | import Environment |
@@ -7,7 +8,7 @@ import Error.Base (LispError (..), LispResult (..), | |||
7 | unwrap) | 8 | unwrap) |
8 | import Error.Pretty (defaults, showError) | 9 | import Error.Pretty (defaults, showError) |
9 | import Evaluator (eval) | 10 | import Evaluator (eval) |
10 | import Parser (Expr (..), parseLispValue) | 11 | import Parser (parseLispValue) |
11 | import System.Console.Readline | 12 | import System.Console.Readline |
12 | import System.Environment (getArgs) | 13 | import System.Environment (getArgs) |
13 | import Text.ParserCombinators.Parsec | 14 | import Text.ParserCombinators.Parsec |
@@ -29,7 +30,10 @@ repl env = do | |||
29 | case inp of | 30 | case inp of |
30 | Nothing -> return () | 31 | Nothing -> return () |
31 | Just ",q" -> return () | 32 | Just ",q" -> return () |
32 | Just i -> evalExpr env i >>= either (putStrLn . pp i) putStrLn >> repl env | 33 | Just i -> do |
34 | addHistory i | ||
35 | evalExpr env i >>= either (putStrLn . pp i) putStrLn | ||
36 | repl env | ||
33 | 37 | ||
34 | 38 | ||
35 | main :: IO () | 39 | main :: IO () |
@@ -24,6 +24,7 @@ library | |||
24 | parsec == 3.*, | 24 | parsec == 3.*, |
25 | mtl >= 2.1 | 25 | mtl >= 2.1 |
26 | exposed-modules: | 26 | exposed-modules: |
27 | Base, | ||
27 | Parser, | 28 | Parser, |
28 | Evaluator, | 29 | Evaluator, |
29 | Operators, | 30 | Operators, |
diff --git a/src/Environment.hs b/src/Environment.hs index 4c444b6..b7b7ee6 100644 --- a/src/Environment.hs +++ b/src/Environment.hs | |||
@@ -8,15 +8,13 @@ module Environment ( Env | |||
8 | , IOResult | 8 | , IOResult |
9 | ) where | 9 | ) where |
10 | 10 | ||
11 | import Base (Env (..), Expr (..)) | ||
11 | import Control.Applicative ((<$>)) | 12 | import Control.Applicative ((<$>)) |
12 | import Control.Monad (mapM) | 13 | import Control.Monad (mapM) |
13 | import Control.Monad.Except | 14 | import Control.Monad.Except |
14 | import Data.IORef | 15 | import Data.IORef |
15 | import Data.Maybe (isJust) | 16 | import Data.Maybe (isJust) |
16 | import Error.Base (LispError (..), LispResult (..), unwrap) | 17 | import Error.Base (LispError (..), LispResult (..), unwrap) |
17 | import Parser (Expr (..)) | ||
18 | |||
19 | type Env = IORef [(String, IORef Expr)] | ||
20 | 18 | ||
21 | newEnv :: IO Env | 19 | newEnv :: IO Env |
22 | newEnv = newIORef [] | 20 | newEnv = newIORef [] |
diff --git a/src/Error/Base.hs b/src/Error/Base.hs index 747904a..008a2fc 100644 --- a/src/Error/Base.hs +++ b/src/Error/Base.hs | |||
@@ -3,8 +3,8 @@ module Error.Base ( LispError (..) | |||
3 | , unwrap | 3 | , unwrap |
4 | ) where | 4 | ) where |
5 | 5 | ||
6 | import Base (Expr (..)) | ||
6 | import Control.Monad.Except | 7 | import Control.Monad.Except |
7 | import Parser | ||
8 | import Text.Parsec | 8 | import Text.Parsec |
9 | import Text.Parsec.Error | 9 | import Text.Parsec.Error |
10 | import Text.ParserCombinators.Parsec | 10 | import Text.ParserCombinators.Parsec |
diff --git a/src/Evaluator.hs b/src/Evaluator.hs index 9e6632e..3bc1e09 100644 --- a/src/Evaluator.hs +++ b/src/Evaluator.hs | |||
@@ -1,5 +1,6 @@ | |||
1 | module Evaluator (eval) where | 1 | module Evaluator (eval) where |
2 | 2 | ||
3 | import Base | ||
3 | import Control.Applicative ((*>)) | 4 | import Control.Applicative ((*>)) |
4 | import Control.Arrow ((&&&)) | 5 | import Control.Arrow ((&&&)) |
5 | import Control.Monad.Except | 6 | import Control.Monad.Except |
@@ -7,7 +8,6 @@ import Environment | |||
7 | import Error.Base (LispError (..), LispResult (..), | 8 | import Error.Base (LispError (..), LispResult (..), |
8 | unwrap) | 9 | unwrap) |
9 | import Operators | 10 | import Operators |
10 | import Parser | ||
11 | import Text.ParserCombinators.Parsec | 11 | import Text.ParserCombinators.Parsec |
12 | 12 | ||
13 | apply :: String -> [Expr] -> LispResult Expr | 13 | apply :: String -> [Expr] -> LispResult Expr |
@@ -20,6 +20,7 @@ evalUnquoteSplicing :: Env -> Expr -> IOResult Expr | |||
20 | evalUnquoteSplicing env (List xs) = List <$> mapM (eval env) xs | 20 | evalUnquoteSplicing env (List xs) = List <$> mapM (eval env) xs |
21 | evalUnquoteSplicing env literal = return literal | 21 | evalUnquoteSplicing env literal = return literal |
22 | 22 | ||
23 | -- might be worth including unquote and unquote-splicing in lisk's prelude | ||
23 | evalUnquote :: Env -> Expr -> IOResult Expr | 24 | evalUnquote :: Env -> Expr -> IOResult Expr |
24 | evalUnquote env (DottedList h t) = List . (:[]) <$> liftM2 DottedList (mapM (evalUnquote env) h) (evalUnquote env t) | 25 | evalUnquote env (DottedList h t) = List . (:[]) <$> liftM2 DottedList (mapM (evalUnquote env) h) (evalUnquote env t) |
25 | evalUnquote env (Vector vs) = List . (:[]) . Vector <$> mapM (evalUnquote env) vs | 26 | evalUnquote env (Vector vs) = List . (:[]) . Vector <$> mapM (evalUnquote env) vs |
diff --git a/src/Operators.hs b/src/Operators.hs index fa39e23..bab888d 100644 --- a/src/Operators.hs +++ b/src/Operators.hs | |||
@@ -1,8 +1,8 @@ | |||
1 | module Operators (primitives) where | 1 | module Operators (primitives) where |
2 | 2 | ||
3 | import Base | ||
3 | import Control.Monad.Except | 4 | import Control.Monad.Except |
4 | import Error.Base (LispError (..), LispResult (..)) | 5 | import Error.Base (LispError (..), LispResult (..)) |
5 | import Parser | ||
6 | 6 | ||
7 | primitives :: [(String, [Expr] -> LispResult Expr)] | 7 | primitives :: [(String, [Expr] -> LispResult Expr)] |
8 | primitives = map (\(n, f) -> (n, f n)) | 8 | primitives = map (\(n, f) -> (n, f n)) |
diff --git a/src/Parser.hs b/src/Parser.hs index f83f4cc..94de680 100644 --- a/src/Parser.hs +++ b/src/Parser.hs | |||
@@ -1,5 +1,4 @@ | |||
1 | module Parser ( parseLispValue | 1 | module Parser ( parseLispValue |
2 | , Expr(..) | ||
3 | , parseString | 2 | , parseString |
4 | , parseInt | 3 | , parseInt |
5 | , parseFloat | 4 | , parseFloat |
@@ -7,22 +6,10 @@ module Parser ( parseLispValue | |||
7 | , parseQuote | 6 | , parseQuote |
8 | ) where | 7 | ) where |
9 | 8 | ||
9 | import Base (Expr (..), Function) | ||
10 | import Control.Applicative ((<$>)) | 10 | import Control.Applicative ((<$>)) |
11 | import Text.ParserCombinators.Parsec | 11 | import Text.ParserCombinators.Parsec |
12 | 12 | ||
13 | -- TODO: use LispNumber (src/Operators.hs) here instead of IntLiteral and FloatLiteral | ||
14 | -- TODO: add character literals: \#a \#b \#c \#space \#newline | ||
15 | -- TODO: add support for complex numbers, oct and hex numbers | ||
16 | data Expr = List [Expr] | ||
17 | | Vector [Expr] | ||
18 | | DottedList [Expr] Expr | ||
19 | | StringLiteral String | ||
20 | | IntLiteral Integer | ||
21 | | FloatLiteral Double | ||
22 | | BoolLiteral Bool | ||
23 | | Id String | ||
24 | deriving (Eq) | ||
25 | |||
26 | -- backslash double quote escapes a quote inside strings | 13 | -- backslash double quote escapes a quote inside strings |
27 | quotedChar = noneOf ['\"'] <|> try (string "\\\"" >> return '"') | 14 | quotedChar = noneOf ['\"'] <|> try (string "\\\"" >> return '"') |
28 | 15 | ||
@@ -92,7 +79,6 @@ parseQuote = parseModifier "'" "quote" | |||
92 | parseQuasiquote = parseModifier "`" "quasiquote" | 79 | parseQuasiquote = parseModifier "`" "quasiquote" |
93 | parseUnquote = parseModifier "," "unquote" | 80 | parseUnquote = parseModifier "," "unquote" |
94 | parseUnquoteSplicing = parseModifier ",@" "unquote-splicing" | 81 | parseUnquoteSplicing = parseModifier ",@" "unquote-splicing" |
95 | -- TODO: add modifier for unquote splicing: ,@ | ||
96 | 82 | ||
97 | parseLispValue :: Parser Expr | 83 | parseLispValue :: Parser Expr |
98 | parseLispValue = | 84 | parseLispValue = |
@@ -114,16 +100,3 @@ parseLispValue = | |||
114 | return $ maybe (List x) (DottedList x) t | 100 | return $ maybe (List x) (DottedList x) t |
115 | <?> "lisp value" | 101 | <?> "lisp value" |
116 | 102 | ||
117 | showLispList :: [Expr] -> String | ||
118 | showLispList = unwords . map show | ||
119 | |||
120 | instance Show Expr where | ||
121 | show (DottedList xs x) = "(" ++ showLispList xs ++ " . " ++ show x ++ ")" | ||
122 | show (List xs) = "(" ++ showLispList xs ++ ")" | ||
123 | show (Vector xs) = "#(" ++ showLispList xs ++ ")" | ||
124 | show (StringLiteral s) = "\"" ++ s ++ "\"" | ||
125 | show (IntLiteral n) = show n | ||
126 | show (FloatLiteral n) = show n | ||
127 | show (BoolLiteral True) = "#t" | ||
128 | show (BoolLiteral False) = "#f" | ||
129 | show (Id i) = i | ||