| Maintainer | Toshio Ito <debug.ito@gmail.com> |
|---|---|
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Staversion.Internal.Version
Contents
Description
This is an internal module. End-users should not use it.
Synopsis
- data Version
- data VersionRange
- data LowerBound = LowerBound Version !Bound
- data UpperBound
- data Bound
- type VersionInterval = (LowerBound, UpperBound)
- thisVersion :: Version -> VersionRange
- unionVersionRanges :: VersionRange -> VersionRange -> VersionRange
- simplifyVersionRange :: VersionRange -> VersionRange
- fromVersionIntervals :: VersionIntervals -> VersionRange
- asVersionIntervals :: VersionRange -> [VersionInterval]
- mkVersion :: [Int] -> Version
- mkVersionIntervals :: [VersionInterval] -> VersionIntervals
- versionNumbers :: Version -> [Int]
- docVersionRange :: VersionRange -> Doc
- type BaseVersion = Version
- showBaseVersion :: BaseVersion -> String
- parseVersionText :: Text -> Maybe Version
Re-exports
A Version represents the version of a software entity.
Instances of Eq and Ord are provided, which gives exact
equality and lexicographic ordering of the version number
components (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2, etc.).
This type is opaque and distinct from the Version type in
Data.Version since Cabal-2.0. The difference extends to the
Binary instance using a different (and more compact) encoding.
Since: Cabal-syntax-2.0.0.2
Instances
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))))) | |
data LowerBound #
Constructors
| LowerBound Version !Bound | Either exclusive |
Instances
| Show LowerBound | |
Defined in Distribution.Types.VersionInterval.Legacy Methods showsPrec :: Int -> LowerBound -> ShowS # show :: LowerBound -> String # showList :: [LowerBound] -> ShowS # | |
| Eq LowerBound | |
Defined in Distribution.Types.VersionInterval.Legacy | |
| Ord LowerBound |
|
Defined in Distribution.Types.VersionInterval.Legacy Methods compare :: LowerBound -> LowerBound -> Ordering # (<) :: LowerBound -> LowerBound -> Bool # (<=) :: LowerBound -> LowerBound -> Bool # (>) :: LowerBound -> LowerBound -> Bool # (>=) :: LowerBound -> LowerBound -> Bool # max :: LowerBound -> LowerBound -> LowerBound # min :: LowerBound -> LowerBound -> LowerBound # | |
data UpperBound #
Constructors
| NoUpperBound | ..,∞) |
| UpperBound Version !Bound | Either exclusive |
Instances
| Show UpperBound | |
Defined in Distribution.Types.VersionInterval.Legacy Methods showsPrec :: Int -> UpperBound -> ShowS # show :: UpperBound -> String # showList :: [UpperBound] -> ShowS # | |
| Eq UpperBound | |
Defined in Distribution.Types.VersionInterval.Legacy | |
| Ord UpperBound |
|
Defined in Distribution.Types.VersionInterval.Legacy Methods compare :: UpperBound -> UpperBound -> Ordering # (<) :: UpperBound -> UpperBound -> Bool # (<=) :: UpperBound -> UpperBound -> Bool # (>) :: UpperBound -> UpperBound -> Bool # (>=) :: UpperBound -> UpperBound -> Bool # max :: UpperBound -> UpperBound -> UpperBound # min :: UpperBound -> UpperBound -> UpperBound # | |
Constructors
| ExclusiveBound |
|
| InclusiveBound |
|
Instances
type VersionInterval = (LowerBound, UpperBound) #
Version intervals with exclusive or inclusive bounds, in all combinations:
- \( (lb,ub) \) meaning \( lb < \_ < ub \).
- \( (lb,ub] \) meaning \( lb < \_ ≤ ub \).
- \( [lb,ub) \) meaning \( lb ≤ \_ < ub \).
- \( [lb,ub] \) meaning \( lb ≤ \_ < ub \).
The upper bound can also be missing, meaning "\( ..,∞) \)".
thisVersion :: Version -> VersionRange #
The version range == v.
withinRange v' (thisVersion v) = v' == v
unionVersionRanges :: VersionRange -> VersionRange -> VersionRange #
The version range vr1 || vr2.
withinRange v' (unionVersionRanges vr1 vr2) = withinRange v' vr1 || withinRange v' vr2
simplifyVersionRange :: VersionRange -> VersionRange #
Simplify a VersionRange expression. For non-empty version ranges
this produces a canonical form. Empty or inconsistent version ranges
are left as-is because that provides more information.
If you need a canonical form use
fromVersionIntervals . toVersionIntervals
It satisfies the following properties:
withinRange v (simplifyVersionRange r) = withinRange v r
withinRange v r = withinRange v r' ==> simplifyVersionRange r = simplifyVersionRange r' || isNoVersion r || isNoVersion r'
fromVersionIntervals :: VersionIntervals -> VersionRange #
Convert a VersionIntervals value back into a VersionRange expression
representing the version intervals.
asVersionIntervals :: VersionRange -> [VersionInterval] #
View a VersionRange as a sequence of separated intervals.
This provides a canonical view of the semantics of a VersionRange as
opposed to the syntax of the expression used to define it. For the syntactic
view use foldVersionRange.
Canonical means that two semantically equal ranges translate to the same
[, thus its VersionInterval]Eq instance can decide semantical equality
of ranges.
In the returned sequence, each interval is non-empty.
The sequence is in increasing order and the intervals are separated, i.e., they
neither overlap nor touch. Therefore only the first and last interval can be
unbounded. The sequence can be empty if the range is empty
(e.g. a range expression like > 2 && < 1).
Other checks are trivial to implement using this view. For example:
isNoVersion vr | [] <- asVersionIntervals vr = True
| otherwise = FalseisSpecificVersion vr
| [(LowerBound v InclusiveBound
,UpperBound v' InclusiveBound)] <- asVersionIntervals vr
, v == v' = Just v
| otherwise = NothingCompatibility
versionNumbers :: Version -> [Int] Source #
docVersionRange :: VersionRange -> Doc Source #
Util
type BaseVersion = Version Source #
A Version type by Data.Version.
showBaseVersion :: BaseVersion -> String Source #