Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- type Line = Text
- eachSection :: forall (m :: Type -> Type) a. Monad m => ConduitM Line Void m a -> ConduitM Text a m ()
- eachPair :: forall (m :: Type -> Type) a. Monad m => (Text -> ConduitM Line Void m a) -> ConduitM Line a m ()
- data DumpPackage = DumpPackage {
- ghcPkgId :: !GhcPkgId
- packageIdent :: !PackageIdentifier
- sublib :: !(Maybe SublibDump)
- license :: !(Maybe License)
- libDirs :: ![FilePath]
- libraries :: ![Text]
- hasExposedModules :: !Bool
- exposedModules :: !(Set ModuleName)
- depends :: ![GhcPkgId]
- haddockInterfaces :: ![FilePath]
- haddockHtml :: !(Maybe FilePath)
- isExposed :: !Bool
- conduitDumpPackage :: forall (m :: Type -> Type). 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
- ghcPkgField :: (HasCompiler env, HasProcessContext env, HasTerm env) => GhcPkgExe -> Path Abs Dir -> MungedPackageId -> String -> ConduitM Text Void (RIO env) a -> RIO env a
- sinkMatching :: forall (m :: Type -> Type) o. 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 :: forall (m :: Type -> Type) a. 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 :: forall (m :: Type -> Type) a. 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 installed 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 :: forall (m :: Type -> Type). 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] | A list of package databases. If empty, use the global package database. |
-> ConduitM Text Void (RIO env) a | Sink. |
-> RIO env a |
Call ghc-pkg dump
with appropriate flags and stream to the given sink,
using either the global package database or the given package databases.
:: (HasCompiler env, HasProcessContext env, HasTerm env) | |
=> GhcPkgExe | |
-> PackageName | |
-> [Path Abs Dir] | A list of package databases. If empty, use the global package database. |
-> ConduitM Text Void (RIO env) a | Sink. |
-> RIO env a |
Call ghc-pkg describe
with appropriate flags and stream to the given
sink, using either the global package database or the given package
databases.
:: (HasCompiler env, HasProcessContext env, HasTerm env) | |
=> GhcPkgExe | |
-> Path Abs Dir | A package database. |
-> MungedPackageId | A munged package identifier. |
-> String | A field name. |
-> ConduitM Text Void (RIO env) a | Sink. |
-> RIO env a |
Call ghc-pkg field
with appropriate flags and stream to the given
sink, using the given package database. Throws ExitCodeException
if the
process fails (for example, if the package is not found in the package
database or the field is not found in the package's *.conf file).
:: forall (m :: Type -> Type) o. 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