staversion-0.2.3.0: What version is the package X in stackage lts-Y.ZZ?

MaintainerToshio Ito <debug.ito@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Staversion.Internal.Aggregate

Contents

Description

This is an internal module. End-users should not use it.

Synopsis

Top-level function

aggregateResults :: Aggregator -> [Result] -> ([AggregatedResult], [LogEntry]) Source #

Aggregate Results with the given Aggregator. It first groups Results based on its resultFor field, and then each group is aggregated into an AggregatedResult.

If it fails, it returns an empty list of AggregatedResult. It also returns a list of LogEntrys to report warnings and errors.

Aggregators

data VersionRange #

Instances
Eq VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

Data VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VersionRange -> c VersionRange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VersionRange #

toConstr :: VersionRange -> Constr #

dataTypeOf :: VersionRange -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VersionRange) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VersionRange) #

gmapT :: (forall b. Data b => b -> b) -> VersionRange -> VersionRange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VersionRange -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VersionRange -> r #

gmapQ :: (forall d. Data d => d -> u) -> VersionRange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionRange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange #

Read VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

Show VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

Generic VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

Associated Types

type Rep VersionRange :: * -> * #

Text VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

Parsec VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

Pretty VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

Methods

pretty :: VersionRange -> Doc #

Binary VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

NFData VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

Methods

rnf :: VersionRange -> () #

type Rep VersionRange 
Instance details

Defined in Distribution.Types.VersionRange

type Rep VersionRange = D1 (MetaData "VersionRange" "Distribution.Types.VersionRange" "Cabal-2.2.0.1" False) (((C1 (MetaCons "AnyVersion" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ThisVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version))) :+: (C1 (MetaCons "LaterVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)) :+: (C1 (MetaCons "OrLaterVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)) :+: C1 (MetaCons "EarlierVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version))))) :+: ((C1 (MetaCons "OrEarlierVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)) :+: (C1 (MetaCons "WildcardVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)) :+: C1 (MetaCons "MajorBoundVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)))) :+: (C1 (MetaCons "UnionVersionRanges" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VersionRange) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VersionRange)) :+: (C1 (MetaCons "IntersectVersionRanges" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VersionRange) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VersionRange)) :+: C1 (MetaCons "VersionRangeParens" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VersionRange))))))

aggOr :: Aggregator Source #

Aggregator of ORed versions.

aggPvpMajor :: Aggregator Source #

Aggregate versions to the range that the versions cover in a PVP sense. This aggregator sets the upper bound to a major version, which means it assumes major-version bump is not backward-compatible.

aggPvpMinor :: Aggregator Source #

Aggregate versions to the range that versions cover in a PVP sense. This aggregator sets the upper bound to a minor version, which means it assumes minor-version bump is not backward-compatible.

Utility

groupAllPreservingOrderBy Source #

Arguments

:: (a -> a -> Bool)

The comparator that determines if the two elements are in the same group. This comparator must be transitive, like '(==)'.

-> [a] 
-> [NonEmpty a] 

Low-level functions

aggregatePackageVersions Source #

Arguments

:: Aggregator 
-> NonEmpty (String, [(PackageName, Maybe Version)])

(label, version map). label is used for error logs.

-> (Maybe [(PackageName, Maybe VersionRange)], [LogEntry]) 

Aggregate one or more maps between PackageName and Version.

The input Maybe Versions should all be Just. Nothing version is warned and ignored. If the input versions are all Nothing, the result version range is Nothing.

The PackageName lists in the input must be consistent (i.e. they all must be the same list.) If not, it returns Nothing map and an error is logged.