stack-3.3.1: The Haskell Tool Stack
Safe HaskellNone
LanguageGHC2021

Stack.PackageDump

Synopsis

Documentation

type Line = Text Source #

A single line of input, not including line endings

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.

Constructors

DumpPackage 

Fields

Instances

Instances details
Read DumpPackage Source # 
Instance details

Defined in Stack.Types.DumpPackage

Show DumpPackage Source # 
Instance details

Defined in Stack.Types.DumpPackage

Methods

showsPrec :: Int -> DumpPackage -> ShowS #

show :: DumpPackage -> String #

showList :: [DumpPackage] -> ShowS #

Eq DumpPackage Source # 
Instance details

Defined in Stack.Types.DumpPackage

conduitDumpPackage :: forall (m :: Type -> Type). MonadThrow m => ConduitM Text DumpPackage m () Source #

Convert a stream of bytes into a stream of DumpPackages

ghcPkgDump Source #

Arguments

:: (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.

ghcPkgDescribe Source #

Arguments

:: (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.

ghcPkgField Source #

Arguments

:: (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).

sinkMatching Source #

Arguments

:: 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.

pruneDeps Source #

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