summaryrefslogtreecommitdiff
path: root/app/Compiler.hs
diff options
context:
space:
mode:
authorMirek Kratochvil <exa.exa@gmail.com>2022-11-11 22:10:26 +0100
committerMirek Kratochvil <exa.exa@gmail.com>2022-11-11 22:10:26 +0100
commitfe6666d204c0728b4556574ddc184bc46013b193 (patch)
treef0e33f3d379ce562c02620660ebdbd1fcb870fe7 /app/Compiler.hs
parent5d186de9c8483b4de749459fda9c507c68f8fa73 (diff)
downloadprlg-fe6666d204c0728b4556574ddc184bc46013b193.tar.gz
prlg-fe6666d204c0728b4556574ddc184bc46013b193.tar.bz2
looks like vars work
Diffstat (limited to 'app/Compiler.hs')
-rw-r--r--app/Compiler.hs28
1 files changed, 24 insertions, 4 deletions
diff --git a/app/Compiler.hs b/app/Compiler.hs
index 08e4b24..4f94637 100644
--- a/app/Compiler.hs
+++ b/app/Compiler.hs
@@ -1,5 +1,7 @@
module Compiler where
+import Data.Char (isUpper)
+import Data.Containers.ListUtils (nubOrd)
import Data.List
import Interpreter (Code, Datum(..), Id(..), Instr(..), StrTable, strtablize)
@@ -10,13 +12,29 @@ data PrlgStr
data PrlgInt
= CallI Id [PrlgInt]
- | LiteralI Int --split off vars here later
+ | LiteralI Int
+ | VarI Int Int
+ | VoidI
deriving (Show)
-strtablizePrlg :: StrTable -> PrlgStr -> (StrTable, PrlgInt)
-strtablizePrlg = go
+varname :: String -> Bool
+varname ('_':_) = True
+varname (c:_) = isUpper c
+varname _ = False
+
+varnames :: PrlgStr -> [String]
+varnames (CallS _ xs) = nubOrd $ concatMap varnames xs
+varnames (LiteralS x)
+ | varname x = [x]
+ | otherwise = []
+
+strtablizePrlg :: [String] -> StrTable -> PrlgStr -> (StrTable, PrlgInt)
+strtablizePrlg stab = go
where
- go t (LiteralS str) = LiteralI <$> strtablize t str
+ go t (LiteralS str)
+ | str == "_" = (t, VoidI)
+ | Just idx <- elemIndex str stab = VarI idx <$> strtablize t str
+ | otherwise = LiteralI <$> strtablize t str
go t (CallS str ps) =
let (t', i) = strtablize t str
in CallI (Id i $ length ps) <$> mapAccumL go t' ps
@@ -35,6 +53,8 @@ compileGoal x = compileArg x
compileArg :: PrlgInt -> Code
compileArg (CallI x args) = U (Struct x) : concatMap compileArg args
compileArg (LiteralI x) = [U (Atom x)]
+compileArg (VarI x _) = [U (LocalRef x)]
+compileArg VoidI = [U VoidRef]
seqGoals :: [Code] -> Code
seqGoals [] = [NoGoal]