Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data ModuleT i m a
- getModuleInfo :: (MonadModule m, ModName n) => n -> m (Maybe (ModuleInfo m))
- evalModuleT :: MonadIO m => ModuleT i m a -> Packages -> String -> (FilePath -> m i) -> m a
- runModuleT :: MonadIO m => ModuleT i m a -> Packages -> String -> (FilePath -> m i) -> Map ModuleName i -> m (a, Map ModuleName i)
- class Monad m => MonadModule m where
- type ModuleInfo m
- class ModName n where
- convertModuleName :: ModName n => n -> ModuleName
Module monad
When you need to resolve modules, you work in a ModuleT
monad (or
another monad that is an instance of MonadModule
) and use the
getModuleInfo
function.
It finds an installed module by its name and reads (and caches) its
info from the info file. Then you run a ModuleT
monadic action
using evalModuleT
or runModuleT
.
To run a ModuleT
action you'll also need to provide the set of
packages (represented by their InstalledPackageInfo
) in which to
search for modules. You can get such a set from either
getInstalledPackages
or readPackagesInfo
, depending on your use
case.
A standard module monad transformer.
i
is the type of module info, m
is the underlying monad.
MonadError e m => MonadError e (ModuleT i m) Source # | |
MonadReader r m => MonadReader r (ModuleT i m) Source # | |
MonadState s m => MonadState s (ModuleT i m) Source # | |
MonadWriter w m => MonadWriter w (ModuleT i m) Source # | |
MonadTrans (ModuleT i) Source # | |
Monad m => Monad (ModuleT i m) Source # | |
Functor m => Functor (ModuleT i m) Source # | |
Monad m => Applicative (ModuleT i m) Source # | |
MonadIO m => MonadIO (ModuleT i m) Source # | |
MonadCont m => MonadCont (ModuleT i m) Source # | |
(Functor m, Monad m) => MonadModule (ModuleT i m) Source # | |
type ModuleInfo (ModuleT i m) Source # | |
getModuleInfo :: (MonadModule m, ModName n) => n -> m (Maybe (ModuleInfo m)) Source #
Tries to find the module in the current set of packages, then find the module's info file, and reads and caches its contents.
Returns Nothing
if the module could not be found in the current set of
packages. If the module is found, but something else goes wrong (e.g.
there's no info file for it), an exception is thrown.
:: MonadIO m | |
=> ModuleT i m a | the monadic action to run |
-> Packages | packages in which to look for modules |
-> String | file extension of info files |
-> (FilePath -> m i) | how to read information from an info file |
-> m a |
Run a ModuleT
action.
This is a simplified version of runModuleT
.
:: MonadIO m | |
=> ModuleT i m a | the monadic action to run |
-> Packages | packages in which to look for modules |
-> String | file extension of info files |
-> (FilePath -> m i) | how to read information from an info file |
-> Map ModuleName i | initial set of module infos |
-> m (a, Map ModuleName i) | return value, plus all cached module infos (that is, the initial set plus all infos that have been read by the action itself) |
Run a ModuleT
action
class Monad m => MonadModule m where Source #
This class defines the interface that is used by getModuleInfo
, so
that you can use it in monads other than ModuleT
.
You don't typically have to define your own instances of this class, but here are a couple of cases when you might:
type ModuleInfo m Source #
The type of module info
lookupInCache :: ModName n => n -> m (Maybe (ModuleInfo m)) Source #
insertInCache :: ModName n => n -> ModuleInfo m -> m () Source #
getPackages :: m Packages Source #
readModuleInfo :: ModName n => [FilePath] -> n -> m (ModuleInfo m) Source #
Read the module info, given a list of search paths and the module name
Module names
class ModName n where Source #
Different libraries (Cabal, haskell-src-exts, ...) use different types to represent module names. Hence this class.
modToString :: n -> String Source #
convertModuleName :: ModName n => n -> ModuleName Source #
Convert module name from arbitrary representation to Cabal's one