| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Stack.PackageDump
Synopsis
- type Line = Text
- eachSection :: Monad m => ConduitM Line Void m a -> ConduitM Text a m ()
- eachPair :: Monad m => (Text -> ConduitM Line Void m a) -> ConduitM Line a m ()
- data DumpPackage profiling haddock symbols = DumpPackage {
- dpGhcPkgId :: !GhcPkgId
- dpPackageIdent :: !PackageIdentifier
- dpParentLibIdent :: !(Maybe 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 => ConduitM Text (DumpPackage () () ()) m ()
- ghcPkgDump :: (HasProcessContext env, HasLogFunc env) => WhichCompiler -> [Path Abs Dir] -> ConduitM Text Void (RIO env) a -> RIO env a
- ghcPkgDescribe :: (HasProcessContext env, HasLogFunc env) => PackageName -> WhichCompiler -> [Path Abs Dir] -> ConduitM Text Void (RIO env) a -> RIO env a
- newInstalledCache :: MonadIO m => m InstalledCache
- loadInstalledCache :: HasLogFunc env => Path Abs File -> RIO env InstalledCache
- saveInstalledCache :: HasLogFunc env => Path Abs File -> InstalledCache -> RIO env ()
- addProfiling :: MonadIO m => InstalledCache -> ConduitM (DumpPackage a b c) (DumpPackage Bool b c) m ()
- addHaddock :: MonadIO m => InstalledCache -> ConduitM (DumpPackage a b c) (DumpPackage a Bool c) m ()
- addSymbols :: MonadIO m => InstalledCache -> ConduitM (DumpPackage a b c) (DumpPackage a b Bool) m ()
- sinkMatching :: Monad m => Bool -> Bool -> Bool -> Map PackageName Version -> ConduitM (DumpPackage Bool Bool Bool) o 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 => ConduitM Line Void m a -> ConduitM Text a m () Source #
Apply the given Sink to each section of output, broken by a single line containing ---
eachPair :: Monad m => (Text -> ConduitM Line Void m a) -> ConduitM Line a m () Source #
Grab each key/value pair
data DumpPackage profiling haddock symbols Source #
Dump information for a single package
Constructors
| DumpPackage | |
Fields
| |
Instances
| (Eq profiling, Eq haddock, Eq symbols) => Eq (DumpPackage profiling haddock symbols) Source # | |
Defined in Stack.PackageDump Methods (==) :: DumpPackage profiling haddock symbols -> DumpPackage profiling haddock symbols -> Bool # (/=) :: DumpPackage profiling haddock symbols -> DumpPackage profiling haddock symbols -> Bool # | |
| (Show profiling, Show haddock, Show symbols) => Show (DumpPackage profiling haddock symbols) Source # | |
Defined in Stack.PackageDump Methods showsPrec :: Int -> DumpPackage profiling haddock symbols -> ShowS # show :: DumpPackage profiling haddock symbols -> String # showList :: [DumpPackage profiling haddock symbols] -> ShowS # | |
conduitDumpPackage :: MonadThrow m => ConduitM Text (DumpPackage () () ()) m () Source #
Convert a stream of bytes into a stream of DumpPackages
Arguments
| :: (HasProcessContext env, HasLogFunc env) | |
| => WhichCompiler | |
| -> [Path Abs Dir] | if empty, use global |
| -> ConduitM Text Void (RIO env) a | |
| -> RIO env a |
Call ghc-pkg dump with appropriate flags and stream to the given Sink, for a single database
Arguments
| :: (HasProcessContext env, HasLogFunc env) | |
| => PackageName | |
| -> WhichCompiler | |
| -> [Path Abs Dir] | if empty, use global |
| -> ConduitM Text Void (RIO env) a | |
| -> RIO env 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 :: HasLogFunc env => Path Abs File -> RIO env InstalledCache Source #
Load a InstalledCache from disk, swallowing any errors and returning an
empty cache.
saveInstalledCache :: HasLogFunc env => Path Abs File -> InstalledCache -> RIO env () Source #
Save a InstalledCache to disk
addProfiling :: MonadIO m => InstalledCache -> ConduitM (DumpPackage a b c) (DumpPackage Bool b c) m () Source #
Add profiling information to the stream of DumpPackages
addHaddock :: MonadIO m => InstalledCache -> ConduitM (DumpPackage a b c) (DumpPackage a Bool c) m () Source #
Add haddock information to the stream of DumpPackages
addSymbols :: MonadIO m => InstalledCache -> ConduitM (DumpPackage a b c) (DumpPackage a b Bool) m () 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 |
| -> ConduitM (DumpPackage Bool Bool Bool) o 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