elna/lib/Language/Elna/Backend/Allocator.hs

169 lines
6.4 KiB
Haskell
Raw Normal View History

2024-10-02 22:56:15 +02:00
module Language.Elna.Backend.Allocator
2024-10-01 00:02:19 +02:00
( MachineConfiguration(..)
, Store(..)
, allocate
2024-09-27 00:22:44 +02:00
) where
2024-10-01 00:02:19 +02:00
import Data.HashMap.Strict (HashMap)
2024-12-04 16:11:06 +01:00
import qualified Data.HashMap.Strict as HashMap
2024-11-24 13:05:11 +01:00
import Data.Int (Int32)
import Data.Word (Word32)
2024-10-01 00:02:19 +02:00
import Data.Vector (Vector)
import Language.Elna.Backend.Intermediate
( ProcedureQuadruples(..)
, Operand(..)
, Quadruple(..)
, Variable(..)
)
2024-10-01 00:02:19 +02:00
import Language.Elna.Location (Identifier(..))
import Control.Monad.Trans.Reader (ReaderT, asks, runReaderT)
2024-12-04 16:11:06 +01:00
import Control.Monad.Trans.State (State, runState)
import GHC.Records (HasField(..))
2024-11-24 13:05:11 +01:00
import Control.Monad.Trans.Class (MonadTrans(..))
import Control.Monad.Trans.Except (ExceptT(..), runExceptT, throwE)
import Data.List ((!?))
2024-12-04 16:11:06 +01:00
import Language.Elna.Frontend.SymbolTable (Info(..), SymbolTable)
import qualified Language.Elna.Frontend.SymbolTable as SymbolTable
2024-10-01 00:02:19 +02:00
data Store r
= RegisterStore r
2024-11-24 13:05:11 +01:00
| StackStore Int32 r
data AllocationError = AllocationError
deriving Eq
instance Show AllocationError
where
show = const "Ran out of registers during register allocation"
2024-10-01 00:02:19 +02:00
newtype MachineConfiguration r = MachineConfiguration
2024-10-06 18:07:57 +02:00
{ temporaryRegisters :: [r]
2024-10-01 00:02:19 +02:00
}
newtype MachineState = MachineState
2024-12-04 16:11:06 +01:00
{ symbolTable :: SymbolTable
} deriving (Eq, Show)
newtype Allocator r a = Allocator
2024-11-24 13:05:11 +01:00
{ runAllocator :: ExceptT AllocationError (ReaderT (MachineConfiguration r) (State MachineState)) 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)
2024-10-01 00:02:19 +02:00
allocate
:: forall r
. MachineConfiguration r
2024-12-04 16:11:06 +01:00
-> SymbolTable
2024-10-01 00:02:19 +02:00
-> HashMap Identifier (Vector (Quadruple Variable))
2024-11-24 13:05:11 +01:00
-> Either AllocationError (HashMap Identifier (ProcedureQuadruples (Store r)))
2024-12-04 16:11:06 +01:00
allocate machineConfiguration globalTable = HashMap.traverseWithKey function
2024-10-01 00:02:19 +02:00
where
2024-12-04 16:11:06 +01:00
run localTable = flip runState (MachineState{ symbolTable = localTable })
2024-11-24 13:05:11 +01:00
. flip runReaderT machineConfiguration
. runExceptT
. runAllocator
. mapM quadruple
2024-12-04 16:11:06 +01:00
function :: Identifier -> Vector (Quadruple Variable) -> Either AllocationError (ProcedureQuadruples (Store r))
function identifier quadruples' =
let Just (ProcedureInfo localTable _) = SymbolTable.lookup identifier globalTable
(result, lastState) = run localTable quadruples'
2024-11-24 13:05:11 +01:00
in makeResult lastState <$> result
2024-12-04 16:11:06 +01:00
makeResult MachineState{ symbolTable } result = ProcedureQuadruples
2024-11-24 13:05:11 +01:00
{ quadruples = result
2024-12-04 16:11:06 +01:00
, stackSize = fromIntegral $ SymbolTable.size symbolTable * 4
2024-11-24 13:05:11 +01:00
}
quadruple :: Quadruple Variable -> Allocator r (Quadruple (Store r))
quadruple = \case
StartQuadruple -> pure StartQuadruple
StopQuadruple -> pure StopQuadruple
2024-12-04 16:11:06 +01:00
ParameterQuadruple operand1 -> ParameterQuadruple
<$> operand operand1
CallQuadruple name count -> pure $ CallQuadruple name count
2024-12-04 16:11:06 +01:00
AddQuadruple operand1 operand2 variable -> AddQuadruple
<$> operand operand1
<*> operand operand2
<*> storeVariable variable
SubtractionQuadruple operand1 operand2 variable -> SubtractionQuadruple
<$> operand operand1
<*> operand operand2
<*> storeVariable variable
NegationQuadruple operand1 variable -> NegationQuadruple
<$> operand operand1
<*> storeVariable variable
ProductQuadruple operand1 operand2 variable -> ProductQuadruple
<$> operand operand1
<*> operand operand2
<*> storeVariable variable
DivisionQuadruple operand1 operand2 variable -> DivisionQuadruple
<$> operand operand1
<*> operand operand2
<*> storeVariable variable
LabelQuadruple label -> pure $ LabelQuadruple label
GoToQuadruple label -> pure $ GoToQuadruple label
2024-12-04 16:11:06 +01:00
EqualQuadruple operand1 operand2 goToLabel -> EqualQuadruple
<$> operand operand1
<*> operand operand2
<*> pure goToLabel
NonEqualQuadruple operand1 operand2 goToLabel -> NonEqualQuadruple
<$> operand operand1
<*> operand operand2
<*> pure goToLabel
LessQuadruple operand1 operand2 goToLabel -> LessQuadruple
<$> operand operand1
<*> operand operand2
<*> pure goToLabel
GreaterQuadruple operand1 operand2 goToLabel -> do
operand1' <- operand operand1
operand2' <- operand operand2
pure $ GreaterQuadruple operand1' operand2' goToLabel
2024-12-04 16:11:06 +01:00
LessOrEqualQuadruple operand1 operand2 goToLabel -> LessOrEqualQuadruple
<$> operand operand1
<*> operand operand2
<*> pure goToLabel
GreaterOrEqualQuadruple operand1 operand2 goToLabel -> GreaterOrEqualQuadruple
<$> operand operand1
<*> operand operand2
<*> pure goToLabel
AssignQuadruple operand1 variable -> AssignQuadruple
<$> operand operand1
<*> storeVariable variable
ArrayAssignQuadruple operand1 operand2 variable -> ArrayAssignQuadruple
<$> operand operand1
<*> operand operand2
<*> storeVariable variable
ArrayQuadruple variable1 operand1 variable2 -> ArrayQuadruple
<$> storeVariable variable1
<*> operand operand1
<*> storeVariable variable2
operand :: Operand Variable -> Allocator r (Operand (Store r))
2024-12-04 16:11:06 +01:00
operand (IntOperand literalOperand) = pure $ IntOperand literalOperand
operand (VariableOperand variableOperand) =
VariableOperand <$> storeVariable variableOperand
storeVariable :: Variable -> Allocator r (Store r)
storeVariable (TempVariable index) = do
2024-11-24 13:05:11 +01:00
temporaryRegisters' <- Allocator $ lift $ asks $ getField @"temporaryRegisters"
maybe (Allocator $ throwE AllocationError) (pure . RegisterStore)
$ temporaryRegisters' !? fromIntegral index
storeVariable (LocalVariable index) = do
2024-11-24 13:05:11 +01:00
temporaryRegisters' <- Allocator $ lift $ asks $ getField @"temporaryRegisters"
maybe (Allocator $ throwE AllocationError) (pure . StackStore (fromIntegral (succ index) * (-4)))
$ temporaryRegisters' !? pred (length temporaryRegisters' - fromIntegral index)
storeVariable (ParameterVariable index) = do
temporaryRegisters' <- Allocator $ lift $ asks $ getField @"temporaryRegisters"
maybe (Allocator $ throwE AllocationError) (pure . StackStore (fromIntegral index * 4))
$ temporaryRegisters' !? fromIntegral index