Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Versions for packages.
Synopsis
- data VersionRange
- newtype IntersectingVersionRange = IntersectingVersionRange {}
- data VersionCheck
- versionRangeText :: VersionRange -> Text
- withinRange :: Version -> VersionRange -> Bool
- intersectVersionRanges :: VersionRange -> VersionRange -> VersionRange
- toMajorVersion :: Version -> Version
- latestApplicableVersion :: VersionRange -> Set Version -> Maybe Version
- checkVersion :: VersionCheck -> Version -> Version -> Bool
- nextMajorVersion :: Version -> Version
- minorVersion :: Version -> Version
- stackVersion :: Version
- showStackVersion :: String
- stackMajorVersion :: Version
- stackMinorVersion :: Version
Documentation
data VersionRange #
Instances
Parsec VersionRange |
Small history:
Set operations are introduced in 3.0
Operators are introduced in 1.8. Issues only a warning.
Wild-version ranges are introduced in 1.6. Issues only a warning.
|
Defined in Distribution.Types.VersionRange.Internal parsec :: CabalParsing m => m VersionRange # | |
Pretty VersionRange |
|
Defined in Distribution.Types.VersionRange.Internal pretty :: VersionRange -> Doc # prettyVersioned :: CabalSpecVersion -> VersionRange -> Doc # | |
Structured VersionRange | |
Defined in Distribution.Types.VersionRange.Internal structure :: Proxy VersionRange -> Structure # structureHash' :: Tagged VersionRange MD5 | |
Data VersionRange | |
Defined in Distribution.Types.VersionRange.Internal 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 | |
Defined in Distribution.Types.VersionRange.Internal type Rep VersionRange :: Type -> Type # from :: VersionRange -> Rep VersionRange x # to :: Rep VersionRange x -> VersionRange # | |
Read VersionRange | |
Defined in Distribution.Types.VersionRange.Internal readsPrec :: Int -> ReadS VersionRange # readList :: ReadS [VersionRange] # | |
Show VersionRange | |
Defined in Distribution.Types.VersionRange.Internal showsPrec :: Int -> VersionRange -> ShowS # show :: VersionRange -> String # showList :: [VersionRange] -> ShowS # | |
Binary VersionRange | |
Defined in Distribution.Types.VersionRange.Internal | |
NFData VersionRange | |
Defined in Distribution.Types.VersionRange.Internal rnf :: VersionRange -> () # | |
Eq VersionRange | |
Defined in Distribution.Types.VersionRange.Internal (==) :: VersionRange -> VersionRange -> Bool # (/=) :: VersionRange -> VersionRange -> Bool # | |
IsCabalString VersionRange | |
Defined in Pantry.Types cabalStringName :: proxy VersionRange -> String | |
type Rep VersionRange | |
Defined in Distribution.Types.VersionRange.Internal type Rep VersionRange = D1 ('MetaData "VersionRange" "Distribution.Types.VersionRange.Internal" "Cabal-syntax-3.8.1.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))))) |
newtype IntersectingVersionRange Source #
Instances
data VersionCheck Source #
Instances
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.
checkVersion :: VersionCheck -> Version -> Version -> Bool Source #
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)