module DSL where import Data.Char (isDigit, isSpace) import Data.Foldable (foldlM) import Parsers ------------------------------------------------------------------------------ -- Data types / instances ------------------------------------------------------------------------------ data StackData = StackInt Integer | StackBool Bool instance Show StackData where show (StackInt x) = show x show (StackBool True) = "true" show (StackBool False) = "false" type TypeCheck = StackData -> Bool type Stack = [StackData] data Intrinsic -- core stack operations = I_DUMP | I_DROP | I_SWAP | I_DUP | I_OVER | I_ROT -- core arithmetic operations | I_PLUS | I_MINUS deriving (Show, Eq) data Operation = OpPushData StackData | OpIntrinsic Intrinsic deriving (Show) data StackModifier = StackModifier { smName :: String , smTypes :: [TypeCheck] , smFunc :: Stack -> IO Stack } type Program = [Operation] data Machine = Machine { ok :: Bool , stack :: Stack } data TokenData = T_WHITESPACE | T_INT_LITERAL Integer | T_INTRINSIC Intrinsic deriving (Show, Eq) data DSLToken = DSLToken { tStr :: String -- original text , tData :: TokenData -- actual data } deriving (Show) type DSLLexer = Parser Char DSLToken type DSLParser = Parser DSLToken ------------------------------------------------------------------------------ -- Lexing ------------------------------------------------------------------------------ buildDSLLexer :: (Parser Char [Char]) -> ([Char] -> TokenData) -> DSLLexer buildDSLLexer p f = do str <- p return DSLToken { tStr=str , tData=f str } intrinsicL :: String -> Intrinsic -> DSLLexer intrinsicL s i = buildDSLLexer (list s) (const $ T_INTRINSIC i) wsL :: DSLLexer wsL = buildDSLLexer (mult1 $ satisfy isSpace) (const T_WHITESPACE) intLiteralL :: DSLLexer intLiteralL = buildDSLLexer (mult1 $ satisfy isDigit) (T_INT_LITERAL . read) mainLexer :: Parser Char [DSLToken] mainLexer = phrase $ mult1 $ firstOf subLexers where subLexers = [wsL] ++ literals ++ intrinsics literals = [ intLiteralL ] intrinsics = map (uncurry intrinsicL) [ (".", I_DUMP) , ("DROP", I_DROP) , ("SWAP", I_SWAP) , ("DUP", I_DUP) , ("OVER", I_OVER) , ("ROT", I_ROT) , ("+", I_PLUS) , ("-", I_MINUS) ] ------------------------------------------------------------------------------ -- Parsing ------------------------------------------------------------------------------ wsP :: DSLParser () wsP = do t <- anyToken case tData t of T_WHITESPACE -> result () _ -> flunk dataLiteralP :: DSLParser StackData dataLiteralP = do t <- anyToken case tData t of T_INT_LITERAL x -> result $ StackInt x _ -> flunk pushDataP :: DSLParser Operation pushDataP = OpPushData <$> dataLiteralP intrinsicP :: DSLParser Operation intrinsicP = do t <- anyToken case tData t of T_INTRINSIC i -> result $ OpIntrinsic i _ -> flunk operationP :: DSLParser Operation operationP = firstOf [ pushDataP , intrinsicP ] programP :: DSLParser Program programP = do () <$ optional wsP ops <- operationP `sepBy1` wsP () <$ optional wsP eof return ops stringToProgram :: String -> Maybe Program stringToProgram str = do (_, tokens) <- parse mainLexer str (_, program) <- parse programP tokens return program ------------------------------------------------------------------------------ -- Type checking ------------------------------------------------------------------------------ tAny :: TypeCheck tAny = const True tBool :: TypeCheck tBool (StackBool _) = True tBool _ = False tInt :: TypeCheck tInt (StackInt _) = True tInt _ = False runChecks :: [TypeCheck] -> Stack -> Maybe String runChecks fs s | length fs > length s = Just "stack underflow" | not (and $ zipWith id fs s) = Just "type mis-match" | otherwise = Nothing ------------------------------------------------------------------------------ -- Intrinsics ------------------------------------------------------------------------------ dump :: StackModifier dump = StackModifier { smName="DUMP", smTypes=ts, smFunc=f } where ts = [tAny] f (x:xs) = putStrLn (show x) >> return xs f _ = unreachable drop' :: StackModifier drop' = StackModifier { smName="DROP", smTypes=ts, smFunc=f } where ts = [tAny] f (_:xs) = return xs f _ = unreachable swap :: StackModifier swap = StackModifier { smName="SWAP", smTypes=ts, smFunc=f } where ts = [tAny, tAny] f (x:y:xs) = return $ y:x:xs f _ = unreachable dup :: StackModifier dup = StackModifier { smName="DUP", smTypes=ts, smFunc=f } where ts = [tAny] f (x:xs) = return $ x:x:xs f _ = unreachable over :: StackModifier over = StackModifier { smName="OVER", smTypes=ts, smFunc=f } where ts = [tAny, tAny] f (x:y:xs) = return $ y:x:y:xs f _ = unreachable rot :: StackModifier rot = StackModifier { smName="ROT", smTypes=ts, smFunc=f } where ts = [tAny, tAny, tAny] f (x:y:z:xs) = return $ y:z:x:xs f _ = unreachable plus :: StackModifier plus = StackModifier { smName="PLUS", smTypes=ts, smFunc=f } where ts = [tInt, tInt] f (StackInt x:StackInt y:xs) = return $ StackInt (x+y):xs f _ = unreachable minus :: StackModifier minus = StackModifier { smName="MINUS", smTypes=ts, smFunc=f } where ts = [tInt, tInt] f (StackInt x:StackInt y:xs) = return $ StackInt (x-y):xs f _ = unreachable ------------------------------------------------------------------------------ -- Core operations ------------------------------------------------------------------------------ -- "halt and catch fire" hcf :: Machine -> String -> IO Machine hcf m msg = putStrLn msg >> return m{ ok=False } unreachable :: a unreachable = error "this branch should be unreachable" pushData :: Machine -> StackData -> Machine pushData m@Machine{ stack=xs } x = m{ stack=x:xs } runModifier :: StackModifier -> Stack -> IO (Either String Stack) runModifier sm s = case runChecks (smTypes sm) s of Just err -> return $ Left $ smName sm ++ ": " ++ err Nothing -> Right <$> smFunc sm s applyIntrinsic :: Intrinsic -> Machine -> IO Machine applyIntrinsic i m = do res <- runModifier sm (stack m) case res of Left err -> hcf m err Right s' -> return m{ stack=s' } where sm = case i of I_DUMP -> dump I_DROP -> drop' I_SWAP -> swap I_DUP -> dup I_OVER -> over I_ROT -> rot I_PLUS -> plus I_MINUS -> minus ------------------------------------------------------------------------------ -- Interpretation ------------------------------------------------------------------------------ newMachine :: Machine newMachine = Machine { ok=True, stack=[] } applyOperation :: Machine -> Operation -> IO Machine -- take no action if a previous step failed applyOperation m@Machine{ ok=False } _ = return m applyOperation m (OpPushData x) = return $ pushData m x applyOperation m (OpIntrinsic i) = applyIntrinsic i m applyLinear :: Machine -> [Operation] -> IO Machine applyLinear = foldlM applyOperation interpret :: Program -> IO () interpret p = applyLinear newMachine p >> return () interpretFromString :: String -> IO () interpretFromString = maybe err interpret . stringToProgram where err = putStrLn "Unable to parse program" interpretFromFile :: FilePath -> IO () interpretFromFile path = readFile path >>= interpretFromString