Safe Haskell | None |
---|---|
Language | Haskell98 |
This module introduces a "lighter" GhcMonad typeclass which doesn't require an instance of
ExceptionMonad
, and can therefore be used for both CoreM
and Ghc
.
Synopsis
- class HasHscEnv m
- class (Functor m, MonadIO m, HasHscEnv m, HasDynFlags m) => GhcMonadLike m
- data ModuleInfo
- data TypecheckedModule = TypecheckedModule {}
- askHscEnv :: HasHscEnv m => m HscEnv
- getModuleGraph :: GhcMonadLike m => m ModuleGraph
- getModSummary :: GhcMonadLike m => ModuleName -> m ModSummary
- lookupModSummary :: GhcMonadLike m => ModuleName -> m (Maybe ModSummary)
- lookupGlobalName :: GhcMonadLike m => Name -> m (Maybe TyThing)
- lookupName :: GhcMonadLike m => Name -> m (Maybe TyThing)
- modInfoLookupName :: GhcMonadLike m => ModuleInfo -> Name -> m (Maybe TyThing)
- moduleInfoTc :: GhcMonadLike m => ModSummary -> TcGblEnv -> m ModuleInfo
- parseModule :: GhcMonadLike m => ModSummary -> m ParsedModule
- typecheckModule :: GhcMonadLike m => ParsedModule -> m TypecheckedModule
- desugarModule :: (GhcMonadLike m, IsTypecheckedModule t) => ModSummary -> t -> m ModGuts
- findModule :: GhcMonadLike m => ModuleName -> Maybe FastString -> m Module
- lookupModule :: GhcMonadLike m => ModuleName -> Maybe FastString -> m Module
Types and type classes
class (Functor m, MonadIO m, HasHscEnv m, HasDynFlags m) => GhcMonadLike m Source #
A typeclass which is very similar to the existing GhcMonad
, but it doesn't impose a
ExceptionMonad
constraint.
Instances
GhcMonadLike TcM Source # | |
Defined in Language.Haskell.Liquid.GHC.GhcMonadLike | |
GhcMonadLike Ghc Source # | |
Defined in Language.Haskell.Liquid.GHC.GhcMonadLike | |
GhcMonadLike Hsc Source # | |
Defined in Language.Haskell.Liquid.GHC.GhcMonadLike | |
GhcMonadLike CoreM Source # | |
Defined in Language.Haskell.Liquid.GHC.GhcMonadLike | |
GhcMonadLike (IfM lcl) Source # | |
Defined in Language.Haskell.Liquid.GHC.GhcMonadLike | |
(ExceptionMonad m, GhcMonadLike m) => GhcMonadLike (GhcT m) Source # | |
Defined in Language.Haskell.Liquid.GHC.GhcMonadLike |
data ModuleInfo Source #
Our own simplified version of ModuleInfo
to overcome the fact we cannot construct the "original"
one as the constructor is not exported, and getHomeModuleInfo
and getPackageModuleInfo
are not
exported either, so we had to backport them as well.
data TypecheckedModule Source #
Our own simplified version of TypecheckedModule
.
Functions and typeclass methods
getModuleGraph :: GhcMonadLike m => m ModuleGraph Source #
getModSummary :: GhcMonadLike m => ModuleName -> m ModSummary Source #
lookupModSummary :: GhcMonadLike m => ModuleName -> m (Maybe ModSummary) Source #
lookupGlobalName :: GhcMonadLike m => Name -> m (Maybe TyThing) Source #
lookupName :: GhcMonadLike m => Name -> m (Maybe TyThing) Source #
modInfoLookupName :: GhcMonadLike m => ModuleInfo -> Name -> m (Maybe TyThing) Source #
moduleInfoTc :: GhcMonadLike m => ModSummary -> TcGblEnv -> m ModuleInfo Source #
parseModule :: GhcMonadLike m => ModSummary -> m ParsedModule Source #
typecheckModule :: GhcMonadLike m => ParsedModule -> m TypecheckedModule Source #
desugarModule :: (GhcMonadLike m, IsTypecheckedModule t) => ModSummary -> t -> m ModGuts Source #
Desugar a typechecked module.
findModule :: GhcMonadLike m => ModuleName -> Maybe FastString -> m Module Source #
Takes a ModuleName
and possibly a UnitId
, and consults the
filesystem and package database to find the corresponding Module
,
using the algorithm that is used for an import
declaration.
lookupModule :: GhcMonadLike m => ModuleName -> Maybe FastString -> m Module Source #