Split the allocator and add state to it
This commit is contained in:
		| @@ -14,6 +14,9 @@ import Language.Elna.Backend.Intermediate | |||||||
|     , Variable(..) |     , Variable(..) | ||||||
|     ) |     ) | ||||||
| import Language.Elna.Location (Identifier(..)) | import Language.Elna.Location (Identifier(..)) | ||||||
|  | import Control.Monad.Trans.Reader (ReaderT, asks, runReaderT) | ||||||
|  | import Control.Monad.Trans.State (State, runState) | ||||||
|  | import GHC.Records (HasField(..)) | ||||||
|  |  | ||||||
| data Store r | data Store r | ||||||
|     = RegisterStore r |     = RegisterStore r | ||||||
| @@ -23,61 +26,108 @@ newtype MachineConfiguration r = MachineConfiguration | |||||||
|     { temporaryRegisters :: [r] |     { temporaryRegisters :: [r] | ||||||
|     } |     } | ||||||
|  |  | ||||||
|  | newtype Allocator r a = Allocator | ||||||
|  |     { runAllocator :: ReaderT (MachineConfiguration r) (State Word32) a | ||||||
|  |     } | ||||||
|  |  | ||||||
|  | instance forall r. Functor (Allocator r) | ||||||
|  |   where | ||||||
|  |     fmap f = Allocator . fmap f . runAllocator | ||||||
|  |  | ||||||
|  | instance forall r. Applicative (Allocator r) | ||||||
|  |   where | ||||||
|  |     pure = Allocator . pure | ||||||
|  |     (Allocator x) <*> (Allocator y) = Allocator $ x <*> y | ||||||
|  |  | ||||||
|  | instance forall r. Monad (Allocator r) | ||||||
|  |   where | ||||||
|  |     (Allocator allocator) >>= f = Allocator $ allocator >>= (runAllocator . f) | ||||||
|  |  | ||||||
| allocate | allocate | ||||||
|     :: forall r |     :: forall r | ||||||
|     . MachineConfiguration r |     . MachineConfiguration r | ||||||
|     -> HashMap Identifier (Vector (Quadruple Variable)) |     -> HashMap Identifier (Vector (Quadruple Variable)) | ||||||
|     -> HashMap Identifier (ProcedureQuadruples (Store r)) |     -> HashMap Identifier (ProcedureQuadruples (Store r)) | ||||||
| allocate MachineConfiguration{..} = fmap function | allocate machineConfiguration = fmap function | ||||||
|   where |   where | ||||||
|     function :: Vector (Quadruple Variable) -> ProcedureQuadruples (Store r) |     function :: Vector (Quadruple Variable) -> ProcedureQuadruples (Store r) | ||||||
|     function quadruples' = ProcedureQuadruples |     function quadruples' = ProcedureQuadruples | ||||||
|         { quadruples = quadruple <$> quadruples' |         { quadruples = fst | ||||||
|  |             $ flip runState 0 | ||||||
|  |             $ flip runReaderT machineConfiguration | ||||||
|  |             $ runAllocator | ||||||
|  |             $ mapM quadruple quadruples' | ||||||
|         , stackSize = 0 |         , stackSize = 0 | ||||||
|         } |         } | ||||||
|     quadruple :: Quadruple Variable -> Quadruple (Store r) |  | ||||||
|  | quadruple :: Quadruple Variable -> Allocator r (Quadruple (Store r)) | ||||||
| quadruple = \case | quadruple = \case | ||||||
|         StartQuadruple -> StartQuadruple |     StartQuadruple -> pure StartQuadruple | ||||||
|         StopQuadruple -> StopQuadruple |     StopQuadruple -> pure StopQuadruple | ||||||
|         ParameterQuadruple operand1 -> |     ParameterQuadruple operand1 -> do | ||||||
|             ParameterQuadruple (operand operand1) |         operand1' <- operand operand1 | ||||||
|         CallQuadruple name count -> CallQuadruple name count |         pure $ ParameterQuadruple operand1' | ||||||
|         AddQuadruple operand1 operand2 variable |     CallQuadruple name count -> pure $ CallQuadruple name count | ||||||
|             -> AddQuadruple (operand operand1) (operand operand2) |     AddQuadruple operand1 operand2 variable -> do | ||||||
|             $ storeVariable variable |         operand1' <- operand operand1 | ||||||
|         SubtractionQuadruple operand1 operand2 variable |         operand2' <- operand operand2 | ||||||
|             -> SubtractionQuadruple (operand operand1) (operand operand2) |         AddQuadruple operand1' operand2' <$> storeVariable variable | ||||||
|             $ storeVariable variable |     SubtractionQuadruple operand1 operand2 variable -> do | ||||||
|         NegationQuadruple operand1 variable |         operand1' <- operand operand1 | ||||||
|             -> NegationQuadruple (operand operand1) |         operand2' <- operand operand2 | ||||||
|             $ storeVariable variable |         SubtractionQuadruple operand1' operand2' <$> storeVariable variable | ||||||
|         ProductQuadruple operand1 operand2 variable |     NegationQuadruple operand1 variable -> do | ||||||
|             -> ProductQuadruple (operand operand1) (operand operand2) |         operand1' <- operand operand1 | ||||||
|             $ storeVariable variable |         NegationQuadruple operand1' <$> storeVariable variable | ||||||
|         DivisionQuadruple operand1 operand2 variable |     ProductQuadruple operand1 operand2 variable -> do | ||||||
|             -> DivisionQuadruple (operand operand1) (operand operand2) |         operand1' <- operand operand1 | ||||||
|             $ storeVariable variable |         operand2' <- operand operand2 | ||||||
|         LabelQuadruple label -> LabelQuadruple label |         ProductQuadruple operand1' operand2' <$> storeVariable variable | ||||||
|         GoToQuadruple label -> GoToQuadruple label |     DivisionQuadruple operand1 operand2 variable -> do | ||||||
|         EqualQuadruple operand1 operand2 goToLabel -> |         operand1' <- operand operand1 | ||||||
|             EqualQuadruple (operand operand1) (operand operand2) goToLabel |         operand2' <- operand operand2 | ||||||
|         NonEqualQuadruple operand1 operand2 goToLabel -> |         DivisionQuadruple operand1' operand2' <$> storeVariable variable | ||||||
|             NonEqualQuadruple (operand operand1) (operand operand2) goToLabel |     LabelQuadruple label -> pure $ LabelQuadruple label | ||||||
|         LessQuadruple operand1 operand2 goToLabel -> |     GoToQuadruple label -> pure $ GoToQuadruple label | ||||||
|             LessQuadruple (operand operand1) (operand operand2) goToLabel |     EqualQuadruple operand1 operand2 goToLabel -> do | ||||||
|         GreaterQuadruple operand1 operand2 goToLabel -> |         operand1' <- operand operand1 | ||||||
|             GreaterQuadruple (operand operand1) (operand operand2) goToLabel |         operand2' <- operand operand2 | ||||||
|         LessOrEqualQuadruple operand1 operand2 goToLabel -> |         pure $ EqualQuadruple operand1' operand2' goToLabel | ||||||
|             LessOrEqualQuadruple (operand operand1) (operand operand2) goToLabel |     NonEqualQuadruple operand1 operand2 goToLabel -> do | ||||||
|         GreaterOrEqualQuadruple operand1 operand2 goToLabel -> |         operand1' <- operand operand1 | ||||||
|             GreaterOrEqualQuadruple (operand operand1) (operand operand2) goToLabel |         operand2' <- operand operand2 | ||||||
|         AssignQuadruple operand1 variable -> |         pure $ NonEqualQuadruple operand1' operand2' goToLabel | ||||||
|             AssignQuadruple (operand operand1) $ storeVariable variable |     LessQuadruple operand1 operand2 goToLabel -> do | ||||||
|     operand :: Operand Variable -> Operand (Store r) |         operand1' <- operand operand1 | ||||||
|     operand (IntOperand x) = IntOperand x |         operand2' <- operand operand2 | ||||||
|  |         pure $ LessQuadruple operand1' operand2' goToLabel | ||||||
|  |     GreaterQuadruple operand1 operand2 goToLabel -> do | ||||||
|  |         operand1' <- operand operand1 | ||||||
|  |         operand2' <- operand operand2 | ||||||
|  |         pure $ GreaterQuadruple operand1' operand2' goToLabel | ||||||
|  |     LessOrEqualQuadruple operand1 operand2 goToLabel -> do | ||||||
|  |         operand1' <- operand operand1 | ||||||
|  |         operand2' <- operand operand2 | ||||||
|  |         pure $ LessOrEqualQuadruple operand1' operand2' goToLabel | ||||||
|  |     GreaterOrEqualQuadruple operand1 operand2 goToLabel -> do | ||||||
|  |         operand1' <- operand operand1 | ||||||
|  |         operand2' <- operand operand2 | ||||||
|  |         pure $ GreaterOrEqualQuadruple operand1' operand2' goToLabel | ||||||
|  |     AssignQuadruple operand1 variable -> do | ||||||
|  |         operand1' <- operand operand1 | ||||||
|  |         AssignQuadruple operand1' <$> storeVariable variable | ||||||
|  |  | ||||||
|  | operand :: Operand Variable -> Allocator r (Operand (Store r)) | ||||||
|  | operand (IntOperand x) = pure $ IntOperand x | ||||||
| operand (VariableOperand variableOperand) = | operand (VariableOperand variableOperand) = | ||||||
|         VariableOperand $ storeVariable variableOperand |     VariableOperand <$> storeVariable variableOperand | ||||||
|     storeVariable (TempVariable index) = RegisterStore |  | ||||||
|         $ temporaryRegisters !! fromIntegral index | storeVariable :: Variable -> Allocator r (Store r) | ||||||
|     storeVariable (LocalVariable index) = RegisterStore | storeVariable (TempVariable index) = do | ||||||
|         $ temporaryRegisters !! pred (length temporaryRegisters - fromIntegral index) |     temporaryRegisters' <- Allocator $ asks $ getField @"temporaryRegisters" | ||||||
|  |     pure $ RegisterStore | ||||||
|  |         $ temporaryRegisters' !! fromIntegral index | ||||||
|  | storeVariable (LocalVariable index) = do | ||||||
|  |     temporaryRegisters' <- Allocator $ asks $ getField @"temporaryRegisters" | ||||||
|  |     pure $ RegisterStore | ||||||
|  |         $ temporaryRegisters' !! pred (length temporaryRegisters' - fromIntegral index) | ||||||
|   | |||||||
		Reference in New Issue
	
	Block a user