summaryrefslogtreecommitdiff
path: root/app/IR.hs
diff options
context:
space:
mode:
authorMirek Kratochvil <exa.exa@gmail.com>2023-03-05 21:34:20 +0100
committerMirek Kratochvil <exa.exa@gmail.com>2023-03-05 21:34:20 +0100
commit98c40f4bf8849f5cdd3d3c49123bc911b8fa42e1 (patch)
treee41a1cd05d17765f9e27b0844580655b2dc1ae95 /app/IR.hs
parent45c3f81891837820aea7c3dbd45e3bae25fc4c22 (diff)
downloadprlg-98c40f4bf8849f5cdd3d3c49123bc911b8fa42e1.tar.gz
prlg-98c40f4bf8849f5cdd3d3c49123bc911b8fa42e1.tar.bz2
strings and a few other small nice changes
Diffstat (limited to 'app/IR.hs')
-rw-r--r--app/IR.hs35
1 files changed, 11 insertions, 24 deletions
diff --git a/app/IR.hs b/app/IR.hs
index fef193b..d7345e5 100644
--- a/app/IR.hs
+++ b/app/IR.hs
@@ -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