| Maintainer | Toshio Ito <debug.ito@gmail.com> |
|---|---|
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Staversion.Internal.Aggregate
Description
This is an internal module. End-users should not use it.
Synopsis
- aggregateResults :: Aggregator -> [Result] -> ([AggregatedResult], [LogEntry])
- type Aggregator = NonEmpty Version -> VersionRange
- data VersionRange
- showVersionRange :: VersionRange -> String
- aggOr :: Aggregator
- aggPvpMajor :: Aggregator
- aggPvpMinor :: Aggregator
- groupAllPreservingOrderBy :: (a -> a -> Bool) -> [a] -> [NonEmpty a]
- aggregatePackageVersions :: Aggregator -> NonEmpty (String, [(PackageName, Maybe Version)]) -> (Maybe [(PackageName, Maybe VersionRange)], [LogEntry])
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
type Aggregator = NonEmpty Version -> VersionRange Source #
Aggregate some Versions into a VersionRange.
data VersionRange #
Instances
| Parsec VersionRange |
Small history:
Set operations are introduced in 3.0
Operators are introduced in 1.8. Issues only a warning.
Wild-version ranges are introduced in 1.6. Issues only a warning.
|
Defined in Distribution.Types.VersionRange.Internal Methods parsec :: CabalParsing m => m VersionRange # | |
| Pretty VersionRange |
|
Defined in Distribution.Types.VersionRange.Internal | |
| Structured VersionRange | |
Defined in Distribution.Types.VersionRange.Internal | |
| Data VersionRange | |
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 | |
Defined in Distribution.Types.VersionRange.Internal Associated Types type Rep VersionRange :: Type -> Type # | |
| Read VersionRange | |
Defined in Distribution.Types.VersionRange.Internal Methods readsPrec :: Int -> ReadS VersionRange # readList :: ReadS [VersionRange] # | |
| Show VersionRange | |
Defined in Distribution.Types.VersionRange.Internal Methods showsPrec :: Int -> VersionRange -> ShowS # show :: VersionRange -> String # showList :: [VersionRange] -> ShowS # | |
| Binary VersionRange | |
Defined in Distribution.Types.VersionRange.Internal | |
| NFData VersionRange | |
Defined in Distribution.Types.VersionRange.Internal Methods rnf :: VersionRange -> () # | |
| Eq VersionRange | |
Defined in Distribution.Types.VersionRange.Internal | |
| Ord VersionRange | |
Defined in Distribution.Types.VersionRange.Internal Methods compare :: VersionRange -> VersionRange -> Ordering # (<) :: VersionRange -> VersionRange -> Bool # (<=) :: VersionRange -> VersionRange -> Bool # (>) :: VersionRange -> VersionRange -> Bool # (>=) :: VersionRange -> VersionRange -> Bool # max :: VersionRange -> VersionRange -> VersionRange # min :: VersionRange -> VersionRange -> VersionRange # | |
| type Rep VersionRange | |
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))))) | |
showVersionRange :: VersionRange -> String Source #
Let Cabal convert VersionRange to String
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
Low-level functions
aggregatePackageVersions Source #
Arguments
| :: Aggregator | |
| -> NonEmpty (String, [(PackageName, Maybe Version)]) | ( |
| -> (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.