stack-2.9.3: The Haskell Tool Stack
Safe HaskellSafe-Inferred
LanguageHaskell2010

Stack.Types.Version

Description

Versions for packages.

Synopsis

Documentation

data VersionRange #

Instances

Instances details
Parsec VersionRange
>>> simpleParsec "^>= 3.4" :: Maybe VersionRange
Just (MajorBoundVersion (mkVersion [3,4]))

Small history:

-any and -none removed in 3.4 Use >=0 and <0 instead.

>>> map (`simpleParsec'` "-none") [CabalSpecV3_0, CabalSpecV3_4] :: [Maybe VersionRange]
[Just (EarlierVersion (mkVersion [0])),Nothing]

Set operations are introduced in 3.0

>>> map (`simpleParsec'` "^>= { 1.2 , 1.3 }") [CabalSpecV2_4, CabalSpecV3_0] :: [Maybe VersionRange]
[Nothing,Just (UnionVersionRanges (MajorBoundVersion (mkVersion [1,2])) (MajorBoundVersion (mkVersion [1,3])))]

^>= is introduced in 2.0

>>> map (`simpleParsec'` "^>=1.2") [CabalSpecV1_24, CabalSpecV2_0] :: [Maybe VersionRange]
[Nothing,Just (MajorBoundVersion (mkVersion [1,2]))]

-none is introduced in 1.22

>>> map (`simpleParsec'` "-none") [CabalSpecV1_20, CabalSpecV1_22] :: [Maybe VersionRange]
[Nothing,Just (EarlierVersion (mkVersion [0]))]

Operators are introduced in 1.8. Issues only a warning.

>>> map (`simpleParsecW'` "== 1 || ==2") [CabalSpecV1_6, CabalSpecV1_8] :: [Maybe VersionRange]
[Nothing,Just (UnionVersionRanges (ThisVersion (mkVersion [1])) (ThisVersion (mkVersion [2])))]

Wild-version ranges are introduced in 1.6. Issues only a warning.

>>> map (`simpleParsecW'` "== 1.2.*") [CabalSpecV1_4, CabalSpecV1_6] :: [Maybe VersionRange]
[Nothing,Just (IntersectVersionRanges (OrLaterVersion (mkVersion [1,2])) (EarlierVersion (mkVersion [1,3])))]
Instance details

Defined in Distribution.Types.VersionRange.Internal

Pretty VersionRange
>>> fmap pretty (simpleParsec' CabalSpecV1_6 "== 3.2.*" :: Maybe VersionRange)
Just >=3.2 && <3.3
>>> fmap (prettyVersioned CabalSpecV1_6) (simpleParsec' CabalSpecV1_6 "== 3.2.*" :: Maybe VersionRange)
Just ==3.2.*
>>> fmap pretty (simpleParsec' CabalSpecV1_6 "-any" :: Maybe VersionRange)
Just >=0
>>> fmap (prettyVersioned CabalSpecV1_6) (simpleParsec' CabalSpecV1_6 "-any" :: Maybe VersionRange)
Just >=0
Instance details

Defined in Distribution.Types.VersionRange.Internal

Structured VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Data VersionRange 
Instance details

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 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Associated Types

type Rep VersionRange :: Type -> Type #

Read VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Show VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Binary VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

NFData VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

rnf :: VersionRange -> () #

Eq VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

IsCabalString VersionRange 
Instance details

Defined in Pantry.Types

type Rep VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

type Rep VersionRange = D1 ('MetaData "VersionRange" "Distribution.Types.VersionRange.Internal" "Cabal-3.6.3.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)))))

versionRangeText :: VersionRange -> Text Source #

Display a version range

withinRange :: Version -> VersionRange -> Bool #

Does this version fall within the given range?

This is the evaluation function for the VersionRange type.

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

A modified intersection which also simplifies, for better display.

toMajorVersion :: Version -> Version Source #

Returns the first two components, defaulting to 0 if not present

latestApplicableVersion :: VersionRange -> Set Version -> Maybe Version Source #

Given a version range and a set of versions, find the latest version from the set that is within the range.

nextMajorVersion :: Version -> Version Source #

Get the next major version number for the given version

minorVersion :: Version -> Version Source #

Get minor version (excludes any patchlevel)

stackVersion :: Version Source #

Current Stack version

showStackVersion :: String Source #

Current Stack version in the same format as yielded by showVersion.

stackMajorVersion :: Version Source #

Current Stack major version. Returns the first two components, defaulting to 0 if not present

stackMinorVersion :: Version Source #

Current Stack minor version (excludes patchlevel)