a bit more flexible VarI processing
This commit is contained in:
		
							parent
							
								
									a26f0f29c0
								
							
						
					
					
						commit
						83e1cb5cc7
					
				|  | @ -2,10 +2,9 @@ module Compiler where | ||||||
| 
 | 
 | ||||||
| import Data.Char (isUpper) | import Data.Char (isUpper) | ||||||
| import Data.Containers.ListUtils (nubOrd) | import Data.Containers.ListUtils (nubOrd) | ||||||
| import Data.List (elemIndex) |  | ||||||
| import qualified Data.Map as M | import qualified Data.Map as M | ||||||
| 
 | 
 | ||||||
| import Code (Code, Datum(..), Instr(..)) | import Code (Code, Datum(..), Heap, Instr(..), heapStruct) | ||||||
| import IR (Id(..), PrlgInt(..), StrTable(..)) | import IR (Id(..), PrlgInt(..), StrTable(..)) | ||||||
| 
 | 
 | ||||||
| varname :: String -> Bool | varname :: String -> Bool | ||||||
|  | @ -13,38 +12,48 @@ varname ('_':_) = True | ||||||
| varname (c:_) = isUpper c | varname (c:_) = isUpper c | ||||||
| varname _ = False | varname _ = False | ||||||
| 
 | 
 | ||||||
| varIds :: StrTable -> PrlgInt -> [Int] | varIds :: PrlgInt -> [Int] | ||||||
| varIds st (CallI _ xs) = nubOrd $ concatMap (varIds st) xs | varIds (CallI _ xs) = nubOrd $ concatMap varIds xs | ||||||
| varIds (StrTable _ _ st) (LiteralI x) | varIds (VarI idx _) = [idx] | ||||||
|   | Just s <- st M.!? x | varIds _ = [] | ||||||
|   , varname s = [x] |  | ||||||
|   | otherwise = [] |  | ||||||
| 
 | 
 | ||||||
| variablizePrlg :: Int -> [Int] -> PrlgInt -> PrlgInt | variablizePrlg :: Int -> StrTable -> PrlgInt -> PrlgInt | ||||||
| variablizePrlg void vs (CallI id ps) = | variablizePrlg void (StrTable _ _ itos) = go | ||||||
|   CallI id $ map (variablizePrlg void vs) ps |   where | ||||||
| variablizePrlg void vs (LiteralI i) |     go (CallI id ps) = CallI id $ map go ps | ||||||
|  |     go (LiteralI i) | ||||||
|       | i == void = VoidI |       | i == void = VoidI | ||||||
|   | Just idx <- elemIndex i vs = VarI idx i |       | varname (itos M.! i) = VarI i i | ||||||
|       | otherwise = LiteralI i |       | otherwise = LiteralI i | ||||||
| 
 | 
 | ||||||
| compileGoals :: Id -> Int -> PrlgInt -> [Code] | renumVars :: [(Int, Int)] -> PrlgInt -> PrlgInt | ||||||
| compileGoals andop cut = go | renumVars rename = go | ||||||
|   where |   where | ||||||
|  |     go (CallI id ps) = CallI id $ map go ps | ||||||
|  |     go (VarI idx i) | ||||||
|  |       | Just idx' <- lookup idx rename = VarI idx' i | ||||||
|  |     go x = x | ||||||
|  | 
 | ||||||
|  | squashVars :: PrlgInt -> PrlgInt | ||||||
|  | squashVars x = renumVars (zip (varIds x) [1 ..]) x | ||||||
|  | 
 | ||||||
|  | compileGoals :: Id -> Int -> PrlgInt -> [Code] | ||||||
|  | compileGoals andop cut = go' | ||||||
|  |   where | ||||||
|  |     go' = go . struct2goal | ||||||
|     go p@(CallI x args) |     go p@(CallI x args) | ||||||
|       | x == andop = concatMap go args |       | x == andop = concatMap go' args | ||||||
|     go p@(LiteralI x) |     go p@(CallI (Id x 0) []) | ||||||
|       | x == cut = [[Cut]] |       | x == cut = [[Cut]] | ||||||
|     go x = [compileGoal x] |     go x = [compileGoal x] | ||||||
| 
 | 
 | ||||||
| compileGoal :: PrlgInt -> Code | compileGoal :: PrlgInt -> Code | ||||||
| compileGoal (LiteralI x) = [U (Struct $ Id x 0)] | compileGoal = compileArg | ||||||
| compileGoal x = compileArg x |  | ||||||
| 
 | 
 | ||||||
| compileArg :: PrlgInt -> Code | compileArg :: PrlgInt -> Code | ||||||
| compileArg (CallI x args) = U (Struct x) : concatMap compileArg args | compileArg (CallI s args) = U (Struct s) : concatMap compileArg args | ||||||
| compileArg (LiteralI x) = [U (Atom x)] | compileArg (LiteralI s) = [U (Atom s)] | ||||||
| compileArg (VarI x i) = [U (LocalRef x i)] | compileArg (VarI x s) = [U (LocalRef x s)] | ||||||
| compileArg (VoidI) = [U VoidRef] | compileArg (VoidI) = [U VoidRef] | ||||||
| 
 | 
 | ||||||
| seqGoals :: [Code] -> Code | seqGoals :: [Code] -> Code | ||||||
|  | @ -54,3 +63,23 @@ seqGoals [x] = [Goal] ++ x ++ [LastCall] | ||||||
| seqGoals [x, [Cut]] = [Goal] ++ x ++ [LastCall, Cut] | seqGoals [x, [Cut]] = [Goal] ++ x ++ [LastCall, Cut] | ||||||
| seqGoals ([Cut]:xs) = [Cut] ++ seqGoals xs | seqGoals ([Cut]:xs) = [Cut] ++ seqGoals xs | ||||||
| seqGoals (x:xs) = [Goal] ++ x ++ [Call] ++ seqGoals xs | seqGoals (x:xs) = [Goal] ++ x ++ [Call] ++ seqGoals xs | ||||||
|  | 
 | ||||||
|  | heapStructPrlgInt :: Monad m => m PrlgInt -> Heap -> Int -> m PrlgInt | ||||||
|  | heapStructPrlgInt heaperr heap ref = | ||||||
|  |   squashVars <$> heapStruct atom struct hrec heap ref | ||||||
|  |   where | ||||||
|  |     atom (Atom s) = pure $ LiteralI s | ||||||
|  |     atom VoidRef = pure $ VoidI | ||||||
|  |     struct (Struct s) args = pure $ CallI s args | ||||||
|  |     hrec (HeapRef r) ref | ||||||
|  |       | r == ref = pure $ VarI r 0 | ||||||
|  |       | otherwise = heaperr | ||||||
|  | 
 | ||||||
|  | -- TODO check if this is used | ||||||
|  | goal2struct :: PrlgInt -> PrlgInt | ||||||
|  | goal2struct (CallI (Id s 0) []) = LiteralI s | ||||||
|  | goal2struct x = x | ||||||
|  | 
 | ||||||
|  | struct2goal :: PrlgInt -> PrlgInt | ||||||
|  | struct2goal (LiteralI s) = CallI (Id s 0) [] | ||||||
|  | struct2goal x = x | ||||||
|  |  | ||||||
|  | @ -49,7 +49,7 @@ interpret = (>> return True) . lex | ||||||
|       underscore <- findAtom "_" |       underscore <- findAtom "_" | ||||||
|       prlgv <- |       prlgv <- | ||||||
|         withStrTable $ \st -> |         withStrTable $ \st -> | ||||||
|           (st, C.variablizePrlg underscore (C.varIds st prlgi) prlgi) |           (st, C.squashVars $ C.variablizePrlg underscore st prlgi) | ||||||
|       compile prlgv |       compile prlgv | ||||||
|     compile prlgv = do |     compile prlgv = do | ||||||
|       commaId <- findStruct "," 2 |       commaId <- findStruct "," 2 | ||||||
|  |  | ||||||
		Loading…
	
		Reference in a new issue