hermit-1.0.0.0: Haskell Equational Reasoning Model-to-Implementation Tunnel

Safe HaskellNone
LanguageHaskell2010

HERMIT.Dictionary.Common

Contents

Description

Note: this module should NOT export externals. It is for common transformations needed by the other primitive modules.

Synopsis

Utility Transformations

applyInContextT :: Transform c m a b -> a -> Transform c m x b Source

apply a transformation to a value in the current context.

Finding function calls.

callT :: Monad m => Transform c m CoreExpr (CoreExpr, [CoreExpr]) Source

Lift GHC's collectArgs

callPredT :: Monad m => (Id -> [CoreExpr] -> Bool) -> Transform c m CoreExpr (CoreExpr, [CoreExpr]) Source

Succeeds if we are looking at an application matching the given predicate.

callNameT :: MonadCatch m => HermitName -> Transform c m CoreExpr (CoreExpr, [CoreExpr]) Source

Succeeds if we are looking at an application of given function returning zero or more arguments to which it is applied.

Note: comparison is performed with cmpHN2Var.

callSaturatedT :: Monad m => Transform c m CoreExpr (CoreExpr, [CoreExpr]) Source

Succeeds if we are looking at a fully saturated function call.

callNameG :: MonadCatch m => HermitName -> Transform c m CoreExpr () Source

Succeeds if we are looking at an application of given function

callDataConT :: MonadCatch m => Transform c m CoreExpr (DataCon, [Type], [CoreExpr]) Source

Succeeds if we are looking at an application of a data constructor.

callDataConNameT :: MonadCatch m => String -> Transform c m CoreExpr (DataCon, [Type], [CoreExpr]) Source

Succeeds if we are looking at an application of a named data constructor.

Collecting variable bindings

progConsIdsT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, MonadCatch m) => Transform c m CoreProg [Id] Source

List the identifiers bound by the top-level binding group at the head of the program.

progConsRecIdsT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, Monad m) => Transform c m CoreProg [Id] Source

List the identifiers bound by a recursive top-level binding group at the head of the program.

progConsNonRecIdT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, Monad m) => Transform c m CoreProg Id Source

Return the identifier bound by a non-recursive top-level binding at the head of the program.

nonRecVarT :: (ExtendPath c Crumb, Monad m) => Transform c m CoreBind Var Source

Return the variable bound by a non-recursive let expression.

recIdsT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, Monad m) => Transform c m CoreBind [Id] Source

List all identifiers bound in a recursive binding group.

lamVarT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, Monad m) => Transform c m CoreExpr Var Source

Return the variable bound by a lambda expression.

letVarsT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, MonadCatch m) => Transform c m CoreExpr [Var] Source

List the variables bound by a let expression.

letRecIdsT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, Monad m) => Transform c m CoreExpr [Id] Source

List the identifiers bound by a recursive let expression.

letNonRecVarT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, Monad m) => Transform c m CoreExpr Var Source

Return the variable bound by a non-recursive let expression.

caseVarsT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, Monad m) => Transform c m CoreExpr [Var] Source

List all variables bound by a case expression (in the alternatives and the case binder).

caseBinderIdT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, Monad m) => Transform c m CoreExpr Id Source

Return the case binder.

caseAltVarsT :: (ExtendPath c Crumb, ReadPath c Crumb, AddBindings c, Monad m) => Transform c m CoreExpr [[Var]] Source

List the variables bound by all alternatives in a case expression.

Finding variables bound in the Context

boundVarsT :: (BoundVars c, Monad m) => Transform c m a VarSet Source

Lifted version of boundVars.

findBoundVarT :: (BoundVars c, MonadCatch m) => (Var -> Bool) -> Transform c m a Var Source

Find the unique variable bound in the context that matches the given name, failing if it is not unique.

findIdT :: (BoundVars c, HasHermitMEnv m, LiftCoreM m, MonadCatch m, MonadIO m, MonadThings m) => HermitName -> Transform c m a Id Source

Lookup the name in the context first, then, failing that, in GHC's global reader environment.

findVarT :: (BoundVars c, HasHermitMEnv m, LiftCoreM m, MonadCatch m, MonadIO m, MonadThings m) => HermitName -> Transform c m a Var Source

Lookup the name in the context first, then, failing that, in GHC's global reader environment.

findTyConT :: (BoundVars c, HasHermitMEnv m, LiftCoreM m, MonadCatch m, MonadIO m, MonadThings m) => HermitName -> Transform c m a TyCon Source

Lookup the name in the context first, then, failing that, in GHC's global reader environment.

findTypeT :: (BoundVars c, HasHermitMEnv m, LiftCoreM m, MonadCatch m, MonadIO m, MonadThings m) => HermitName -> Transform c m a Type Source

Lookup the name in the context first, then, failing that, in GHC's global reader environment.

varBindingDepthT :: (ReadBindings c, Monad m) => Var -> Transform c m g BindingDepth Source

Find the depth of a variable's binding.

varIsOccurrenceOfT :: (ExtendPath c Crumb, ReadBindings c, Monad m) => Var -> BindingDepth -> Transform c m Var Bool Source

Determine if the current variable matches the given variable, and is bound at the specified depth (helpful to detect shadowing).

exprIsOccurrenceOfT :: (ExtendPath c Crumb, ReadBindings c, Monad m) => Var -> BindingDepth -> Transform c m CoreExpr Bool Source

Determine if the current expression is an occurrence of the given variable, bound at the specified depth (helpful to detect shadowing).

withVarsInScope :: (AddBindings c, ReadPath c Crumb) => [Var] -> Transform c m a b -> Transform c m a b Source

Modify transformation to apply to current expression as if it were the body of a lambda binding the given variables.

wrongExprForm :: String -> String Source

Constructs a common error message. Argument String should be the desired form of the expression.