diff options
Diffstat (limited to 'lore/Language')
-rw-r--r-- | lore/Language/Bs/Cli.hs | 7 | ||||
-rw-r--r-- | lore/Language/Bs/Eval.hs | 24 | ||||
-rw-r--r-- | lore/Language/Bs/Parser.hs | 22 | ||||
-rw-r--r-- | lore/Language/Bs/Primitives.hs | 12 | ||||
-rw-r--r-- | lore/Language/Bs/Repl.hs | 9 |
5 files changed, 45 insertions, 29 deletions
diff --git a/lore/Language/Bs/Cli.hs b/lore/Language/Bs/Cli.hs index eddb97d..4c48c86 100644 --- a/lore/Language/Bs/Cli.hs +++ b/lore/Language/Bs/Cli.hs @@ -1,13 +1,16 @@ {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE NoImplicitPrelude #-} module Language.Bs.Cli ( run ) where +import Data.String +import Data.Text.IO as TIO import Language.Bs.Eval -- evalFile :: T.Text -> IO () import Language.Bs.Repl -- Repl.mainLoop :: IO () -import System.Directory -import Data.Text.IO as TIO import Options.Applicative +import Protolude +import System.Directory -- SOURCES --http://book.realworldhaskell.org/read/io.html diff --git a/lore/Language/Bs/Eval.hs b/lore/Language/Bs/Eval.hs index 8246d7b..8495b88 100644 --- a/lore/Language/Bs/Eval.hs +++ b/lore/Language/Bs/Eval.hs @@ -2,26 +2,29 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE NoImplicitPrelude #-} module Language.Bs.Eval ( - evalText, - evalFile, - runParseTest, - safeExec, - runASTinEnv, - basicEnv, - fileToEvalForm, - textToEvalForm, - getFileContents + evalText +, evalFile +, runParseTest +, safeExec +, runASTinEnv +, basicEnv +, fileToEvalForm +, textToEvalForm +, getFileContents ) where import Control.Exception import Control.Monad.Reader -import Data.Map as Map +import qualified Data.Map as Map +import Data.String import qualified Data.Text as T import qualified Data.Text.IO as TIO import Language.Bs.Expr import Language.Bs.Parser import Language.Bs.Primitives +import Protolude import System.Directory import Text.Parsec @@ -131,6 +134,7 @@ applyFunc expr params args = bindArgsEval params args expr bindArgsEval :: [Expr] -> [Expr] -> Expr -> Eval Expr bindArgsEval params args expr = do Env{..} <- ask + let newVars = zipWith (\a b -> (extractVar a,b)) params args let (newEnv, newFenv) = Map.partition (not . isFunc) $ Map.fromList newVars local (const $ Env (newEnv <> env) (newFenv <> fenv)) $ eval expr diff --git a/lore/Language/Bs/Parser.hs b/lore/Language/Bs/Parser.hs index 6e004ef..3044a60 100644 --- a/lore/Language/Bs/Parser.hs +++ b/lore/Language/Bs/Parser.hs @@ -1,19 +1,23 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE NoImplicitPrelude #-} module Language.Bs.Parser ( - readExpr, - readExprFile + readExpr +, readExprFile ) where +import Control.Monad (fail) +import Control.Monad (mzero) +import Data.Char (digitToInt) +import Data.Functor.Identity (Identity) +import Data.String +import qualified Data.Text as T import Language.Bs.Expr +import Protolude hiding ((<|>), try) import Text.Parsec +import qualified Text.Parsec.Language as Lang import Text.Parsec.Text import qualified Text.Parsec.Token as Tok -import qualified Text.Parsec.Language as Lang -import Data.Functor.Identity (Identity) -import qualified Data.Text as T -import Data.Char (digitToInt) -import Control.Monad (mzero) lexer :: Tok.GenTokenParser T.Text () Identity lexer = Tok.makeTokenParser style @@ -67,8 +71,8 @@ decimal = Tok.decimal lexer -- Copied from Text.Parsec.Token sign :: Parser (Integer -> Integer) sign = char '-' *> return negate - <|> char '+' *> return id - <|> return id + <|> char '+' *> return identity + <|> return identity intRadix :: Radix -> Parser Integer intRadix r = sign <*> numberWithRadix r diff --git a/lore/Language/Bs/Primitives.hs b/lore/Language/Bs/Primitives.hs index 2c90164..6042b82 100644 --- a/lore/Language/Bs/Primitives.hs +++ b/lore/Language/Bs/Primitives.hs @@ -1,4 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE NoImplicitPrelude #-} -- | bs primitives -- -- I would like to reduce the number of primitives in the language to some @@ -13,6 +14,7 @@ import Data.Text as T import Data.Text.IO as TIO import Language.Bs.Expr import Network.HTTP +import Protolude import System.Directory import System.IO @@ -51,7 +53,7 @@ primEnv = [ , ("file?" , mkF $ unop fileExists) , ("slurp" , mkF $ unop slurp) , ("wslurp" , mkF $ unop wSlurp) - , ("put" , mkF $ binop put) + , ("put" , mkF $ binop put_) ] unop :: Unary -> [Expr] -> Eval Expr @@ -91,10 +93,10 @@ readTextFile fileName handle = do then (TIO.hGetContents handle) >>= (return . Tape) else throw $ ReadFileError $ T.concat [" file does not exist: ", fileName] -put :: Expr -> Expr -> Eval Expr -put (Tape file) (Tape msg) = liftIO $ wFilePut file msg -put (Tape _) val = throw $ TypeMismatch "put expects string in the second argument (try using show), instead got: " val -put val _ = throw $ TypeMismatch "put expects string, instead got: " val +put_ :: Expr -> Expr -> Eval Expr +put_ (Tape file) (Tape msg) = liftIO $ wFilePut file msg +put_ (Tape _) val = throw $ TypeMismatch "put expects string in the second argument (try using show), instead got: " val +put_ val _ = throw $ TypeMismatch "put expects string, instead got: " val wFilePut :: T.Text -> T.Text -> IO Expr wFilePut fileName msg = withFile (T.unpack fileName) WriteMode go diff --git a/lore/Language/Bs/Repl.hs b/lore/Language/Bs/Repl.hs index bd8acca..35e473f 100644 --- a/lore/Language/Bs/Repl.hs +++ b/lore/Language/Bs/Repl.hs @@ -1,11 +1,14 @@ {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE NoImplicitPrelude #-} module Language.Bs.Repl ( - mainLoop, +mainLoop ) where -import Language.Bs.Eval -import Data.Text as T import Control.Monad.Trans +import Data.String +import Data.Text as T +import Language.Bs.Eval +import Protolude import System.Console.Haskeline type Repl a = InputT IO a |