stack-3.1.1: The Haskell Tool Stack
Safe HaskellSafe-Inferred
LanguageGHC2021

Stack.Types.Version

Description

Versions for packages.

Synopsis

Documentation

data VersionRange #

Instances

Instances details
Parsec VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

parsec :: CabalParsing m => m VersionRange

Pretty VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

pretty :: VersionRange -> Doc

prettyVersioned :: CabalSpecVersion -> VersionRange -> Doc

Structured VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

structure :: Proxy VersionRange -> Structure

structureHash' :: Tagged VersionRange MD5

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

Methods

showsPrec :: Int -> VersionRange -> ShowS #

show :: VersionRange -> String #

showList :: [VersionRange] -> ShowS #

Binary VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

put :: VersionRange -> Put

get :: Get VersionRange

putList :: [VersionRange] -> Put

NFData VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

rnf :: VersionRange -> () #

Eq VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Ord 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-syntax-3.10.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

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)