| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Stack.Types.Version
Description
Versions for packages.
Synopsis
- data Version
- data VersionRange
- newtype IntersectingVersionRange = IntersectingVersionRange {}
- data VersionCheck
- versionParser :: Parser Version
- parseVersion :: MonadThrow m => Text -> m Version
- parseVersionFromString :: MonadThrow m => String -> m Version
- versionString :: Version -> String
- versionText :: Version -> Text
- toCabalVersion :: Version -> Version
- fromCabalVersion :: Version -> Version
- mkVersion :: String -> Q Exp
- 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
- data UpgradeTo
- minorVersion :: Version -> Version
- stackVersion :: Version
- stackMinorVersion :: Version
Documentation
A package version.
Instances
| Eq Version Source # | |
| Data Version Source # | |
Defined in Stack.Types.Version Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version # toConstr :: Version -> Constr # dataTypeOf :: Version -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) # gmapT :: (forall b. Data b => b -> b) -> Version -> Version # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # | |
| Ord Version Source # | |
| Show Version Source # | |
| Generic Version Source # | |
| Lift Version Source # | |
| NFData Version Source # | |
Defined in Stack.Types.Version | |
| Hashable Version Source # | |
Defined in Stack.Types.Version | |
| ToJSON Version Source # | |
Defined in Stack.Types.Version | |
| FromJSON Version Source # | |
| FromJSONKey Version Source # | |
Defined in Stack.Types.Version Methods | |
| Display Version Source # | |
Defined in Stack.Types.Version Methods display :: Version -> Utf8Builder # | |
| Store Version Source # | |
| Display Version Source # | |
| type Rep Version Source # | |
Defined in Stack.Types.Version | |
| type Ann Version Source # | |
Defined in Stack.PrettyPrint | |
data VersionRange #
Instances
newtype IntersectingVersionRange Source #
Constructors
| IntersectingVersionRange | |
Fields | |
Instances
| Show IntersectingVersionRange Source # | |
Defined in Stack.Types.Version Methods showsPrec :: Int -> IntersectingVersionRange -> ShowS # show :: IntersectingVersionRange -> String # showList :: [IntersectingVersionRange] -> ShowS # | |
| Semigroup IntersectingVersionRange Source # | |
Defined in Stack.Types.Version | |
| Monoid IntersectingVersionRange Source # | |
Defined in Stack.Types.Version | |
data VersionCheck Source #
Constructors
| MatchMinor | |
| MatchExact | |
| NewerMinor |
Instances
| Eq VersionCheck Source # | |
Defined in Stack.Types.Version | |
| Ord VersionCheck Source # | |
Defined in Stack.Types.Version Methods compare :: VersionCheck -> VersionCheck -> Ordering # (<) :: VersionCheck -> VersionCheck -> Bool # (<=) :: VersionCheck -> VersionCheck -> Bool # (>) :: VersionCheck -> VersionCheck -> Bool # (>=) :: VersionCheck -> VersionCheck -> Bool # max :: VersionCheck -> VersionCheck -> VersionCheck # min :: VersionCheck -> VersionCheck -> VersionCheck # | |
| Show VersionCheck Source # | |
Defined in Stack.Types.Version Methods showsPrec :: Int -> VersionCheck -> ShowS # show :: VersionCheck -> String # showList :: [VersionCheck] -> ShowS # | |
| ToJSON VersionCheck Source # | |
Defined in Stack.Types.Version Methods toJSON :: VersionCheck -> Value # toEncoding :: VersionCheck -> Encoding # toJSONList :: [VersionCheck] -> Value # toEncodingList :: [VersionCheck] -> Encoding # | |
| FromJSON VersionCheck Source # | |
Defined in Stack.Types.Version | |
versionParser :: Parser Version Source #
Attoparsec parser for a package version.
parseVersion :: MonadThrow m => Text -> m Version Source #
Convenient way to parse a package version from a Text.
parseVersionFromString :: MonadThrow m => String -> m Version Source #
Migration function.
versionString :: Version -> String Source #
Get a string representation of a package version.
versionText :: Version -> Text Source #
Get a string representation of a package version.
toCabalVersion :: Version -> Version Source #
Convert to a Cabal version.
fromCabalVersion :: Version -> Version Source #
Convert from a Cabal version.
versionRangeText :: VersionRange -> Text Source #
Display a version range
withinRange :: Version -> VersionRange -> Bool Source #
Check if a version is within 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.
checkVersion :: VersionCheck -> Version -> Version -> Bool Source #
nextMajorVersion :: Version -> Version Source #
Get the next major version number for the given version
A Package upgrade; Latest or a specific version.
minorVersion :: Version -> Version Source #
Get minor version (excludes any patchlevel)
stackVersion :: Version Source #
Current Stack version
stackMinorVersion :: Version Source #
Current Stack minor version (excludes patchlevel)