| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
CoreMonad
Synopsis
- data CoreToDo
- = CoreDoSimplify Int SimplMode
 - | CoreDoPluginPass String CorePluginPass
 - | CoreDoFloatInwards
 - | CoreDoFloatOutwards FloatOutSwitches
 - | CoreLiberateCase
 - | CoreDoPrintCore
 - | CoreDoStaticArgs
 - | CoreDoCallArity
 - | CoreDoExitify
 - | CoreDoStrictness
 - | CoreDoWorkerWrapper
 - | CoreDoSpecialising
 - | CoreDoSpecConstr
 - | CoreCSE
 - | CoreDoRuleCheck CompilerPhase String
 - | CoreDoNothing
 - | CoreDoPasses [CoreToDo]
 - | CoreDesugar
 - | CoreDesugarOpt
 - | CoreTidy
 - | CorePrep
 - | CoreOccurAnal
 
 - runWhen :: Bool -> CoreToDo -> CoreToDo
 - runMaybe :: Maybe a -> (a -> CoreToDo) -> CoreToDo
 - data SimplMode = SimplMode {
- sm_names :: [String]
 - sm_phase :: CompilerPhase
 - sm_dflags :: DynFlags
 - sm_rules :: Bool
 - sm_inline :: Bool
 - sm_case_case :: Bool
 - sm_eta_expand :: Bool
 
 - data FloatOutSwitches = FloatOutSwitches {}
 - pprPassDetails :: CoreToDo -> SDoc
 - type CorePluginPass = ModGuts -> CoreM ModGuts
 - bindsOnlyPass :: (CoreProgram -> CoreM CoreProgram) -> ModGuts -> CoreM ModGuts
 - data SimplCount
 - doSimplTick :: DynFlags -> Tick -> SimplCount -> SimplCount
 - doFreeSimplTick :: Tick -> SimplCount -> SimplCount
 - simplCountN :: SimplCount -> Int
 - pprSimplCount :: SimplCount -> SDoc
 - plusSimplCount :: SimplCount -> SimplCount -> SimplCount
 - zeroSimplCount :: DynFlags -> SimplCount
 - isZeroSimplCount :: SimplCount -> Bool
 - hasDetailedCounts :: SimplCount -> Bool
 - data Tick
 - data CoreM a
 - runCoreM :: HscEnv -> RuleBase -> UniqSupply -> Module -> ModuleSet -> PrintUnqualified -> SrcSpan -> CoreM a -> IO (a, SimplCount)
 - getHscEnv :: CoreM HscEnv
 - getRuleBase :: CoreM RuleBase
 - getModule :: HasModule m => m Module
 - getDynFlags :: HasDynFlags m => m DynFlags
 - getOrigNameCache :: CoreM OrigNameCache
 - getPackageFamInstEnv :: CoreM PackageFamInstEnv
 - getVisibleOrphanMods :: CoreM ModuleSet
 - getPrintUnqualified :: CoreM PrintUnqualified
 - getSrcSpanM :: CoreM SrcSpan
 - addSimplCount :: SimplCount -> CoreM ()
 - liftIO :: MonadIO m => IO a -> m a
 - liftIOWithCount :: IO (SimplCount, a) -> CoreM a
 - liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b
 - liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c
 - liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d
 - liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m e
 - reinitializeGlobals :: CoreM ()
 - getAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (UniqFM [a])
 - getFirstAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (UniqFM a)
 - putMsg :: SDoc -> CoreM ()
 - putMsgS :: String -> CoreM ()
 - errorMsg :: SDoc -> CoreM ()
 - errorMsgS :: String -> CoreM ()
 - warnMsg :: SDoc -> CoreM ()
 - fatalErrorMsg :: SDoc -> CoreM ()
 - fatalErrorMsgS :: String -> CoreM ()
 - debugTraceMsg :: SDoc -> CoreM ()
 - debugTraceMsgS :: String -> CoreM ()
 - dumpIfSet_dyn :: DumpFlag -> String -> SDoc -> CoreM ()
 
Configuration of the core-to-core passes
Constructors
Constructors
| SimplMode | |
Fields 
  | |
data FloatOutSwitches Source #
Constructors
| FloatOutSwitches | |
Fields 
  | |
Instances
pprPassDetails :: CoreToDo -> SDoc Source #
Plugins
bindsOnlyPass :: (CoreProgram -> CoreM CoreProgram) -> ModGuts -> CoreM ModGuts Source #
Counting
data SimplCount Source #
doSimplTick :: DynFlags -> Tick -> SimplCount -> SimplCount Source #
doFreeSimplTick :: Tick -> SimplCount -> SimplCount Source #
simplCountN :: SimplCount -> Int Source #
pprSimplCount :: SimplCount -> SDoc Source #
plusSimplCount :: SimplCount -> SimplCount -> SimplCount Source #
zeroSimplCount :: DynFlags -> SimplCount Source #
isZeroSimplCount :: SimplCount -> Bool Source #
hasDetailedCounts :: SimplCount -> Bool Source #
Constructors
The monad
The monad used by Core-to-Core passes to access common state, register simplification statistics and so on
Instances
| Monad CoreM Source # | |
| Functor CoreM Source # | |
| Applicative CoreM Source # | |
| MonadIO CoreM Source # | |
| Alternative CoreM Source # | |
| MonadPlus CoreM Source # | |
| MonadUnique CoreM Source # | |
Defined in CoreMonad Methods getUniqueSupplyM :: CoreM UniqSupply Source # getUniqueM :: CoreM Unique Source # getUniquesM :: CoreM [Unique] Source #  | |
| HasModule CoreM Source # | |
| HasDynFlags CoreM Source # | |
| MonadThings CoreM Source # | |
runCoreM :: HscEnv -> RuleBase -> UniqSupply -> Module -> ModuleSet -> PrintUnqualified -> SrcSpan -> CoreM a -> IO (a, SimplCount) Source #
Reading from the monad
getDynFlags :: HasDynFlags m => m DynFlags Source #
getOrigNameCache :: CoreM OrigNameCache Source #
The original name cache is the current mapping from Module and
 OccName to a compiler-wide unique Name
Writing to the monad
addSimplCount :: SimplCount -> CoreM () Source #
Lifting into the monad
liftIOWithCount :: IO (SimplCount, a) -> CoreM a Source #
Lift an IO operation into CoreM while consuming its SimplCount
liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b Source #
Lift an IO operation with 1 argument into another monad
liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c Source #
Lift an IO operation with 2 arguments into another monad
liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d Source #
Lift an IO operation with 3 arguments into another monad
liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m e Source #
Lift an IO operation with 4 arguments into another monad
Global initialization
reinitializeGlobals :: CoreM () Source #
Deprecated: It is not necessary to call reinitializeGlobals. Since GHC 8.2, this function is a no-op and will be removed in GHC 8.4
Dealing with annotations
getAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (UniqFM [a]) Source #
Get all annotations of a given type. This happens lazily, that is no deserialization will take place until the [a] is actually demanded and the [a] can also be empty (the UniqFM is not filtered).
This should be done once at the start of a Core-to-Core pass that uses annotations.
See Note [Annotations]
getFirstAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (UniqFM a) Source #
Get at most one annotation of a given type per Unique.
Screen output
errorMsg :: SDoc -> CoreM () Source #
Output an error to the screen. Does not cause the compiler to die.
errorMsgS :: String -> CoreM () Source #
Output an error to the screen. Does not cause the compiler to die.
fatalErrorMsg :: SDoc -> CoreM () Source #
Output a fatal error to the screen. Does not cause the compiler to die.
fatalErrorMsgS :: String -> CoreM () Source #
Output a fatal error to the screen. Does not cause the compiler to die.
debugTraceMsg :: SDoc -> CoreM () Source #
Outputs a debugging message at verbosity level of -v or higher
debugTraceMsgS :: String -> CoreM () Source #
Output a string debugging message at verbosity level of -v or higher