stack-1.6.3: The Haskell Tool Stack

Safe HaskellNone
LanguageHaskell2010

Stack.PackageDump

Synopsis

Documentation

type Line = Text Source #

A single line of input, not including line endings

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

eachPair :: Monad m => (Text -> Sink Line m a) -> Conduit Line m a Source #

Grab each key/value pair

data DumpPackage profiling haddock symbols Source #

Dump information for a single package

Instances

(Eq symbols, Eq haddock, Eq profiling) => Eq (DumpPackage profiling haddock symbols) Source # 

Methods

(==) :: DumpPackage profiling haddock symbols -> DumpPackage profiling haddock symbols -> Bool #

(/=) :: DumpPackage profiling haddock symbols -> DumpPackage profiling haddock symbols -> Bool #

(Show symbols, Show haddock, Show profiling) => Show (DumpPackage profiling haddock symbols) Source # 

Methods

showsPrec :: Int -> DumpPackage profiling haddock symbols -> ShowS #

show :: DumpPackage profiling haddock symbols -> String #

showList :: [DumpPackage profiling haddock symbols] -> ShowS #

conduitDumpPackage :: MonadThrow m => Conduit Text m (DumpPackage () () ()) Source #

Convert a stream of bytes into a stream of DumpPackages

ghcPkgDump Source #

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

ghcPkgDescribe Source #

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

sinkMatching Source #

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.

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