diff options
Diffstat (limited to 'app/IR.hs')
| -rw-r--r-- | app/IR.hs | 35 |
1 files changed, 11 insertions, 24 deletions
@@ -1,28 +1,15 @@ module IR where +import Constant import Data.Char (isNumber) import Data.List (mapAccumL) import qualified Data.Map as M - -data PrlgStr - = CallS String [PrlgStr] - | LiteralS String - | ListS [PrlgStr] (Maybe PrlgStr) - deriving (Show) - -data Id = - Id - { str :: Int - , arity :: Int - } - deriving (Show, Eq, Ord) +import Parser (Lexeme(..), PrlgStr(..)) data PrlgInt = CallI Int [PrlgInt] - | AtomI Int - | NumI Int - | ListI [PrlgInt] (Maybe PrlgInt) -- only exists before desugaring - | VarI Int Int -- VarI localIndex strTableString + | ConstI Constant + | VarI Int -- VarI localIndex strTableString | VoidI deriving (Show) @@ -37,16 +24,16 @@ strtablize t@(StrTable nxt fwd rev) str = Just i -> (t, i) _ -> (StrTable (nxt + 1) (M.insert str nxt fwd) (M.insert nxt str rev), nxt) +internLexeme t (Tok str) + | all isNumber str = (t, ConstI . Number $ read str) + | otherwise = ConstI . Atom <$> strtablize t str +internLexeme t (QTok str _) = ConstI . Atom <$> strtablize t str +internLexeme t (DQTok str _) = (t, ConstI $ Str str) + internPrlg :: StrTable -> PrlgStr -> (StrTable, PrlgInt) internPrlg = go where - go t (LiteralS str) - | all isNumber str = (t, NumI $ read str) - | otherwise = AtomI <$> strtablize t str + go t (LiteralS lex) = internLexeme t lex go t (CallS str ps) = let (t', i) = strtablize t str in CallI i <$> mapAccumL go t' ps - go t (ListS elems Nothing) = flip ListI Nothing <$> mapAccumL go t elems - go t (ListS elems (Just tail)) = - let (t', tail') = go t tail - in flip ListI (Just tail') <$> mapAccumL go t' elems |
