cabal-install-solver-3.8.1.0: The command-line interface for Cabal and Hackage.
Safe HaskellNone
LanguageHaskell2010

Distribution.Solver.Types.ComponentDeps

Description

Fine-grained package dependencies

Like many others, this module is meant to be "double-imported":

import Distribution.Solver.Types.ComponentDeps (
    Component
  , ComponentDep
  , ComponentDeps
  )
import qualified Distribution.Solver.Types.ComponentDeps as CD
Synopsis

Fine-grained package dependencies

data Component Source #

Component of a package.

Instances

Instances details
Eq Component Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Ord Component Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Show Component Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Generic Component Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Associated Types

type Rep Component :: Type -> Type #

Binary Component Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Structured Component Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Pretty Component Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

type Rep Component Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

type ComponentDep a = (Component, a) Source #

Dependency for a single component.

data ComponentDeps a Source #

Fine-grained dependencies for a package.

Typically used as ComponentDeps [Dependency], to represent the list of dependencies for each named component within a package.

Instances

Instances details
Functor ComponentDeps Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Methods

fmap :: (a -> b) -> ComponentDeps a -> ComponentDeps b #

(<$) :: a -> ComponentDeps b -> ComponentDeps a #

Foldable ComponentDeps Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Methods

fold :: Monoid m => ComponentDeps m -> m #

foldMap :: Monoid m => (a -> m) -> ComponentDeps a -> m #

foldMap' :: Monoid m => (a -> m) -> ComponentDeps a -> m #

foldr :: (a -> b -> b) -> b -> ComponentDeps a -> b #

foldr' :: (a -> b -> b) -> b -> ComponentDeps a -> b #

foldl :: (b -> a -> b) -> b -> ComponentDeps a -> b #

foldl' :: (b -> a -> b) -> b -> ComponentDeps a -> b #

foldr1 :: (a -> a -> a) -> ComponentDeps a -> a #

foldl1 :: (a -> a -> a) -> ComponentDeps a -> a #

toList :: ComponentDeps a -> [a] #

null :: ComponentDeps a -> Bool #

length :: ComponentDeps a -> Int #

elem :: Eq a => a -> ComponentDeps a -> Bool #

maximum :: Ord a => ComponentDeps a -> a #

minimum :: Ord a => ComponentDeps a -> a #

sum :: Num a => ComponentDeps a -> a #

product :: Num a => ComponentDeps a -> a #

Traversable ComponentDeps Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Methods

traverse :: Applicative f => (a -> f b) -> ComponentDeps a -> f (ComponentDeps b) #

sequenceA :: Applicative f => ComponentDeps (f a) -> f (ComponentDeps a) #

mapM :: Monad m => (a -> m b) -> ComponentDeps a -> m (ComponentDeps b) #

sequence :: Monad m => ComponentDeps (m a) -> m (ComponentDeps a) #

Eq a => Eq (ComponentDeps a) Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Ord a => Ord (ComponentDeps a) Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Show a => Show (ComponentDeps a) Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Generic (ComponentDeps a) Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Associated Types

type Rep (ComponentDeps a) :: Type -> Type #

Semigroup a => Semigroup (ComponentDeps a) Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Semigroup a => Monoid (ComponentDeps a) Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Binary a => Binary (ComponentDeps a) Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

Structured a => Structured (ComponentDeps a) Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

type Rep (ComponentDeps a) Source # 
Instance details

Defined in Distribution.Solver.Types.ComponentDeps

type Rep (ComponentDeps a) = D1 ('MetaData "ComponentDeps" "Distribution.Solver.Types.ComponentDeps" "cabal-install-solver-3.8.1.0-DQHDRT4McfjEkCZkJP5jZc" 'True) (C1 ('MetaCons "ComponentDeps" 'PrefixI 'True) (S1 ('MetaSel ('Just "unComponentDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Component a))))

Constructing ComponentDeps

zip :: (Monoid a, Monoid b) => ComponentDeps a -> ComponentDeps b -> ComponentDeps (a, b) Source #

Zip two ComponentDeps together by Component, using mempty as the neutral element when a Component is present only in one.

filterDeps :: (Component -> a -> Bool) -> ComponentDeps a -> ComponentDeps a Source #

Keep only selected components (and their associated deps info).

fromLibraryDeps :: a -> ComponentDeps a Source #

ComponentDeps containing library dependencies only

fromSetupDeps :: a -> ComponentDeps a Source #

ComponentDeps containing setup dependencies only.

fromInstalled :: a -> ComponentDeps a Source #

ComponentDeps for installed packages.

We assume that installed packages only record their library dependencies.

Deconstructing ComponentDeps

flatDeps :: Monoid a => ComponentDeps a -> a Source #

All dependencies of a package.

This is just a synonym for fold, but perhaps a use of flatDeps is more obvious than a use of fold, and moreover this avoids introducing lots of #ifdefs for 7.10 just for the use of fold.

nonSetupDeps :: Monoid a => ComponentDeps a -> a Source #

All dependencies except the setup dependencies.

Prior to the introduction of setup dependencies in version 1.24 this would have been _all_ dependencies.

libraryDeps :: Monoid a => ComponentDeps a -> a Source #

Library dependencies proper only. (Includes dependencies of internal libraries.)

setupDeps :: Monoid a => ComponentDeps a -> a Source #

Setup dependencies.

select :: Monoid a => (Component -> Bool) -> ComponentDeps a -> a Source #

Select dependencies satisfying a given predicate.

components :: ComponentDeps a -> Set Component Source #

List components