Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
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 = DumpPackage {
- dpGhcPkgId :: !GhcPkgId
- dpPackageIdent :: !PackageIdentifier
- dpParentLibIdent :: !(Maybe PackageIdentifier)
- dpLicense :: !(Maybe License)
- dpLibDirs :: ![FilePath]
- dpLibraries :: ![Text]
- dpHasExposedModules :: !Bool
- dpExposedModules :: !(Set ModuleName)
- dpDepends :: ![GhcPkgId]
- dpHaddockInterfaces :: ![FilePath]
- dpHaddockHtml :: !(Maybe FilePath)
- dpIsExposed :: !Bool
- conduitDumpPackage :: MonadThrow m => ConduitM Text DumpPackage m ()
- ghcPkgDump :: (HasProcessContext env, HasTerm env) => GhcPkgExe -> [Path Abs Dir] -> ConduitM Text Void (RIO env) a -> RIO env a
- ghcPkgDescribe :: (HasCompiler env, HasProcessContext env, HasTerm env) => GhcPkgExe -> PackageName -> [Path Abs Dir] -> ConduitM Text Void (RIO env) a -> RIO env a
- sinkMatching :: Monad m => Map PackageName Version -> ConduitM DumpPackage o m (Map PackageName DumpPackage)
- 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 Source #
Type representing dump information for a single package, as output by the
ghc-pkg describe
command.
DumpPackage | |
|
Instances
Read DumpPackage Source # | |
Defined in Stack.Types.DumpPackage readsPrec :: Int -> ReadS DumpPackage # readList :: ReadS [DumpPackage] # readPrec :: ReadPrec DumpPackage # readListPrec :: ReadPrec [DumpPackage] # | |
Show DumpPackage Source # | |
Defined in Stack.Types.DumpPackage showsPrec :: Int -> DumpPackage -> ShowS # show :: DumpPackage -> String # showList :: [DumpPackage] -> ShowS # | |
Eq DumpPackage Source # | |
Defined in Stack.Types.DumpPackage (==) :: DumpPackage -> DumpPackage -> Bool # (/=) :: DumpPackage -> DumpPackage -> Bool # |
conduitDumpPackage :: MonadThrow m => ConduitM Text DumpPackage m () Source #
Convert a stream of bytes into a stream of DumpPackage
s
:: (HasProcessContext env, HasTerm env) | |
=> GhcPkgExe | |
-> [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
:: (HasCompiler env, HasProcessContext env, HasTerm env) | |
=> GhcPkgExe | |
-> PackageName | |
-> [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
:: Monad m | |
=> Map PackageName Version | allowed versions |
-> ConduitM DumpPackage o m (Map PackageName DumpPackage) |
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.
:: (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