Cabal-syntax-3.10.1.0: A library for working with .cabal files
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Types.VersionInterval.Legacy

Description

This module implements a view of a VersionRange as a finite list of separated version intervals and provides the Boolean algebra operations union, intersection, and complement.

It interprets the caret operator ^>=x.y as simply ==x.y.*. Until Cabal < 3.6, this module was called Distribution.Types.VersionInterval. The current module Distribution.Types.VersionInterval (refurbished since Cabal >= 3.6) makes some effort to preserve the caret operator, but so far does not expose the Boolean algebra structure.

Synopsis

Version intervals

data VersionIntervals Source #

A complementary representation of a VersionRange, using an increasing sequence of separated (i.e., non-overlapping, non-touching) non-empty intervals. The represented range is the union of these intervals, meaning that the empty sequence denotes the empty range.

As ranges form a Boolean algebra, we can compute union, intersection, and complement. These operations are all linear in the size of the input, thanks to the ordered representation.

The interval-sequence representation gives a canonical representation for the semantics of VersionRanges. This makes it easier to check things like whether a version range is empty, covers all versions, or requires a certain minimum or maximum version. It also makes it easy to check equality (just ==) or containment. It also makes it easier to identify 'simple' version predicates for translation into foreign packaging systems that do not support complex version range expressions.

toVersionIntervals :: VersionRange -> VersionIntervals Source #

Convert a VersionRange to a sequence of version intervals.

fromVersionIntervals :: VersionIntervals -> VersionRange Source #

Convert a VersionIntervals value back into a VersionRange expression representing the version intervals.

withinIntervals :: Version -> VersionIntervals -> Bool Source #

Test if a version falls within the version intervals.

It exists mostly for completeness and testing. It satisfies the following properties:

withinIntervals v (toVersionIntervals vr) = withinRange v vr
withinIntervals v ivs = withinRange v (fromVersionIntervals ivs)

versionIntervals :: VersionIntervals -> [VersionInterval] Source #

Inspect the list of version intervals.

mkVersionIntervals :: [VersionInterval] -> VersionIntervals Source #

Directly construct a VersionIntervals from a list of intervals.

unionVersionIntervals :: VersionIntervals -> VersionIntervals -> VersionIntervals Source #

Union two interval sequences, fusing intervals where necessary. Computed \( O(n+m) \) time, resulting in sequence of length \( ≤ n+m \).

intersectVersionIntervals :: VersionIntervals -> VersionIntervals -> VersionIntervals Source #

The intersection \( is \cap is' \) of two interval sequences \( is \) and \( is' \) of lengths \( n \) and \( m \), resp., satisfies the specification \( is ∩ is' = \{ i ∩ i' \mid i ∈ is, i' ∈ is' \} \). Thanks to the ordered representation of intervals it can be computed in \( O(n+m) \) (rather than the naive \( O(nm) \).

The length of \( is \cap is' \) is \( ≤ \min(n,m) \).

invertVersionIntervals :: VersionIntervals -> VersionIntervals Source #

Compute the complement. \( O(n) \).

relaxLastInterval :: VersionIntervals -> VersionIntervals Source #

Remove the last upper bound, enlarging the range. But empty ranges stay empty. \( O(n) \).

relaxHeadInterval :: VersionIntervals -> VersionIntervals Source #

Remove the first lower bound (i.e, make it \( [0 \). Empty ranges stay empty. \( O(1) \).

Version intervals view

asVersionIntervals :: VersionRange -> [VersionInterval] Source #

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 [VersionInterval], thus its 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                   = False
isSpecificVersion vr
   | [(LowerBound v  InclusiveBound
      ,UpperBound v' InclusiveBound)] <- asVersionIntervals vr
   , v == v'   = Just v
   | otherwise = Nothing

type VersionInterval = (LowerBound, UpperBound) Source #

Version intervals with exclusive or inclusive bounds, in all combinations:

  1. \( (lb,ub) \) meaning \( lb < \_ < ub \).
  2. \( (lb,ub] \) meaning \( lb < \_ ≤ ub \).
  3. \( [lb,ub) \) meaning \( lb ≤ \_ < ub \).
  4. \( [lb,ub] \) meaning \( lb ≤ \_ < ub \).

The upper bound can also be missing, meaning "\( ..,∞) \)".

data LowerBound Source #

Constructors

LowerBound Version !Bound

Either exclusive (v,.. or inclusive [v,...

Instances

Instances details
Show LowerBound Source # 
Instance details

Defined in Distribution.Types.VersionInterval.Legacy

Eq LowerBound Source # 
Instance details

Defined in Distribution.Types.VersionInterval.Legacy

Ord LowerBound Source #

lb1 <= lb2 holds iff interval lb1.. is contained in interval lb2...

Instance details

Defined in Distribution.Types.VersionInterval.Legacy

data UpperBound Source #

Constructors

NoUpperBound
..,∞)
UpperBound Version !Bound

Either exclusive ..,v) or inclusive ..,v].

Instances

Instances details
Show UpperBound Source # 
Instance details

Defined in Distribution.Types.VersionInterval.Legacy

Eq UpperBound Source # 
Instance details

Defined in Distribution.Types.VersionInterval.Legacy

Ord UpperBound Source #

ub1 <= ub2 holds iff interval 0..ub1 is contained in interval 0..ub2.

Instance details

Defined in Distribution.Types.VersionInterval.Legacy

data Bound Source #

Constructors

ExclusiveBound

(v,.. if used as lower bound, ..,v) if used as upper bound.

InclusiveBound

[v,.. if used as lower bound, ..,v] if used as upper bound.

Instances

Instances details
Show Bound Source # 
Instance details

Defined in Distribution.Types.VersionInterval.Legacy

Methods

showsPrec :: Int -> Bound -> ShowS #

show :: Bound -> String #

showList :: [Bound] -> ShowS #

Eq Bound Source # 
Instance details

Defined in Distribution.Types.VersionInterval.Legacy

Methods

(==) :: Bound -> Bound -> Bool #

(/=) :: Bound -> Bound -> Bool #