Cabal-2.2.0.1: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.VersionRange

Contents

Synopsis

Version ranges

data VersionRange Source #

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 Source #

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

toConstr :: VersionRange -> Constr Source #

dataTypeOf :: VersionRange -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 :: * -> * Source #

NFData VersionRange # 
Instance details

Defined in Distribution.Types.VersionRange

Methods

rnf :: VersionRange -> () Source #

Binary VersionRange # 
Instance details

Defined in Distribution.Types.VersionRange

Pretty VersionRange # 
Instance details

Defined in Distribution.Types.VersionRange

Parsec VersionRange # 
Instance details

Defined in Distribution.Types.VersionRange

Text VersionRange # 
Instance details

Defined in Distribution.Types.VersionRange

Newtype TestedWith (CompilerFlavor, VersionRange) # 
Instance details

Defined in Distribution.Parsec.Newtypes

Newtype SpecVersion (Either Version VersionRange) # 
Instance details

Defined in Distribution.Parsec.Newtypes

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))))))

Constructing

anyVersion :: VersionRange Source #

The version range -any. That is, a version range containing all versions.

withinRange v anyVersion = True

noVersion :: VersionRange Source #

The empty version range, that is a version range containing no versions.

This can be constructed using any unsatisfiable version range expression, for example > 1 && < 1.

withinRange v noVersion = False

thisVersion :: Version -> VersionRange Source #

The version range == v

withinRange v' (thisVersion v) = v' == v

notThisVersion :: Version -> VersionRange Source #

The version range || v

withinRange v' (notThisVersion v) = v' /= v

laterVersion :: Version -> VersionRange Source #

The version range > v

withinRange v' (laterVersion v) = v' > v

earlierVersion :: Version -> VersionRange Source #

The version range < v

withinRange v' (earlierVersion v) = v' < v

orLaterVersion :: Version -> VersionRange Source #

The version range >= v

withinRange v' (orLaterVersion v) = v' >= v

orEarlierVersion :: Version -> VersionRange Source #

The version range <= v

withinRange v' (orEarlierVersion v) = v' <= v

unionVersionRanges :: VersionRange -> VersionRange -> VersionRange Source #

The version range vr1 || vr2

  withinRange v' (unionVersionRanges vr1 vr2)
= withinRange v' vr1 || withinRange v' vr2

intersectVersionRanges :: VersionRange -> VersionRange -> VersionRange Source #

The version range vr1 && vr2

  withinRange v' (intersectVersionRanges vr1 vr2)
= withinRange v' vr1 && withinRange v' vr2

withinVersion :: Version -> VersionRange Source #

The version range == v.*.

For example, for version 1.2, the version range == 1.2.* is the same as >= 1.2 && < 1.3

withinRange v' (laterVersion v) = v' >= v && v' < upper v
  where
    upper (Version lower t) = Version (init lower ++ [last lower + 1]) t

majorBoundVersion :: Version -> VersionRange Source #

The version range ^>= v.

For example, for version 1.2.3.4, the version range ^>= 1.2.3.4 is the same as >= 1.2.3.4 && < 1.3.

Note that ^>= 1 is equivalent to >= 1 && < 1.1.

Since: Cabal-2.0.0.2

Inspection

withinRange :: Version -> VersionRange -> Bool Source #

Does this version fall within the given range?

This is the evaluation function for the VersionRange type.

foldVersionRange Source #

Arguments

:: a

"-any" version

-> (Version -> a)
"== v"
-> (Version -> a)
"> v"
-> (Version -> a)
"< v"
-> (a -> a -> a)

"_ || _" union

-> (a -> a -> a)

"_ && _" intersection

-> VersionRange 
-> a 

Fold over the basic syntactic structure of a VersionRange.

This provides a syntactic view of the expression defining the version range. The syntactic sugar ">= v", "<= v" and "== v.*" is presented in terms of the other basic syntax.

For a semantic view use asVersionIntervals.

normaliseVersionRange :: VersionRange -> VersionRange Source #

Normalise VersionRange.

In particular collapse (== v || > v) into >= v, and so on.

hasUpperBound :: VersionRange -> Bool Source #

Does the version range have an upper bound?

Since: Cabal-1.24.0.0

hasLowerBound :: VersionRange -> Bool Source #

Does the version range have an explicit lower bound?

Note: this function only considers the user-specified lower bounds, but not the implicit >=0 lower bound.

Since: Cabal-1.24.0.0

Cata & ana

data VersionRangeF a Source #

F-Algebra of VersionRange. See cataVersionRange.

Since: Cabal-2.2

Instances
Functor VersionRangeF # 
Instance details

Defined in Distribution.Types.VersionRange

Methods

fmap :: (a -> b) -> VersionRangeF a -> VersionRangeF b Source #

(<$) :: a -> VersionRangeF b -> VersionRangeF a Source #

Foldable VersionRangeF # 
Instance details

Defined in Distribution.Types.VersionRange

Methods

fold :: Monoid m => VersionRangeF m -> m Source #

foldMap :: Monoid m => (a -> m) -> VersionRangeF a -> m Source #

foldr :: (a -> b -> b) -> b -> VersionRangeF a -> b Source #

foldr' :: (a -> b -> b) -> b -> VersionRangeF a -> b Source #

foldl :: (b -> a -> b) -> b -> VersionRangeF a -> b Source #

foldl' :: (b -> a -> b) -> b -> VersionRangeF a -> b Source #

foldr1 :: (a -> a -> a) -> VersionRangeF a -> a Source #

foldl1 :: (a -> a -> a) -> VersionRangeF a -> a Source #

toList :: VersionRangeF a -> [a] Source #

null :: VersionRangeF a -> Bool Source #

length :: VersionRangeF a -> Int Source #

elem :: Eq a => a -> VersionRangeF a -> Bool Source #

maximum :: Ord a => VersionRangeF a -> a Source #

minimum :: Ord a => VersionRangeF a -> a Source #

sum :: Num a => VersionRangeF a -> a Source #

product :: Num a => VersionRangeF a -> a Source #

Traversable VersionRangeF # 
Instance details

Defined in Distribution.Types.VersionRange

Methods

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

sequenceA :: Applicative f => VersionRangeF (f a) -> f (VersionRangeF a) Source #

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

sequence :: Monad m => VersionRangeF (m a) -> m (VersionRangeF a) Source #

Eq a => Eq (VersionRangeF a) # 
Instance details

Defined in Distribution.Types.VersionRange

Data a => Data (VersionRangeF a) # 
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) -> VersionRangeF a -> c (VersionRangeF a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VersionRangeF a) Source #

toConstr :: VersionRangeF a -> Constr Source #

dataTypeOf :: VersionRangeF a -> DataType Source #

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

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

gmapT :: (forall b. Data b => b -> b) -> VersionRangeF a -> VersionRangeF a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> VersionRangeF a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionRangeF a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VersionRangeF a -> m (VersionRangeF a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRangeF a -> m (VersionRangeF a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VersionRangeF a -> m (VersionRangeF a) Source #

Read a => Read (VersionRangeF a) # 
Instance details

Defined in Distribution.Types.VersionRange

Show a => Show (VersionRangeF a) # 
Instance details

Defined in Distribution.Types.VersionRange

Generic (VersionRangeF a) # 
Instance details

Defined in Distribution.Types.VersionRange

Associated Types

type Rep (VersionRangeF a) :: * -> * Source #

type Rep (VersionRangeF a) # 
Instance details

Defined in Distribution.Types.VersionRange

type Rep (VersionRangeF a) = D1 (MetaData "VersionRangeF" "Distribution.Types.VersionRange" "Cabal-2.2.0.1" False) (((C1 (MetaCons "AnyVersionF" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ThisVersionF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version))) :+: (C1 (MetaCons "LaterVersionF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)) :+: (C1 (MetaCons "OrLaterVersionF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)) :+: C1 (MetaCons "EarlierVersionF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version))))) :+: ((C1 (MetaCons "OrEarlierVersionF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)) :+: (C1 (MetaCons "WildcardVersionF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)) :+: C1 (MetaCons "MajorBoundVersionF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)))) :+: (C1 (MetaCons "UnionVersionRangesF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: (C1 (MetaCons "IntersectVersionRangesF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "VersionRangeParensF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))))

cataVersionRange :: (VersionRangeF a -> a) -> VersionRange -> a Source #

Fold VersionRange.

Since: Cabal-2.2

anaVersionRange :: (a -> VersionRangeF a) -> a -> VersionRange Source #

Unfold VersionRange.

Since: Cabal-2.2

Utilities

wildcardUpperBound :: Version -> Version Source #

Since: Cabal-2.2

majorUpperBound :: Version -> Version Source #

Compute next greater major version to be used as upper bound

Example: 0.4.1 produces the version 0.5 which then can be used to construct a range >= 0.4.1 && < 0.5

Since: Cabal-2.2