| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Stack.PackageDump
- type Line = Text
 - eachSection :: Monad m => Sink Line m a -> Conduit Text m a
 - eachPair :: Monad m => (Text -> Sink Line m a) -> Conduit Line m a
 - data DumpPackage profiling haddock symbols = DumpPackage {
- dpGhcPkgId :: !GhcPkgId
 - dpPackageIdent :: !PackageIdentifier
 - dpLicense :: !(Maybe License)
 - dpLibDirs :: ![FilePath]
 - dpLibraries :: ![Text]
 - dpHasExposedModules :: !Bool
 - dpExposedModules :: ![Text]
 - dpDepends :: ![GhcPkgId]
 - dpHaddockInterfaces :: ![FilePath]
 - dpHaddockHtml :: !(Maybe FilePath)
 - dpProfiling :: !profiling
 - dpHaddock :: !haddock
 - dpSymbols :: !symbols
 - dpIsExposed :: !Bool
 
 - conduitDumpPackage :: MonadThrow m => Conduit Text m (DumpPackage () () ())
 - ghcPkgDump :: (MonadUnliftIO m, MonadLogger m) => EnvOverride -> WhichCompiler -> [Path Abs Dir] -> Sink Text IO a -> m a
 - ghcPkgDescribe :: (MonadUnliftIO m, MonadLogger m) => PackageName -> EnvOverride -> WhichCompiler -> [Path Abs Dir] -> Sink Text IO a -> m a
 - newInstalledCache :: MonadIO m => m InstalledCache
 - loadInstalledCache :: (MonadLogger m, MonadUnliftIO m) => Path Abs File -> m InstalledCache
 - saveInstalledCache :: (MonadLogger m, MonadIO m) => Path Abs File -> InstalledCache -> m ()
 - addProfiling :: MonadIO m => InstalledCache -> Conduit (DumpPackage a b c) m (DumpPackage Bool b c)
 - addHaddock :: MonadIO m => InstalledCache -> Conduit (DumpPackage a b c) m (DumpPackage a Bool c)
 - addSymbols :: MonadIO m => InstalledCache -> Conduit (DumpPackage a b c) m (DumpPackage a b Bool)
 - sinkMatching :: Monad m => Bool -> Bool -> Bool -> Map PackageName Version -> Consumer (DumpPackage Bool Bool Bool) m (Map PackageName (DumpPackage Bool Bool Bool))
 - pruneDeps :: (Ord name, Ord id) => (id -> name) -> (item -> id) -> (item -> [id]) -> (item -> item -> item) -> [item] -> Map name item
 
Documentation
eachSection :: Monad m => Sink Line m a -> Conduit Text m a Source #
Apply the given Sink to each section of output, broken by a single line containing ---
data DumpPackage profiling haddock symbols Source #
Dump information for a single package
Constructors
| DumpPackage | |
Fields 
  | |
conduitDumpPackage :: MonadThrow m => Conduit Text m (DumpPackage () () ()) Source #
Convert a stream of bytes into a stream of DumpPackages
Arguments
| :: (MonadUnliftIO m, MonadLogger m) | |
| => EnvOverride | |
| -> WhichCompiler | |
| -> [Path Abs Dir] | if empty, use global  | 
| -> Sink Text IO a | |
| -> m a | 
Call ghc-pkg dump with appropriate flags and stream to the given Sink, for a single database
Arguments
| :: (MonadUnliftIO m, MonadLogger m) | |
| => PackageName | |
| -> EnvOverride | |
| -> WhichCompiler | |
| -> [Path Abs Dir] | if empty, use global  | 
| -> Sink Text IO a | |
| -> m a | 
Call ghc-pkg describe with appropriate flags and stream to the given Sink, for a single database
newInstalledCache :: MonadIO m => m InstalledCache Source #
Create a new, empty InstalledCache
loadInstalledCache :: (MonadLogger m, MonadUnliftIO m) => Path Abs File -> m InstalledCache Source #
Load a InstalledCache from disk, swallowing any errors and returning an
 empty cache.
saveInstalledCache :: (MonadLogger m, MonadIO m) => Path Abs File -> InstalledCache -> m () Source #
Save a InstalledCache to disk
addProfiling :: MonadIO m => InstalledCache -> Conduit (DumpPackage a b c) m (DumpPackage Bool b c) Source #
Add profiling information to the stream of DumpPackages
addHaddock :: MonadIO m => InstalledCache -> Conduit (DumpPackage a b c) m (DumpPackage a Bool c) Source #
Add haddock information to the stream of DumpPackages
addSymbols :: MonadIO m => InstalledCache -> Conduit (DumpPackage a b c) m (DumpPackage a b Bool) Source #
Add debugging symbol information to the stream of DumpPackages
Arguments
| :: Monad m | |
| => Bool | require profiling?  | 
| -> Bool | require haddock?  | 
| -> Bool | require debugging symbols?  | 
| -> Map PackageName Version | allowed versions  | 
| -> Consumer (DumpPackage Bool Bool Bool) m (Map PackageName (DumpPackage Bool Bool Bool)) | 
Find the package IDs matching the given constraints with all dependencies installed.
 Packages not mentioned in the provided Map are allowed to be present too.
Arguments
| :: (Ord name, Ord id) | |
| => (id -> name) | extract the name from an id  | 
| -> (item -> id) | the id of an item  | 
| -> (item -> [id]) | get the dependencies of an item  | 
| -> (item -> item -> item) | choose the desired of two possible items  | 
| -> [item] | input items  | 
| -> Map name item | 
Prune a list of possible packages down to those whose dependencies are met.
- id uniquely identifies an item
 - There can be multiple items per name