Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Synopsis
- data InternaliseM a
- runInternaliseM :: MonadFreshNames m => Bool -> InternaliseM () -> m (Stms SOACS, [FunDef SOACS])
- throwError :: MonadError e m => e -> m a
- type VarSubstitutions = Map VName [SubExp]
- data InternaliseEnv = InternaliseEnv {}
- type FunInfo = ([VName], [DeclType], [FParam], [(SubExp, Type)] -> Maybe [DeclExtType])
- substitutingVars :: VarSubstitutions -> InternaliseM a -> InternaliseM a
- lookupSubst :: VName -> InternaliseM (Maybe [SubExp])
- addFunDef :: FunDef SOACS -> InternaliseM ()
- lookupFunction :: VName -> InternaliseM FunInfo
- lookupFunction' :: VName -> InternaliseM (Maybe FunInfo)
- lookupConst :: VName -> InternaliseM (Maybe [SubExp])
- bindFunction :: VName -> FunDef SOACS -> FunInfo -> InternaliseM ()
- bindConstant :: VName -> FunDef SOACS -> InternaliseM ()
- localConstsScope :: InternaliseM a -> InternaliseM a
- assert :: String -> SubExp -> ErrorMsg SubExp -> SrcLoc -> InternaliseM Certificates
- module Futhark.Tools
Documentation
data InternaliseM a Source #
Instances
runInternaliseM :: MonadFreshNames m => Bool -> InternaliseM () -> m (Stms SOACS, [FunDef SOACS]) Source #
throwError :: MonadError e m => e -> m a #
Is used within a monadic computation to begin exception processing.
type VarSubstitutions = Map VName [SubExp] Source #
A mapping from external variable names to the corresponding internalised subexpressions.
data InternaliseEnv Source #
InternaliseEnv | |
|
Instances
MonadReader InternaliseEnv InternaliseM Source # | |
Defined in Futhark.Internalise.Monad ask :: InternaliseM InternaliseEnv # local :: (InternaliseEnv -> InternaliseEnv) -> InternaliseM a -> InternaliseM a # reader :: (InternaliseEnv -> a) -> InternaliseM a # |
substitutingVars :: VarSubstitutions -> InternaliseM a -> InternaliseM a Source #
lookupSubst :: VName -> InternaliseM (Maybe [SubExp]) Source #
addFunDef :: FunDef SOACS -> InternaliseM () Source #
Add a function definition to the program being constructed.
lookupFunction' :: VName -> InternaliseM (Maybe FunInfo) Source #
lookupConst :: VName -> InternaliseM (Maybe [SubExp]) Source #
bindFunction :: VName -> FunDef SOACS -> FunInfo -> InternaliseM () Source #
bindConstant :: VName -> FunDef SOACS -> InternaliseM () Source #
localConstsScope :: InternaliseM a -> InternaliseM a Source #
assert :: String -> SubExp -> ErrorMsg SubExp -> SrcLoc -> InternaliseM Certificates Source #
Convenient reexports
module Futhark.Tools