| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
DsMonad
- type DsM = TcRnIf DsGblEnv DsLclEnv
- mapM :: Traversable t => forall a m b. Monad m => (a -> m b) -> t a -> m (t b)
- mapAndUnzipM :: Monad m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- initDs :: HscEnv -> Module -> GlobalRdrEnv -> TypeEnv -> FamInstEnv -> DsM a -> IO (Messages, Maybe a)
- initDsTc :: DsM a -> TcM a
- fixDs :: (a -> DsM a) -> DsM a
- foldlM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a
- foldrM :: Monad m => (b -> a -> m a) -> a -> [b] -> m a
- whenGOptM :: GeneralFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- unsetWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- class Functor f => Applicative f where
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- newLocalName :: Name -> TcM Name
- duplicateLocalDs :: Id -> DsM Id
- newSysLocalDs :: Type -> DsM Id
- newSysLocalsDs :: [Type] -> DsM [Id]
- newUniqueId :: Id -> Type -> DsM Id
- newFailLocalDs :: Type -> DsM Id
- newPredVarDs :: PredType -> DsM Var
- getSrcSpanDs :: DsM SrcSpan
- putSrcSpanDs :: SrcSpan -> DsM a -> DsM a
- mkPrintUnqualifiedDs :: DsM PrintUnqualified
- newUnique :: TcRnIf gbl lcl Unique
- data UniqSupply
- newUniqueSupply :: TcRnIf gbl lcl UniqSupply
- getGhcModeDs :: DsM GhcMode
- dsGetFamInstEnvs :: DsM FamInstEnvs
- dsGetStaticBindsVar :: DsM (IORef [(Fingerprint, (Id, CoreExpr))])
- dsLookupGlobal :: Name -> DsM TyThing
- dsLookupGlobalId :: Name -> DsM Id
- dsDPHBuiltin :: (PArrBuiltin -> a) -> DsM a
- dsLookupTyCon :: Name -> DsM TyCon
- dsLookupDataCon :: Name -> DsM DataCon
- data PArrBuiltin = PArrBuiltin {
- lengthPVar :: Var
- replicatePVar :: Var
- singletonPVar :: Var
- mapPVar :: Var
- filterPVar :: Var
- zipPVar :: Var
- crossMapPVar :: Var
- indexPVar :: Var
- emptyPVar :: Var
- appPVar :: Var
- enumFromToPVar :: Var
- enumFromThenToPVar :: Var
- dsLookupDPHRdrEnv :: OccName -> DsM Name
- dsLookupDPHRdrEnv_maybe :: OccName -> DsM (Maybe Name)
- dsInitPArrBuiltin :: DsM a -> DsM a
- type DsMetaEnv = NameEnv DsMetaVal
- data DsMetaVal
- dsGetMetaEnv :: DsM (NameEnv DsMetaVal)
- dsLookupMetaEnv :: Name -> DsM (Maybe DsMetaVal)
- dsExtendMetaEnv :: DsMetaEnv -> DsM a -> DsM a
- type DsWarning = (SrcSpan, SDoc)
- warnDs :: SDoc -> DsM ()
- failWithDs :: SDoc -> DsM a
- discardWarningsDs :: DsM a -> DsM a
- data DsMatchContext = DsMatchContext (HsMatchContext Name) SrcSpan
- data EquationInfo = EqnInfo {
- eqn_pats :: [Pat Id]
- eqn_rhs :: MatchResult
- data MatchResult = MatchResult CanItFail (CoreExpr -> DsM CoreExpr)
- type DsWrapper = CoreExpr -> CoreExpr
- idDsWrapper :: DsWrapper
- data CanItFail
- orFail :: CanItFail -> CanItFail -> CanItFail
Documentation
mapM :: Traversable t => forall a m b. Monad m => (a -> m b) -> t a -> m (t b) Source
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and collect the results. For
a version that ignores the results see mapM_.
mapAndUnzipM :: Monad m => (a -> m (b, c)) -> [a] -> m ([b], [c]) Source
The mapAndUnzipM function maps its first argument over a list, returning
the result as a pair of lists. This function is mainly used with complicated
data structures or a state-transforming monad.
initDs :: HscEnv -> Module -> GlobalRdrEnv -> TypeEnv -> FamInstEnv -> DsM a -> IO (Messages, Maybe a) Source
whenGOptM :: GeneralFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () Source
unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source
unsetWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source
class Functor f => Applicative f where Source
A functor with application, providing operations to
A minimal complete definition must include implementations of these functions satisfying the following laws:
- identity
pureid<*>v = v- composition
pure(.)<*>u<*>v<*>w = u<*>(v<*>w)- homomorphism
puref<*>purex =pure(f x)- interchange
u
<*>purey =pure($y)<*>u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor instance for f will satisfy
If f is also a Monad, it should satisfy
(which implies that pure and <*> satisfy the applicative functor laws).
Methods
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 Source
Sequential application.
(*>) :: f a -> f b -> f b infixl 4 Source
Sequence actions, discarding the value of the first argument.
(<*) :: f a -> f b -> f a infixl 4 Source
Sequence actions, discarding the value of the second argument.
Instances
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 Source
An infix synonym for fmap.
Examples
Convert from a to a Maybe Int using Maybe Stringshow:
>>>show <$> NothingNothing>>>show <$> Just 3Just "3"
Convert from an to an Either Int IntEither IntString using show:
>>>show <$> Left 17Left 17>>>show <$> Right 17Right "17"
Double each element of a list:
>>>(*2) <$> [1,2,3][2,4,6]
Apply even to the second element of a pair:
>>>even <$> (2,2)(2,True)
newLocalName :: Name -> TcM Name Source
duplicateLocalDs :: Id -> DsM Id Source
newSysLocalDs :: Type -> DsM Id Source
newSysLocalsDs :: [Type] -> DsM [Id] Source
newFailLocalDs :: Type -> DsM Id Source
newPredVarDs :: PredType -> DsM Var Source
putSrcSpanDs :: SrcSpan -> DsM a -> DsM a Source
data UniqSupply Source
A value of type UniqSupply is unique, and it can
supply one distinct Unique. Also, from the supply, one can
also manufacture an arbitrary number of further UniqueSupply values,
which will be distinct from the first and from all others.
newUniqueSupply :: TcRnIf gbl lcl UniqSupply Source
dsGetStaticBindsVar :: DsM (IORef [(Fingerprint, (Id, CoreExpr))]) Source
Gets a reference to the SPT entries created so far.
dsLookupGlobal :: Name -> DsM TyThing Source
dsLookupGlobalId :: Name -> DsM Id Source
dsDPHBuiltin :: (PArrBuiltin -> a) -> DsM a Source
Get a name from Data.Array.Parallel for the desugarer, from the ds_parr_bi component of the
global desugerar environment.
dsLookupTyCon :: Name -> DsM TyCon Source
dsLookupDataCon :: Name -> DsM DataCon Source
data PArrBuiltin Source
Constructors
| PArrBuiltin | |
Fields
| |
dsLookupDPHRdrEnv :: OccName -> DsM Name Source
dsInitPArrBuiltin :: DsM a -> DsM a Source
dsExtendMetaEnv :: DsMetaEnv -> DsM a -> DsM a Source
failWithDs :: SDoc -> DsM a Source
discardWarningsDs :: DsM a -> DsM a Source
data DsMatchContext Source
Constructors
| DsMatchContext (HsMatchContext Name) SrcSpan |
data EquationInfo Source
Instances
data MatchResult Source
Constructors
| MatchResult CanItFail (CoreExpr -> DsM CoreExpr) |