ghc-6.10.3: The GHC APIContentsIndex
SimplMonad
Synopsis
data SimplM result
initSmpl :: DynFlags -> RuleBase -> (FamInstEnv, FamInstEnv) -> UniqSupply -> SimplM a -> (a, SimplCount)
getDOptsSmpl :: SimplM DynFlags
getSimplRules :: SimplM RuleBase
getFamEnvs :: SimplM (FamInstEnv, FamInstEnv)
class Monad m => MonadUnique m where
getUniqueSupplyM :: m UniqSupply
getUniqueM :: m Unique
getUniquesM :: m [Unique]
newId :: FastString -> Type -> SimplM Id
data SimplCount
data Tick
= PreInlineUnconditionally Id
| PostInlineUnconditionally Id
| UnfoldingDone Id
| RuleFired FastString
| LetFloatFromLet
| EtaExpansion Id
| EtaReduction Id
| BetaReduction Id
| CaseOfCase Id
| KnownBranch Id
| CaseMerge Id
| AltMerge Id
| CaseElim Id
| CaseIdentity Id
| FillInCaseDefault Id
| BottomFound
| SimplifierDone
tick :: Tick -> SimplM ()
freeTick :: Tick -> SimplM ()
getSimplCount :: SimplM SimplCount
zeroSimplCount :: DynFlags -> SimplCount
pprSimplCount :: SimplCount -> SDoc
plusSimplCount :: SimplCount -> SimplCount -> SimplCount
isZeroSimplCount :: SimplCount -> Bool
type SwitchChecker = SimplifierSwitch -> SwitchResult
data SwitchResult
= SwBool Bool
| SwString FastString
| SwInt Int
getSimplIntSwitch :: SwitchChecker -> (Int -> SimplifierSwitch) -> Int
isAmongSimpl :: [SimplifierSwitch] -> SimplifierSwitch -> SwitchResult
intSwitchSet :: (switch -> SwitchResult) -> (Int -> switch) -> Maybe Int
switchIsOn :: (switch -> SwitchResult) -> switch -> Bool
Documentation
data SimplM result
show/hide Instances
initSmpl :: DynFlags -> RuleBase -> (FamInstEnv, FamInstEnv) -> UniqSupply -> SimplM a -> (a, SimplCount)
getDOptsSmpl :: SimplM DynFlags
getSimplRules :: SimplM RuleBase
getFamEnvs :: SimplM (FamInstEnv, FamInstEnv)
class Monad m => MonadUnique m where
A monad for generating unique identifiers
Methods
getUniqueSupplyM :: m UniqSupply
Get a new UniqueSupply
getUniqueM :: m Unique
Get a new unique identifier
getUniquesM :: m [Unique]
Get an infinite list of new unique identifiers
show/hide Instances
newId :: FastString -> Type -> SimplM Id
data SimplCount
data Tick
Constructors
PreInlineUnconditionally Id
PostInlineUnconditionally Id
UnfoldingDone Id
RuleFired FastString
LetFloatFromLet
EtaExpansion Id
EtaReduction Id
BetaReduction Id
CaseOfCase Id
KnownBranch Id
CaseMerge Id
AltMerge Id
CaseElim Id
CaseIdentity Id
FillInCaseDefault Id
BottomFound
SimplifierDone
show/hide Instances
tick :: Tick -> SimplM ()
freeTick :: Tick -> SimplM ()
getSimplCount :: SimplM SimplCount
zeroSimplCount :: DynFlags -> SimplCount
pprSimplCount :: SimplCount -> SDoc
plusSimplCount :: SimplCount -> SimplCount -> SimplCount
isZeroSimplCount :: SimplCount -> Bool
type SwitchChecker = SimplifierSwitch -> SwitchResult
data SwitchResult
Constructors
SwBool Bool
SwString FastString
SwInt Int
getSimplIntSwitch :: SwitchChecker -> (Int -> SimplifierSwitch) -> Int
isAmongSimpl :: [SimplifierSwitch] -> SimplifierSwitch -> SwitchResult
intSwitchSet :: (switch -> SwitchResult) -> (Int -> switch) -> Maybe Int
switchIsOn :: (switch -> SwitchResult) -> switch -> Bool
Produced by Haddock version 2.4.2