Skip to content

Commit

Permalink
Add doctest docs for version range predicates
Browse files Browse the repository at this point in the history
- Used named chunk for predicate examples
- Add predicate subsections for types of bounds
  • Loading branch information
philderbeast committed Nov 25, 2024
1 parent 5d15804 commit 14e24a2
Showing 1 changed file with 60 additions and 18 deletions.
78 changes: 60 additions & 18 deletions Cabal-syntax/src/Distribution/Types/VersionRange.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,23 @@
{-# LANGUAGE ViewPatterns #-}

module Distribution.Types.VersionRange
( -- * Version ranges
( -- * Version Range
VersionRange

-- ** Predicates
-- $predicate-examples

-- *** Lower Bound
, hasLowerBound
, hasGTLowerBound
-- *** Upper Bound
, hasUpperBound
, hasLEQUpperBound
, hasTrailingZeroUpperBound
-- *** Any Version
, isAnyVersion
, isAnyVersionLight

-- ** Constructing
, anyVersion
, noVersion
Expand All @@ -20,35 +34,30 @@ module Distribution.Types.VersionRange
, withinVersion
, majorBoundVersion

-- ** Inspection
-- ** Modification
, normaliseVersionRange
, stripParensVersionRange

--
-- See "Distribution.Version" for more utilities.
-- ** Inspection
, withinRange
, foldVersionRange
, normaliseVersionRange
, stripParensVersionRange
, hasUpperBound
, hasLowerBound
, hasLEQUpperBound
, hasTrailingZeroUpperBound
, hasGTLowerBound

-- ** Cata & ana
-- ** Parser
, versionRangeParser

-- * Version F-Algebra
, VersionRangeF (..)
, projectVersionRange
, embedVersionRange
, cataVersionRange
, anaVersionRange
, hyloVersionRange
, projectVersionRange
, embedVersionRange

-- ** Utilities
, isAnyVersion
, isAnyVersionLight
-- * Version Utilities
-- See "Distribution.Version" for more utilities.
, wildcardUpperBound
, majorUpperBound
, isWildcardRange
, versionRangeParser
) where

import Distribution.Compat.Prelude
Expand Down Expand Up @@ -179,6 +188,9 @@ isWildcardRange ver1 ver2 = check (versionNumbers ver1) (versionNumbers ver2)
-- | Does the version range have an upper bound?
--
-- @since 1.24.0.0
--
-- >>> forM ["< 1", ">= 0 && < 1", ">= 0 || < 1", "^>= 4.20.0.0"] (fmap hasUpperBound . simpleParsec)
-- Just [True,True,False,True]
hasUpperBound :: VersionRange -> Bool
hasUpperBound =
foldVersionRange
Expand All @@ -195,6 +207,9 @@ hasUpperBound =
-- the implicit >=0 lower bound.
--
-- @since 1.24.0.0
--
-- >>> forM ["< 1", ">= 0 && < 1", ">= 0 || < 1", "^>= 4.20.0.0"] (fmap hasLowerBound . simpleParsec)
-- Just [False,True,False,True]
hasLowerBound :: VersionRange -> Bool
hasLowerBound =
foldVersionRange
Expand All @@ -206,14 +221,23 @@ hasLowerBound =
(||)

-- | Is the upper bound version range LEQ (less or equal, <=)?
--
-- >>> forM ["< 1", "<= 1", ">= 0 && < 1", ">= 0 || < 1", ">= 0 && <= 1", ">= 0 || <= 1", "^>= 4.20.0.0"] (fmap hasLEQUpperBound . simpleParsec)
-- Just [False,True,False,False,True,True,False]
hasLEQUpperBound :: VersionRange -> Bool
hasLEQUpperBound = queryVersionRange (\case HasLEQUpperBound -> True; _ -> False) hasLEQUpperBound

-- | Is the lower bound version range GT (greater than, >)?
--
-- >>> forM ["< 1", ">= 0 && < 1", ">= 0 || < 1", "> 0 && < 1", "> 0 || < 1", "^>= 4.20.0.0"] (fmap hasGTLowerBound . simpleParsec)
-- Just [False,False,False,True,True,False]
hasGTLowerBound :: VersionRange -> Bool
hasGTLowerBound = queryVersionRange (\case HasGTLowerBound -> True; _ -> False) hasGTLowerBound

-- | Does the upper bound version range have a trailing zero?
--
-- >>> forM ["< 1", "< 1.1", "< 1.0", "< 1.1.0", "^>= 4.20.0.0"] (fmap hasTrailingZeroUpperBound . simpleParsec)
-- Just [False,False,True,True,False]
hasTrailingZeroUpperBound :: VersionRange -> Bool
hasTrailingZeroUpperBound = queryVersionRange (\case HasTrailingZeroUpperBound -> True; _ -> False) hasTrailingZeroUpperBound

Expand All @@ -223,3 +247,21 @@ queryVersionRange pf p (projectVersionRange -> v) = let f = queryVersionRange pf
IntersectVersionRangesF x y -> f x || f y
UnionVersionRangesF x y -> f x || f y
_ -> False

-- $setup
-- >>> import Distribution.Parsec
-- >>> import Data.Traversable

-- $predicate-examples
--
-- The parsed 'VersionRange' of each version constraint used in the examples for
-- 'hasUpperBound' and 'hasLowerBound' are:
--
-- >>> simpleParsec "< 1" :: Maybe VersionRange
-- Just (EarlierVersion (mkVersion [1]))
-- >>> simpleParsec ">= 0 && < 1" :: Maybe VersionRange
-- Just (IntersectVersionRanges (OrLaterVersion (mkVersion [0])) (EarlierVersion (mkVersion [1])))
-- >>> simpleParsec ">= 0 || < 1" :: Maybe VersionRange
-- Just (UnionVersionRanges (OrLaterVersion (mkVersion [0])) (EarlierVersion (mkVersion [1])))
-- >>> simpleParsec "^>= 4.20.0.0" :: Maybe VersionRange
-- Just (MajorBoundVersion (mkVersion [4,20,0,0]))

0 comments on commit 14e24a2

Please sign in to comment.