module LinearScan.Blocks where import Debug.Trace (trace, traceShow) import qualified Prelude import qualified Data.IntMap import qualified Data.IntSet import qualified Data.List import qualified Data.Ord import qualified Data.Functor.Identity import qualified LinearScan.Utils import qualified LinearScan.UsePos as UsePos type PhysReg = Prelude.Int type VarId = Prelude.Int data VarInfo = Build_VarInfo (Prelude.Either PhysReg VarId) UsePos.VarKind Prelude.Bool varId :: Prelude.Int -> VarInfo -> Prelude.Either PhysReg VarId varId maxReg v = case v of { Build_VarInfo varId0 varKind0 regRequired0 -> varId0} varKind :: Prelude.Int -> VarInfo -> UsePos.VarKind varKind maxReg v = case v of { Build_VarInfo varId0 varKind0 regRequired0 -> varKind0} regRequired :: Prelude.Int -> VarInfo -> Prelude.Bool regRequired maxReg v = case v of { Build_VarInfo varId0 varKind0 regRequired0 -> regRequired0} nat_of_varId :: Prelude.Int -> VarInfo -> Prelude.Int nat_of_varId maxReg v = case varId maxReg v of { Prelude.Left n -> n; Prelude.Right v0 -> (Prelude.+) v0 maxReg} data OpKind = IsNormal | IsCall | IsBranch type OpId = Prelude.Int data OpInfo accType opType1 opType2 = Build_OpInfo (opType1 -> OpKind) (opType1 -> [] VarInfo) (PhysReg -> PhysReg -> accType -> (,) ([] opType2) accType) (PhysReg -> PhysReg -> accType -> (,) ([] opType2) accType) (PhysReg -> (Prelude.Maybe VarId) -> accType -> (,) ([] opType2) accType) ((Prelude.Maybe VarId) -> PhysReg -> accType -> (,) ([] opType2) accType) (opType1 -> ([] ((,) VarId PhysReg)) -> [] opType2) (opType1 -> Prelude.String) opKind :: Prelude.Int -> (OpInfo a1 a2 a3) -> a2 -> OpKind opKind maxReg o = case o of { Build_OpInfo opKind0 opRefs0 moveOp0 swapOp0 saveOp0 restoreOp0 applyAllocs0 showOp -> opKind0} opRefs :: Prelude.Int -> (OpInfo a1 a2 a3) -> a2 -> [] VarInfo opRefs maxReg o = case o of { Build_OpInfo opKind0 opRefs0 moveOp0 swapOp0 saveOp0 restoreOp0 applyAllocs0 showOp -> opRefs0} moveOp :: Prelude.Int -> (OpInfo a1 a2 a3) -> PhysReg -> PhysReg -> a1 -> (,) ([] a3) a1 moveOp maxReg o = case o of { Build_OpInfo opKind0 opRefs0 moveOp0 swapOp0 saveOp0 restoreOp0 applyAllocs0 showOp -> moveOp0} swapOp :: Prelude.Int -> (OpInfo a1 a2 a3) -> PhysReg -> PhysReg -> a1 -> (,) ([] a3) a1 swapOp maxReg o = case o of { Build_OpInfo opKind0 opRefs0 moveOp0 swapOp0 saveOp0 restoreOp0 applyAllocs0 showOp -> swapOp0} saveOp :: Prelude.Int -> (OpInfo a1 a2 a3) -> PhysReg -> (Prelude.Maybe VarId) -> a1 -> (,) ([] a3) a1 saveOp maxReg o = case o of { Build_OpInfo opKind0 opRefs0 moveOp0 swapOp0 saveOp0 restoreOp0 applyAllocs0 showOp -> saveOp0} restoreOp :: Prelude.Int -> (OpInfo a1 a2 a3) -> (Prelude.Maybe VarId) -> PhysReg -> a1 -> (,) ([] a3) a1 restoreOp maxReg o = case o of { Build_OpInfo opKind0 opRefs0 moveOp0 swapOp0 saveOp0 restoreOp0 applyAllocs0 showOp -> restoreOp0} applyAllocs :: Prelude.Int -> (OpInfo a1 a2 a3) -> a2 -> ([] ((,) VarId PhysReg)) -> [] a3 applyAllocs maxReg o = case o of { Build_OpInfo opKind0 opRefs0 moveOp0 swapOp0 saveOp0 restoreOp0 applyAllocs0 showOp -> applyAllocs0} type BlockId = Prelude.Int data BlockInfo blockType1 blockType2 opType1 opType2 = Build_BlockInfo (blockType1 -> BlockId) (blockType1 -> [] BlockId) (blockType1 -> (,) ((,) ([] opType1) ([] opType1)) ([] opType1)) (blockType1 -> ([] opType2) -> ([] opType2) -> ([] opType2) -> blockType2) blockId :: (BlockInfo a1 a2 a3 a4) -> a1 -> BlockId blockId b = case b of { Build_BlockInfo blockId0 blockSuccessors0 blockOps0 setBlockOps0 -> blockId0} blockSuccessors :: (BlockInfo a1 a2 a3 a4) -> a1 -> [] BlockId blockSuccessors b = case b of { Build_BlockInfo blockId0 blockSuccessors0 blockOps0 setBlockOps0 -> blockSuccessors0} blockOps :: (BlockInfo a1 a2 a3 a4) -> a1 -> (,) ((,) ([] a3) ([] a3)) ([] a3) blockOps b = case b of { Build_BlockInfo blockId0 blockSuccessors0 blockOps0 setBlockOps0 -> blockOps0} setBlockOps :: (BlockInfo a1 a2 a3 a4) -> a1 -> ([] a4) -> ([] a4) -> ([] a4) -> a2 setBlockOps b = case b of { Build_BlockInfo blockId0 blockSuccessors0 blockOps0 setBlockOps0 -> setBlockOps0} allBlockOps :: (BlockInfo a1 a2 a3 a4) -> a1 -> [] a3 allBlockOps binfo block = case blockOps binfo block of { (,) p c -> case p of { (,) a b -> (Prelude.++) a ((Prelude.++) b c)}} blockSize :: (BlockInfo a1 a2 a3 a4) -> a1 -> Prelude.Int blockSize binfo block = Data.List.length (allBlockOps binfo block) foldOps :: (BlockInfo a1 a2 a3 a4) -> (a5 -> a3 -> a5) -> a5 -> ([] a1) -> a5 foldOps binfo f z = Data.List.foldl' (\bacc blk -> Data.List.foldl' f bacc (allBlockOps binfo blk)) z countOps :: (BlockInfo a1 a2 a3 a4) -> ([] a1) -> Prelude.Int countOps binfo = foldOps binfo (\acc x -> (Prelude.succ) acc) 0