| Safe Haskell | None | 
|---|
HERMIT.Dictionary.GHC
- externals :: [External]
- anyCallR :: forall c m. (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, MonadCatch m) => Rewrite c m Core -> Rewrite c m Core
- substR :: MonadCatch m => Var -> CoreExpr -> Rewrite c m Core
- substAltR :: Monad m => Var -> CoreExpr -> Rewrite c m CoreAlt
- substCoreExpr :: Var -> CoreExpr -> CoreExpr -> CoreExpr
- inScope :: ReadBindings c => c -> Id -> Bool
- rule :: (ReadBindings c, HasCoreRules c) => String -> Rewrite c HermitM CoreExpr
- rules :: (ReadBindings c, HasCoreRules c) => [String] -> Rewrite c HermitM CoreExpr
- dynFlagsT :: HasDynFlags m => Translate c m a DynFlags
- arityOf :: ReadBindings c => c -> Id -> Int
- lintExprT :: (BoundVars c, Monad m, HasDynFlags m) => Translate c m CoreExpr String
- lintModuleT :: TranslateH ModGuts String
- specConstrR :: RewriteH ModGuts
- occurAnalyseR :: (AddBindings c, ExtendPath c Crumb, ReadPath c Crumb, MonadCatch m) => Rewrite c m Core
- occurAnalyseChangedR :: (AddBindings c, ExtendPath c Crumb, ReadPath c Crumb, MonadCatch m) => Rewrite c m Core
- occurAnalyseExprChangedR :: MonadCatch m => Rewrite c m CoreExpr
- occurAnalyseAndDezombifyR :: (AddBindings c, ExtendPath c Crumb, ReadPath c Crumb, MonadCatch m) => Rewrite c m Core
- dezombifyR :: (ExtendPath c Crumb, Monad m) => Rewrite c m CoreExpr
GHC-based Transformations
This module contains transformations that are reflections of GHC functions, or derived from GHC functions.
Externals that reflect GHC functions, or are derived from GHC functions.
anyCallR :: forall c m. (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, MonadCatch m) => Rewrite c m Core -> Rewrite c m CoreSource
Top-down traversal tuned to matching function calls.
Substitution
substR :: MonadCatch m => Var -> CoreExpr -> Rewrite c m CoreSource
Substitute all occurrences of a variable with an expression, in either a program or an expression.
substAltR :: Monad m => Var -> CoreExpr -> Rewrite c m CoreAltSource
Substitute all occurrences of a variable with an expression, in a case alternative.
substCoreExpr :: Var -> CoreExpr -> CoreExpr -> CoreExprSource
Substitute all occurrences of a variable with an expression, in an expression.
Utilities
inScope :: ReadBindings c => c -> Id -> BoolSource
Determine whether an identifier is in scope.
rule :: (ReadBindings c, HasCoreRules c) => String -> Rewrite c HermitM CoreExprSource
Lookup a rule and attempt to construct a corresponding rewrite.
rules :: (ReadBindings c, HasCoreRules c) => [String] -> Rewrite c HermitM CoreExprSource
dynFlagsT :: HasDynFlags m => Translate c m a DynFlagsSource
Lifted version of getDynFlags.
arityOf :: ReadBindings c => c -> Id -> IntSource
Try to figure out the arity of an identifier.
Lifted GHC capabilities
lintExprT :: (BoundVars c, Monad m, HasDynFlags m) => Translate c m CoreExpr StringSource
Note: this can miss several things that a whole-module core lint will find. For instance, running this on the RHS of a binding, the type of the RHS will not be checked against the type of the binding. Running on the whole let expression will catch that however.
lintModuleT :: TranslateH ModGuts StringSource
Run the Core Lint typechecker. Fails on errors, with error messages. Succeeds returning warnings.
specConstrR :: RewriteH ModGutsSource
Run GHC's specConstr pass, and apply any rules generated.
occurAnalyseR :: (AddBindings c, ExtendPath c Crumb, ReadPath c Crumb, MonadCatch m) => Rewrite c m CoreSource
Apply occurAnalyseExprR to all sub-expressions.
occurAnalyseChangedR :: (AddBindings c, ExtendPath c Crumb, ReadPath c Crumb, MonadCatch m) => Rewrite c m CoreSource
Occurrence analyse all sub-expressions, failing if the result is syntactically equal to the initial expression.
occurAnalyseExprChangedR :: MonadCatch m => Rewrite c m CoreExprSource
Occurrence analyse an expression, failing if the result is syntactically equal to the initial expression.
occurAnalyseAndDezombifyR :: (AddBindings c, ExtendPath c Crumb, ReadPath c Crumb, MonadCatch m) => Rewrite c m CoreSource
Run GHC's occurrence analyser, and also eliminate any zombies.
dezombifyR :: (ExtendPath c Crumb, Monad m) => Rewrite c m CoreExprSource
Zap the OccInfo in a zombie identifier.