diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Eval.hs | 4 | ||||
-rw-r--r-- | src/Helper.hs | 12 | ||||
-rw-r--r-- | src/Parser.hs | 12 |
3 files changed, 24 insertions, 4 deletions
diff --git a/src/Eval.hs b/src/Eval.hs index 7cf598b..3a1b0c1 100644 --- a/src/Eval.hs +++ b/src/Eval.hs @@ -137,7 +137,7 @@ evalInstruction (ContextualInstruction instr inp) s@(EnvState env) rec conf = ca <> (show e') <> "\n*> " <> (show reduced) - <> (if likeTernary reduced + <> (if likeTernary reduced -- TODO: Also sugar string/char then "\t(" <> (show $ ternaryToDecimal reduced) <> ")" else "" ) @@ -255,5 +255,5 @@ evalMain = do exec path (try . Byte.readFile) (fromBitString . Bit.bitString) ["-E", path] -> exec path (try . readFile) id ['-' : _] -> usage - [path ] -> evalFile path putStrLn decodeStdout + [path ] -> evalFile path putStr decodeStdout _ -> usage diff --git a/src/Helper.hs b/src/Helper.hs index 160ca9a..d653319 100644 --- a/src/Helper.hs +++ b/src/Helper.hs @@ -8,6 +8,7 @@ module Helper where import qualified Control.Monad.State as S import qualified Data.BitString as Bit import qualified Data.ByteString as Byte +import qualified Data.ByteString.Char8 as C import Data.List import Text.Megaparsec @@ -136,8 +137,15 @@ encodeBytes bytes = listify $ map (encodeByte . Bit.toList . Bit.bitString . Byte.pack . (: [])) (Byte.unpack bytes) +stringToExpression :: String -> Expression +stringToExpression = encodeBytes . C.pack + +charToExpression :: Char -> Expression +charToExpression ch = encodeByte $ Bit.toList $ Bit.bitString $ C.pack [ch] + encodeStdin :: IO Expression encodeStdin = do + putStrLn "Waiting for stdin eof" bytes <- Byte.getContents pure $ encodeBytes bytes @@ -153,10 +161,10 @@ decodeByte (Abstraction (Application (Application (Bruijn 0) (Abstraction (Abstr = False : (decodeByte es) decodeByte (Abstraction (Application (Application (Bruijn 0) (Abstraction (Abstraction (Bruijn 1)))) es)) = True : (decodeByte es) -decodeByte _ = error "invalid" +decodeByte _ = error "invalid" -- TODO: Better errors using Maybe decodeStdout :: Expression -> String -decodeStdout e = show $ Byte.concat $ map +decodeStdout e = C.unpack $ Byte.concat $ map (Bit.realizeBitStringStrict . Bit.fromList . decodeByte) (unlistify e) diff --git a/src/Parser.hs b/src/Parser.hs index 5d62ab0..1d889d3 100644 --- a/src/Parser.hs +++ b/src/Parser.hs @@ -73,6 +73,16 @@ parseNumeral = do number :: Parser Integer number = ap sign nat +parseString :: Parser Expression +parseString = do + str <- between (char '\"') (char '\"') (some $ satisfy (`notElem` "\"\\")) + pure (stringToExpression str) <?> "string" + +parseChar :: Parser Expression +parseChar = do + ch <- between (char '\'') (char '\'') (satisfy (`notElem` "\"\\")) + pure (charToExpression ch) <?> "char" + parseVariable :: Parser Expression parseVariable = do var <- identifier @@ -82,6 +92,8 @@ parseSingleton :: Parser Expression parseSingleton = parseBruijn <|> parseNumeral + <|> parseString + <|> parseChar <|> parseAbstraction <|> (parens parseApplication <?> "enclosed application") <|> parseVariable |