module LinearScan.ScanState 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.Interval as Interval import qualified LinearScan.Lib as Lib type PhysReg = Prelude.Int type FixedIntervalsType = [] (Prelude.Maybe Interval.IntervalDesc) data ScanStateDesc = Build_ScanStateDesc Prelude.Int ([] Interval.IntervalDesc) FixedIntervalsType ([] ((,) Prelude.Int Prelude.Int)) ([] ((,) Prelude.Int PhysReg)) ([] ((,) Prelude.Int PhysReg)) ([] ((,) Prelude.Int (Prelude.Maybe PhysReg))) nextInterval :: Prelude.Int -> ScanStateDesc -> Prelude.Int nextInterval maxReg s = case s of { Build_ScanStateDesc nextInterval0 intervals0 fixedIntervals0 unhandled0 active0 inactive0 handled0 -> nextInterval0} type IntervalId = Prelude.Int intervals :: Prelude.Int -> ScanStateDesc -> [] Interval.IntervalDesc intervals maxReg s = case s of { Build_ScanStateDesc nextInterval0 intervals0 fixedIntervals0 unhandled0 active0 inactive0 handled0 -> intervals0} fixedIntervals :: Prelude.Int -> ScanStateDesc -> FixedIntervalsType fixedIntervals maxReg s = case s of { Build_ScanStateDesc nextInterval0 intervals0 fixedIntervals0 unhandled0 active0 inactive0 handled0 -> fixedIntervals0} unhandled :: Prelude.Int -> ScanStateDesc -> [] ((,) IntervalId Prelude.Int) unhandled maxReg s = case s of { Build_ScanStateDesc nextInterval0 intervals0 fixedIntervals0 unhandled0 active0 inactive0 handled0 -> unhandled0} active :: Prelude.Int -> ScanStateDesc -> [] ((,) IntervalId PhysReg) active maxReg s = case s of { Build_ScanStateDesc nextInterval0 intervals0 fixedIntervals0 unhandled0 active0 inactive0 handled0 -> active0} inactive :: Prelude.Int -> ScanStateDesc -> [] ((,) IntervalId PhysReg) inactive maxReg s = case s of { Build_ScanStateDesc nextInterval0 intervals0 fixedIntervals0 unhandled0 active0 inactive0 handled0 -> inactive0} handled :: Prelude.Int -> ScanStateDesc -> [] ((,) IntervalId (Prelude.Maybe PhysReg)) handled maxReg s = case s of { Build_ScanStateDesc nextInterval0 intervals0 fixedIntervals0 unhandled0 active0 inactive0 handled0 -> handled0} registerWithHighestPos :: Prelude.Int -> ([] (Prelude.Maybe Lib.Coq_oddnum)) -> (,) Prelude.Int (Prelude.Maybe Lib.Coq_oddnum) registerWithHighestPos maxReg = (LinearScan.Utils.vfoldl'_with_index) maxReg (\reg res x -> case res of { (,) r o -> case o of { Prelude.Just n -> case x of { Prelude.Just m -> case (Prelude.<=) ((Prelude.succ) ( n)) ( m) of { Prelude.True -> (,) reg (Prelude.Just m); Prelude.False -> (,) r (Prelude.Just n)}; Prelude.Nothing -> (,) reg Prelude.Nothing}; Prelude.Nothing -> (,) r Prelude.Nothing}}) ((,) ( 0) (Prelude.Just Lib.odd1)) data ScanStateStatus = Pending | InUse type ScanStateSig = ScanStateDesc packScanState :: Prelude.Int -> ScanStateStatus -> ScanStateDesc -> ScanStateDesc packScanState maxReg b sd = sd