|
|
|
|
Synopsis |
|
|
|
Documentation |
|
type DsM result = TcRnIf DsGblEnv DsLclEnv result |
|
mapM |
|
mapAndUnzipM |
|
initDs :: HscEnv -> Module -> GlobalRdrEnv -> TypeEnv -> 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 |
Monadic version of foldl
|
|
foldrM :: Monad m => (b -> a -> m a) -> a -> [b] -> m a |
Monadic version of foldr
|
|
ifOptM :: DynFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () |
Do it flag is true
|
|
Applicative (pure, <*>) |
|
<$> |
|
newLocalName :: Name -> TcRnIf gbl lcl Name |
|
duplicateLocalDs :: Id -> DsM Id |
|
newSysLocalDs :: Type -> DsM Id |
|
newSysLocalsDs :: [Type] -> DsM [Id] |
|
newUniqueId :: Name -> Type -> DsM Id |
|
newFailLocalDs :: Type -> DsM Id |
|
getSrcSpanDs :: DsM SrcSpan |
|
putSrcSpanDs :: SrcSpan -> DsM a -> DsM a |
|
getModuleDs :: DsM Module |
|
newUnique :: TcRnIf gbl lcl Unique |
|
data UniqSupply |
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 |
|
getDOptsDs :: DsM DynFlags |
|
getGhcModeDs :: DsM GhcMode |
|
doptDs :: DynFlag -> TcRnIf gbl lcl Bool |
|
dsLookupGlobal :: Name -> DsM TyThing |
|
dsLookupGlobalId :: Name -> DsM Id |
|
dsLookupTyCon :: Name -> DsM TyCon |
|
dsLookupDataCon :: Name -> DsM DataCon |
|
dsLookupClass :: Name -> DsM Class |
|
type DsMetaEnv = NameEnv DsMetaVal |
|
data DsMetaVal |
|
|
dsLookupMetaEnv :: Name -> DsM (Maybe DsMetaVal) |
|
dsExtendMetaEnv :: DsMetaEnv -> DsM a -> DsM a |
|
type DsWarning = (SrcSpan, SDoc) |
|
warnDs :: SDoc -> DsM () |
|
failWithDs :: SDoc -> DsM a |
|
data DsMatchContext |
|
|
data EquationInfo |
Constructors | | Instances | |
|
|
data MatchResult |
|
|
type DsWrapper = CoreExpr -> CoreExpr |
|
idDsWrapper :: DsWrapper |
|
data CanItFail |
|
|
orFail :: CanItFail -> CanItFail -> CanItFail |
|
Produced by Haddock version 2.4.2 |