staversion-0.2.4.3: What version is the package X in stackage lts-Y.ZZ?
MaintainerToshio Ito <debug.ito@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Staversion.Internal.Aggregate

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

Instances details
Parsec VersionRange
>>> simpleParsec "^>= 3.4" :: Maybe VersionRange
Just (MajorBoundVersion (mkVersion [3,4]))

Small history:

-any and -none removed in 3.4 Use >=0 and <0 instead.

>>> map (`simpleParsec'` "-none") [CabalSpecV3_0, CabalSpecV3_4] :: [Maybe VersionRange]
[Just (EarlierVersion (mkVersion [0])),Nothing]

Set operations are introduced in 3.0

>>> map (`simpleParsec'` "^>= { 1.2 , 1.3 }") [CabalSpecV2_4, CabalSpecV3_0] :: [Maybe VersionRange]
[Nothing,Just (UnionVersionRanges (MajorBoundVersion (mkVersion [1,2])) (MajorBoundVersion (mkVersion [1,3])))]

^>= is introduced in 2.0

>>> map (`simpleParsec'` "^>=1.2") [CabalSpecV1_24, CabalSpecV2_0] :: [Maybe VersionRange]
[Nothing,Just (MajorBoundVersion (mkVersion [1,2]))]

-none is introduced in 1.22

>>> map (`simpleParsec'` "-none") [CabalSpecV1_20, CabalSpecV1_22] :: [Maybe VersionRange]
[Nothing,Just (EarlierVersion (mkVersion [0]))]

Operators are introduced in 1.8. Issues only a warning.

>>> map (`simpleParsecW'` "== 1 || ==2") [CabalSpecV1_6, CabalSpecV1_8] :: [Maybe VersionRange]
[Nothing,Just (UnionVersionRanges (ThisVersion (mkVersion [1])) (ThisVersion (mkVersion [2])))]

Wild-version ranges are introduced in 1.6. Issues only a warning.

>>> map (`simpleParsecW'` "== 1.2.*") [CabalSpecV1_4, CabalSpecV1_6] :: [Maybe VersionRange]
[Nothing,Just (IntersectVersionRanges (OrLaterVersion (mkVersion [1,2])) (EarlierVersion (mkVersion [1,3])))]
Instance details

Defined in Distribution.Types.VersionRange.Internal

Pretty VersionRange
>>> fmap pretty (simpleParsec' CabalSpecV1_6 "== 3.2.*" :: Maybe VersionRange)
Just >=3.2 && <3.3
>>> fmap (prettyVersioned CabalSpecV1_6) (simpleParsec' CabalSpecV1_6 "== 3.2.*" :: Maybe VersionRange)
Just ==3.2.*
>>> fmap pretty (simpleParsec' CabalSpecV1_6 "-any" :: Maybe VersionRange)
Just >=0
>>> fmap (prettyVersioned CabalSpecV1_6) (simpleParsec' CabalSpecV1_6 "-any" :: Maybe VersionRange)
Just >=0
Instance details

Defined in Distribution.Types.VersionRange.Internal

Structured VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Data VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

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 :: forall r r'. (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 #

Generic VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Associated Types

type Rep VersionRange :: Type -> Type #

Read VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Show VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Binary VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

NFData VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

rnf :: VersionRange -> () #

Eq VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Ord VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

type Rep VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

type Rep VersionRange = D1 ('MetaData "VersionRange" "Distribution.Types.VersionRange.Internal" "Cabal-syntax-3.10.1.0" 'False) (((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 "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)))))

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.