plugins-1.0ContentsIndex
System.Plugins.Env
Synopsis
withModEnv :: Env -> (ModEnv -> IO a) -> IO a
withDepEnv :: Env -> (DepEnv -> IO a) -> IO a
withPkgEnvs :: Env -> (PkgEnvs -> IO a) -> IO a
withMerged :: Env -> (MergeEnv -> IO a) -> IO a
modifyModEnv :: Env -> (ModEnv -> IO ModEnv) -> IO ()
modifyDepEnv :: Env -> (DepEnv -> IO DepEnv) -> IO ()
modifyPkgEnv :: Env -> (PkgEnvs -> IO PkgEnvs) -> IO ()
modifyMerged :: Env -> (MergeEnv -> IO MergeEnv) -> IO ()
addModule :: String -> Module -> IO ()
rmModule :: String -> IO Bool
addModules :: [(String, Module)] -> IO ()
isLoaded :: String -> IO Bool
loaded :: String -> IO Bool
addModuleDeps :: Module -> [Module] -> IO ()
getModuleDeps :: Module -> IO [Module]
rmModuleDeps :: Module -> IO ()
isMerged :: FilePath -> FilePath -> IO Bool
lookupMerged :: FilePath -> FilePath -> IO (Maybe FilePath)
addMerge :: FilePath -> FilePath -> FilePath -> IO ()
addPkgConf :: FilePath -> IO ()
union :: PkgEnvs -> [PackageConfig] -> PkgEnvs
grabDefaultPkgConf :: IO PkgEnvs
readPackageConf :: FilePath -> IO [PackageConfig]
lookupPkg :: PackageName -> IO ([FilePath], [FilePath])
Documentation
withModEnv :: Env -> (ModEnv -> IO a) -> IO a
apply f to the loaded objects Env, apply f to the package.conf FM locks up the MVar so you can't recursively call a function inside a with any -Env function. Nice and threadsafe
withDepEnv :: Env -> (DepEnv -> IO a) -> IO a
withPkgEnvs :: Env -> (PkgEnvs -> IO a) -> IO a
withMerged :: Env -> (MergeEnv -> IO a) -> IO a
modifyModEnv :: Env -> (ModEnv -> IO ModEnv) -> IO ()
modifyDepEnv :: Env -> (DepEnv -> IO DepEnv) -> IO ()
modifyPkgEnv :: Env -> (PkgEnvs -> IO PkgEnvs) -> IO ()
modifyMerged :: Env -> (MergeEnv -> IO MergeEnv) -> IO ()
addModule :: String -> Module -> IO ()
insert a loaded module name into the environment
rmModule :: String -> IO Bool
remove a module name from the environment. Returns True if the module was actually removed.
addModules :: [(String, Module)] -> IO ()
insert a list of module names all in one go
isLoaded :: String -> IO Bool
is a module/package already loaded?
loaded :: String -> IO Bool
addModuleDeps :: Module -> [Module] -> IO ()
Set the dependencies of a Module.
getModuleDeps :: Module -> IO [Module]
Get module dependencies. Nothing if none have been recored.
rmModuleDeps :: Module -> IO ()
Unrecord a module from the environment.
isMerged :: FilePath -> FilePath -> IO Bool
lookupMerged :: FilePath -> FilePath -> IO (Maybe FilePath)
addMerge :: FilePath -> FilePath -> FilePath -> IO ()
addPkgConf :: FilePath -> IO ()
Insert a single package.conf (containing multiple configs) means: create a new FM. insert packages into FM. add FM to end of list of FM stored in the environment.
union :: PkgEnvs -> [PackageConfig] -> PkgEnvs
add a new FM for the package.conf to the list of existing ones
grabDefaultPkgConf :: IO PkgEnvs
generate a PkgEnv from the system package.conf The path to the default package.conf was determined by configure This imposes a constraint that you must build your plugins with the same ghc you use to build hs-plugins. This is reasonable, we feel.
readPackageConf :: FilePath -> IO [PackageConfig]
lookupPkg :: PackageName -> IO ([FilePath], [FilePath])
Produced by Haddock version 0.8