module LinearScan
(
allocate
, BlockInfo(..)
, defaultBlockInfo
, OpInfo(..)
, OpKind(..)
, defaultOpInfo
, VarInfo(..)
, VarKind(..)
, Allocation(..)
, PhysReg
, defaultVarInfo
) where
import qualified LinearScan.Main as LS
import LinearScan.Main
( VarKind(..)
, Allocation(..)
, OpKind(..)
, PhysReg
)
data VarInfo = VarInfo
{ varId :: Int
, varKind :: VarKind
, varAlloc :: Allocation
, regRequired :: Bool
}
deriving (Eq, Show)
deriving instance Eq VarKind
deriving instance Show VarKind
defaultVarInfo :: VarInfo
defaultVarInfo = VarInfo
{ varId = 0
, varKind = Temp
, varAlloc = Unallocated
, regRequired = False
}
toVarInfo :: LS.VarInfo -> VarInfo
toVarInfo (LS.Build_VarInfo a b c d) = VarInfo a b c d
fromVarInfo :: VarInfo -> LS.VarInfo
fromVarInfo (VarInfo a b c d) = LS.Build_VarInfo a b c d
data OpInfo = OpInfo
{ opId :: Int
, opMeta :: Int
, opKind :: OpKind
, varRefs :: [VarInfo]
, regRefs :: [PhysReg]
}
deriving (Eq, Show)
deriving instance Eq OpKind
deriving instance Show OpKind
defaultOpInfo :: OpInfo
defaultOpInfo = OpInfo
{ opId = 0
, opMeta = 0
, opKind = Normal
, varRefs = []
, regRefs = []
}
toOpInfo :: LS.OpInfo -> OpInfo
toOpInfo (LS.Build_OpInfo a b c d e) = OpInfo a b c (map toVarInfo d) e
fromOpInfo :: OpInfo -> LS.OpInfo
fromOpInfo (OpInfo a b c d e) = LS.Build_OpInfo a b c (map fromVarInfo d) e
data BlockInfo = BlockInfo
{ blockId :: Int
, blockOps :: [OpInfo]
}
deriving (Eq, Show)
defaultBlockInfo :: BlockInfo
defaultBlockInfo = BlockInfo
{ blockId = 0
, blockOps = []
}
toBlockInfo :: LS.BlockInfo -> BlockInfo
toBlockInfo (LS.Build_BlockInfo a b) = BlockInfo a (map toOpInfo b)
fromBlockInfo :: BlockInfo -> LS.BlockInfo
fromBlockInfo (BlockInfo a b) = LS.Build_BlockInfo a (map fromOpInfo b)
allocate :: [BlockInfo] -> Either String [BlockInfo]
allocate [] = Left "No basic blocks were provided"
allocate blocks =
case LS.linearScan (map fromBlockInfo blocks) of
Left x -> Left $ case x of
LS.ECannotSplitSingleton n ->
"Current interval is a singleton (" ++ show n ++ ")"
LS.ECannotSplitAssignedSingleton n ->
"Current interval is an assigned singleton (" ++ show n ++ ")"
LS.ENoIntervalsToSplit ->
"There are no intervals to split"
LS.ERegisterAlreadyAssigned n ->
"Register is already assigned (" ++ show n ++ ")"
LS.ERegisterAssignmentsOverlap n ->
"Register assignments overlap (" ++ show n ++ ")"
Right z -> Right (map toBlockInfo z)