Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module defines types and functions for working with versions as defined by Semantic Versioning. It also provides types and functions for working with version constraints as described by npm.
Synopsis
- data Version
- data PreRelease
- data Build
- data Constraint
- makeVersion :: Word64 -> Word64 -> Word64 -> [PreRelease] -> [Build] -> Version
- initialVersion :: Version
- parseVersion :: String -> Maybe Version
- parsePreRelease :: String -> Maybe PreRelease
- parseBuild :: String -> Maybe Build
- parseConstraint :: String -> Maybe Constraint
- unsafeParseVersion :: String -> Version
- unsafeParsePreRelease :: String -> PreRelease
- unsafeParseBuild :: String -> Build
- unsafeParseConstraint :: String -> Constraint
- renderVersion :: Version -> String
- renderPreRelease :: PreRelease -> String
- renderBuild :: Build -> String
- renderConstraint :: Constraint -> String
- isUnstable :: Version -> Bool
- isStable :: Version -> Bool
- fromBaseVersion :: Version -> Version
- toBaseVersion :: Version -> Version
- bumpMajor :: Version -> Version
- bumpMinor :: Version -> Version
- bumpPatch :: Version -> Version
- satisfiesConstraint :: Constraint -> Version -> Bool
- majorLens :: Functor f => (Word64 -> f Word64) -> Version -> f Version
- minorLens :: Functor f => (Word64 -> f Word64) -> Version -> f Version
- patchLens :: Functor f => (Word64 -> f Word64) -> Version -> f Version
- preReleasesLens :: Functor f => ([PreRelease] -> f [PreRelease]) -> Version -> f Version
- buildsLens :: Functor f => ([Build] -> f [Build]) -> Version -> f Version
Documentation
This module doesn't export anything that conflicts with the Prelude, so you can import it unqualified.
>>>
import Salve
This module provides lenses for modifying versions. If you want to modify versions, consider importing a lens library like microlens.
The Version
data type is the core of this module. Use parseVersion
to
make versions and renderVersion
to convert them into strings.
>>>
renderVersion <$> parseVersion "1.2.3"
Just "1.2.3"
The Constraint
data type allows you to specify version constraints. Use
parseConstraint
to make constraints and renderConstraint
to convert them
into strings.
>>>
renderConstraint <$> parseConstraint ">1.2.0"
Just ">1.2.0"
Use satisfiesConstraint
to see if a version satisfiesConstraint a
constraint.
>>>
satisfiesConstraint <$> parseConstraint ">1.2.0" <*> parseVersion "1.2.3"
Just True
Cheat sheet
If you're coming from Cabal, you might not be familiar with npm's version range syntax. This table shows you how npm version ranges map to Cabal's version constraints.
Salve | Cabal | Notes ----- | ----- | ----- <1.2.3 | <1.2.3 | - <=1.2.3 | <=1.2.3 | - =1.2.3 | ==1.2.3 | equals sign is optional >=1.2.3 | >=1.2.3 | - >1.2.3 | >1.2.3 | - 1.2.3 || >1.2.3 | ==1.2.3 || >1.2.3 | lower precedence than and >=1.2.3 <2.0.0 | >=1.2.3 && <2.0.0 | higher precedence than or 1.2.3 - 2.3.4 | >=1.2.3 && <=2.3.4 | inclusive ranges 1.2.x | ==1.2.* | can use X or * instead of x 1.x.x | ==1.* | - x.x.x | ==* | same as -any ~1.2.3 | ^>=1.2.3 | same as >=1.2.3 && <1.3.0 ^1.2.3 | >=1.2.3 && <2 | - ^0.2.3 | >=0.2.3 && <0.3 | - ^0.0.3 | >=0.0.3 && <0.0.4 | -
Rationale
The PVP
Haskell's Package Versioning Policy (PVP) defines three things:
- A spec for versioning your package, which includes how version numbers look and how to encode breaking changes.
- A spec for constraining the versions of your dependencies, which incldues how version ranges look.
- A prescription for how to constrain the versions of your dependencies, which includes how the ranges of your dependencies should be.
By comparison, Semantic Versioning only deals with the first thing. npm's version ranges only deal with the second thing. This module deals with the first and second things but leaves the third up to you.
Looking at the first point, why might you want to use SemVer instead of the PVP? The PVP has many problems, as described by the Problematic versioning policy blog post. In short, the PVP is too flexible and it's unique to Haskell, which causes unnecessary friction with developers from other languages.
Moving on to the second point, why should we use npm's version ranges
instead of the PVP's? This is a less clear cut. The two syntaxes are broadly
compatible. Really the only gains here are compatibility with a widely-used
syntax and convenient shorthand for common constraints (like hyphens
1.2.3 - 2.3.4
, tildes ~1.2.3
, and carets ^1.2.3
).
Other modules
There are already a few modules that provide version numbers. Why do we need another one? Let's take a look at the options.
Data.Version from the
base
package:- Exposes constructors, which allows creating versions that cannot be parsed.
- Allows any number of components, from zero to inifinity.
- Deprecated tags on versions.
- Does not support build metadata on versions.
- Does not support constraints.
Distribution.Version from the
Cabal
package:- Has the same problems as Data.Version because it re-uses that version type.
- Depends on the
array
,binary
,bytestring
,containers
,deepseq
,directory
,filepath
,pretty
,process
,time
, andunix
packages.
Data.SemVer from the
semver
package:- Depends on the
attoparsec
,deepseq
, andtext
packages. - Does not support version constraints.
- Depends on the
Data.SemVer from the
semver-range
package:- Depends on the
classy-prelude
,parsec
,text
, andunordered-containers
packages. - Module name collides with the
semver
package. - Supports constraints, but does not provide a way to render them.
- Depends on the
Data.Versions from the
versions
package:- Depends on the
deepseq
,hashable
,megaparsec
, andtext
packages. - Intentially allows weird versions.
- Does not support constraints.
- Depends on the
By comparison, this module:
- Does not expose constructors. Any version you create can be rendered and parsed without issue.
- Requires exactly three components. You won't have to wonder if version
1.2.0
is greater than1.2
. - Allows pre-release identifiers on versions. Go ahead and release version
1.0.0-alpha
for early adopters. - Allows build metadata on versions. Show when a release was made with
versions like
1.0.0+2001-02-03
. - Supports version constraints. Just like versions, rendering and parsing constraints is no problem.
- Only depends on the
base
package. You can use all the functionality without installing any other packages. - Has a unique module name. You won't have to use the
PackageImports
extension simply to deal with version numbers.
Types
A semantic version number. Versions have five parts:
majorLens
: The major version number.minorLens
: The minor version number.patchLens
: The patch version number.preReleasesLens
: A list of pre-release identifiers.buildsLens
: A list of build metadata.
Use parseVersion
to create versions.
Instances
Eq Version Source # | |
Data Version Source # | |
Defined in Salve.Internal 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 # | In general, versions compare in the way that you would expect. First the major version numbers are compared, then the minors, then the patches.
Numbers are compared numerically, not alphabetically.
If all the numbers are the same, the pre-releases are compared.
A version with a pre-release is always less than a version without one as long as the other parts are the same.
Builds are not considered when comparing versions.
|
Read Version Source # | |
Show Version Source # | |
Generic Version Source # | |
type Rep Version Source # | |
Defined in Salve.Internal type Rep Version = D1 (MetaData "Version" "Salve.Internal" "salve-1.0.10-CS6HqfWAQu5RpiFvSg5on" False) (C1 (MetaCons "Version" PrefixI True) ((S1 (MetaSel (Just "versionMajor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64) :*: S1 (MetaSel (Just "versionMinor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) :*: (S1 (MetaSel (Just "versionPatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64) :*: (S1 (MetaSel (Just "versionPreReleases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PreRelease]) :*: S1 (MetaSel (Just "versionBuilds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Build]))))) |
data PreRelease Source #
Pre-release information attached to a version. These can either be numeric or textual. They must not be empty.
- Numeric: Can be any non-negative integer. Cannot have leading zeros.
- Textual: Can be any string of ASCII digits, letters, or hyphens. Cannot be all digits, as that would be numeric.
In general, pre-releases must match the regular expression
/^[-0-9A-Za-z]+$/
.
Use parsePreRelease
to create pre-releases.
Instances
Eq PreRelease Source # | |
Defined in Salve.Internal (==) :: PreRelease -> PreRelease -> Bool # (/=) :: PreRelease -> PreRelease -> Bool # | |
Data PreRelease Source # | |
Defined in Salve.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PreRelease -> c PreRelease # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PreRelease # toConstr :: PreRelease -> Constr # dataTypeOf :: PreRelease -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PreRelease) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PreRelease) # gmapT :: (forall b. Data b => b -> b) -> PreRelease -> PreRelease # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PreRelease -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PreRelease -> r # gmapQ :: (forall d. Data d => d -> u) -> PreRelease -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PreRelease -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PreRelease -> m PreRelease # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PreRelease -> m PreRelease # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PreRelease -> m PreRelease # | |
Ord PreRelease Source # | Numeric pre-releases are always less than textual pre-releases.
Numeric pre-releases are compared numerically.
Textual pre-releases are compared alphabetically.
|
Defined in Salve.Internal compare :: PreRelease -> PreRelease -> Ordering # (<) :: PreRelease -> PreRelease -> Bool # (<=) :: PreRelease -> PreRelease -> Bool # (>) :: PreRelease -> PreRelease -> Bool # (>=) :: PreRelease -> PreRelease -> Bool # max :: PreRelease -> PreRelease -> PreRelease # min :: PreRelease -> PreRelease -> PreRelease # | |
Read PreRelease Source # | |
Defined in Salve.Internal readsPrec :: Int -> ReadS PreRelease # readList :: ReadS [PreRelease] # readPrec :: ReadPrec PreRelease # readListPrec :: ReadPrec [PreRelease] # | |
Show PreRelease Source # | |
Defined in Salve.Internal showsPrec :: Int -> PreRelease -> ShowS # show :: PreRelease -> String # showList :: [PreRelease] -> ShowS # | |
Generic PreRelease Source # | |
Defined in Salve.Internal type Rep PreRelease :: Type -> Type # from :: PreRelease -> Rep PreRelease x # to :: Rep PreRelease x -> PreRelease # | |
type Rep PreRelease Source # | |
Defined in Salve.Internal type Rep PreRelease = D1 (MetaData "PreRelease" "Salve.Internal" "salve-1.0.10-CS6HqfWAQu5RpiFvSg5on" False) (C1 (MetaCons "PreReleaseNumeric" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)) :+: C1 (MetaCons "PreReleaseTextual" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) |
Build metadata attached to a version. These are similar to
PreRelease
s with some key differences:
- There is no such thing as numeric builds. Even though builds can look like numbers, all builds are textual.
- As a result, builds that look numeric are allowed to have leading zeros.
- Builds cannot be compared. That is, they do not have an
Ord
instance.
Use parseBuild
to create builds.
Instances
Eq Build Source # | |
Data Build Source # | |
Defined in Salve.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Build -> c Build # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Build # dataTypeOf :: Build -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Build) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Build) # gmapT :: (forall b. Data b => b -> b) -> Build -> Build # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Build -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Build -> r # gmapQ :: (forall d. Data d => d -> u) -> Build -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Build -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Build -> m Build # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Build -> m Build # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Build -> m Build # | |
Read Build Source # | |
Show Build Source # | |
Generic Build Source # | |
type Rep Build Source # | |
Defined in Salve.Internal |
data Constraint Source #
Constrains allowable version numbers.
Use parseConstraint
to create constraints and satisfiesConstraint
to see
if a version number satisfies a constraint.
Instances
Constructors
makeVersion :: Word64 -> Word64 -> Word64 -> [PreRelease] -> [Build] -> Version Source #
Makes a new version number.
>>>
makeVersion 1 2 3 [unsafeParsePreRelease "pre"] [unsafeParseBuild "build"]
Version {versionMajor = 1, versionMinor = 2, versionPatch = 3, versionPreReleases = [PreReleaseTextual "pre"], versionBuilds = [Build "build"]}
This can be a useful alternative to parseVersion
if you want a total way
to create a version.
initialVersion :: Version Source #
The initial version number for development.
>>>
initialVersion
Version {versionMajor = 0, versionMinor = 0, versionPatch = 0, versionPreReleases = [], versionBuilds = []}
Parsing
parseVersion :: String -> Maybe Version Source #
Attempts to parse a version. This parser follows SemVer's BNF.
>>>
parseVersion "1.2.3-p.4+b.5"
Just (Version {versionMajor = 1, versionMinor = 2, versionPatch = 3, versionPreReleases = [PreReleaseTextual "p",PreReleaseNumeric 4], versionBuilds = [Build "b",Build "5"]})
Returns Nothing
if the parse fails.
>>>
parseVersion "wrong"
Nothing
Whitespace is allowed.
>>>
parseVersion " 1.2.3 "
Just (Version {versionMajor = 1, versionMinor = 2, versionPatch = 3, versionPreReleases = [], versionBuilds = []})
parsePreRelease :: String -> Maybe PreRelease Source #
Attempts to parse a pre-release.
>>>
parsePreRelease "pre"
Just (PreReleaseTextual "pre")>>>
parsePreRelease "1"
Just (PreReleaseNumeric 1)
Returns Nothing
if the parse fails.
>>>
parsePreRelease "wrong!"
Nothing
Numeric pre-releases cannot contain leading zeros.
>>>
parsePreRelease "01"
Nothing
parseBuild :: String -> Maybe Build Source #
Attempts to parse a build.
>>>
parseBuild "build"
Just (Build "build")>>>
parseBuild "1"
Just (Build "1")
Returns Nothing
if the parse fails.
>>>
parseBuild "wrong!"
Nothing
Unlike pre-releases, numeric builds can have leading zeros.
>>>
parseBuild "01"
Just (Build "01")
parseConstraint :: String -> Maybe Constraint Source #
Attempts to parse a constraint. This parser mostly follows npm's BNF.
>>>
parseConstraint ">1.2.3"
Just (ConstraintOperator OperatorGT (Version {versionMajor = 1, versionMinor = 2, versionPatch = 3, versionPreReleases = [], versionBuilds = []}))
Returns Nothing
if the parse fails.
>>>
parseConstraint "wrong"
Nothing
The two departures from npm's BNF are that x-ranges cannot be used with other operators and partial version numbers are not allowed.
>>>
parseConstraint "1.2.x"
Just (ConstraintWildcard (WildcardPatch 1 2))>>>
parseConstraint ">=1.2.x"
Nothing
>>>
parseConstraint "1.2"
Nothing>>>
parseConstraint ">=1.2"
Nothing
Unsafe
These functions can be used to unsafely parse strings. Instead of
returning Nothing
, they raise an exception. Only use these if you are sure
the string can be successfully parsed!
unsafeParseVersion :: String -> Version Source #
Parses a version.
>>>
unsafeParseVersion "1.2.3-p.4+b.5"
Version {versionMajor = 1, versionMinor = 2, versionPatch = 3, versionPreReleases = [PreReleaseTextual "p",PreReleaseNumeric 4], versionBuilds = [Build "b",Build "5"]}
Raises an exception if the parse fails.
>>>
unsafeParseVersion "wrong"
*** Exception: unsafeParseVersion: invalid version: "wrong" ...
See parseVersion
for a safe version of this function.
unsafeParsePreRelease :: String -> PreRelease Source #
Parses a pre-release.
>>>
unsafeParsePreRelease "pre"
PreReleaseTextual "pre"
Raises an exception if the parse fails.
>>>
unsafeParsePreRelease "wrong!"
*** Exception: unsafeParsePreRelease: invalid pre-release: "wrong!" ...
See parsePreRelease
for a safe version of this function.
unsafeParseBuild :: String -> Build Source #
Parses a build.
>>>
unsafeParseBuild "build"
Build "build"
Raises an exception if the parse fails.
>>>
unsafeParseBuild "wrong!"
Build "*** Exception: unsafeParseBuild: invalid build: "wrong!" ...
See parseBuild
for a safe version of this function.
unsafeParseConstraint :: String -> Constraint Source #
Parses a constraint.
>>>
unsafeParseConstraint ">1.2.3"
ConstraintOperator OperatorGT (Version {versionMajor = 1, versionMinor = 2, versionPatch = 3, versionPreReleases = [], versionBuilds = []})
Raises an exception if the parse fails.
>>>
unsafeParseConstraint "wrong"
*** Exception: unsafeParseConstraint: invalid constraint: "wrong" ...
See parseConstraint
for a safe version of this function.
Rendering
renderVersion :: Version -> String Source #
Renders a version.
>>>
renderVersion <$> parseVersion "1.2.3-p.4+b.5"
Just "1.2.3-p.4+b.5"
renderPreRelease :: PreRelease -> String Source #
Renders a pre-release.
>>>
renderPreRelease <$> parsePreRelease "pre"
Just "pre">>>
renderPreRelease <$> parsePreRelease "1"
Just "1"
renderBuild :: Build -> String Source #
Renders a build.
>>>
renderBuild <$> parseBuild "build"
Just "build">>>
renderBuild <$> parseBuild "1"
Just "1"
renderConstraint :: Constraint -> String Source #
Renders a constraint.
>>>
renderConstraint <$> parseConstraint ">1.2.3"
Just ">1.2.3"
Parsing and rendering a constraint doesn't always return what you started with.
>>>
renderConstraint <$> parseConstraint "=1.2.3"
Just "1.2.3"
Predicates
isUnstable :: Version -> Bool Source #
Conversions
fromBaseVersion :: Version -> Version Source #
Converts from a Version
from the base
package.
>>>
renderVersion . fromBaseVersion $ Version.makeVersion [1, 2, 3]
"1.2.3"
Missing version components are set to zero.
>>>
renderVersion . fromBaseVersion $ Version.makeVersion []
"0.0.0">>>
renderVersion . fromBaseVersion $ Version.makeVersion [1]
"1.0.0">>>
renderVersion . fromBaseVersion $ Version.makeVersion [1, 2]
"1.2.0"
Extra version components are ignored.
>>>
renderVersion . fromBaseVersion $ Version.makeVersion [1, 2, 3, 4]
"1.2.3"
Tags are ignored.
>>>
renderVersion . fromBaseVersion $ Version.Version [] ["ignored"]
"0.0.0"
toBaseVersion :: Version -> Version Source #
Converts to a Version
from the base
package.
>>>
toBaseVersion <$> parseVersion "1.2.3"
Just (Version {versionBranch = [1,2,3], versionTags = []})
Pre-releases and builds are converted to tags.
>>>
toBaseVersion <$> parseVersion "1.2.3-pre+build"
Just (Version {versionBranch = [1,2,3], versionTags = ["pre","build"]})
Helpers
bumpMajor :: Version -> Version Source #
Increments the major version number.
>>>
bumpMajor <$> parseVersion "0.0.0"
Just (Version {versionMajor = 1, versionMinor = 0, versionPatch = 0, versionPreReleases = [], versionBuilds = []})
The minor and patch numbers are reset to zero.
>>>
bumpMajor <$> parseVersion "1.2.3"
Just (Version {versionMajor = 2, versionMinor = 0, versionPatch = 0, versionPreReleases = [], versionBuilds = []})
The pre-releases and builds are removed.
>>>
bumpMajor <$> parseVersion "0.0.0-pre+build"
Just (Version {versionMajor = 1, versionMinor = 0, versionPatch = 0, versionPreReleases = [], versionBuilds = []})
Consider using majorLens
if you want to arbitrarily change the major
number, or if you don't want the other parts of the version to change.
bumpMinor :: Version -> Version Source #
Increments the minor version number.
>>>
bumpMinor <$> parseVersion "0.0.0"
Just (Version {versionMajor = 0, versionMinor = 1, versionPatch = 0, versionPreReleases = [], versionBuilds = []})
The patch number is reset to zero.
>>>
bumpMinor <$> parseVersion "1.2.3"
Just (Version {versionMajor = 1, versionMinor = 3, versionPatch = 0, versionPreReleases = [], versionBuilds = []})
The pre-releases and builds are removed.
>>>
bumpMinor <$> parseVersion "0.0.0-pre+build"
Just (Version {versionMajor = 0, versionMinor = 1, versionPatch = 0, versionPreReleases = [], versionBuilds = []})
Consider using minorLens
if you want to arbitrarily change the minor
number, or if you don't want the other parts of the version to change.
bumpPatch :: Version -> Version Source #
Increments the patch number.
>>>
bumpPatch <$> parseVersion "0.0.0"
Just (Version {versionMajor = 0, versionMinor = 0, versionPatch = 1, versionPreReleases = [], versionBuilds = []})
The major and minor numbers are not changed.
>>>
bumpPatch <$> parseVersion "1.2.3"
Just (Version {versionMajor = 1, versionMinor = 2, versionPatch = 4, versionPreReleases = [], versionBuilds = []})
The pre-releases and builds are removed.
>>>
bumpPatch <$> parseVersion "0.0.0-pre+build"
Just (Version {versionMajor = 0, versionMinor = 0, versionPatch = 1, versionPreReleases = [], versionBuilds = []})
Consider using patchLens
if you want to arbitrarily change the patch
number, or if you don't want the other parts of the version to change.
satisfiesConstraint :: Constraint -> Version -> Bool Source #
Lenses
These lenses can be used to access and modify specific parts of a
Version
.
Don't be scared by these type signatures. They are provided in full to avoid
the RankNTypes
language extension. The type signature
is the same as
Functor
f => (a -> f a) -> Version
-> f Version
Lens'
, which you may already be familiar with.Version
a
majorLens :: Functor f => (Word64 -> f Word64) -> Version -> f Version Source #
Focuses on the major version number.
>>>
view majorLens <$> parseVersion "1.2.3-pre.4+build.5"
Just 1>>>
set majorLens 4 <$> parseVersion "1.2.3"
Just (Version {versionMajor = 4, versionMinor = 2, versionPatch = 3, versionPreReleases = [], versionBuilds = []})
minorLens :: Functor f => (Word64 -> f Word64) -> Version -> f Version Source #
Focuses on the minor version number.
>>>
view minorLens <$> parseVersion "1.2.3-pre.4+build.5"
Just 2>>>
set minorLens 4 <$> parseVersion "1.2.3"
Just (Version {versionMajor = 1, versionMinor = 4, versionPatch = 3, versionPreReleases = [], versionBuilds = []})
patchLens :: Functor f => (Word64 -> f Word64) -> Version -> f Version Source #
Focuses on the patch version number.
>>>
view patchLens <$> parseVersion "1.2.3-pre.4+build.5"
Just 3>>>
set patchLens 4 <$> parseVersion "1.2.3"
Just (Version {versionMajor = 1, versionMinor = 2, versionPatch = 4, versionPreReleases = [], versionBuilds = []})
preReleasesLens :: Functor f => ([PreRelease] -> f [PreRelease]) -> Version -> f Version Source #
Focuses on the pre-release identifiers.
>>>
view preReleasesLens <$> parseVersion "1.2.3-pre.4+build.5"
Just [PreReleaseTextual "pre",PreReleaseNumeric 4]>>>
set preReleasesLens [] <$> parseVersion "1.2.3-pre"
Just (Version {versionMajor = 1, versionMinor = 2, versionPatch = 3, versionPreReleases = [], versionBuilds = []})
buildsLens :: Functor f => ([Build] -> f [Build]) -> Version -> f Version Source #
Focuses on the build metadata.
>>>
view buildsLens <$> parseVersion "1.2.3-pre.4+build.5"
Just [Build "build",Build "5"]>>>
set buildsLens [] <$> parseVersion "1.2.3+build"
Just (Version {versionMajor = 1, versionMinor = 2, versionPatch = 3, versionPreReleases = [], versionBuilds = []})
Examples
These examples are provided to showcase functionality and explain weird behavior. If something isn't clear, please open a pull request adding an example!
Versions
Leading zeros are not allowed.
>>>
parseVersion "01.0.0"
Nothing>>>
parseVersion "0.01.0"
Nothing>>>
parseVersion "0.0.01"
Nothing
Negative numbers are not allowed.
>>>
parseVersion "-1.0.0"
Nothing>>>
parseVersion "0.-1.0"
Nothing>>>
parseVersion "0.0.-1"
Nothing
Non-digits are not allowed.
>>>
parseVersion "a.0.0"
Nothing>>>
parseVersion "0.a.0"
Nothing>>>
parseVersion "0.0.a"
Nothing
Partial version numbers are not allowed.
>>>
parseVersion "0.0"
Nothing
Extra version numbers are not allowed.
>>>
parseVersion "0.0.0.0"
Nothing
Spaces are allowed
>>>
parseVersion " 0.0.0"
Just (Version {versionMajor = 0, versionMinor = 0, versionPatch = 0, versionPreReleases = [], versionBuilds = []})>>>
parseVersion "0.0.0 "
Just (Version {versionMajor = 0, versionMinor = 0, versionPatch = 0, versionPreReleases = [], versionBuilds = []})
Interior spaces are not allowed.
>>>
parseVersion "0 .0.0"
Nothing>>>
parseVersion "0. 0.0"
Nothing
Each version component cannot be larger than a 64-bit unsigned integer.
>>>
parseVersion "18446744073709551615.0.0"
Just (Version {versionMajor = 18446744073709551615, versionMinor = 0, versionPatch = 0, versionPreReleases = [], versionBuilds = []})>>>
parseVersion "18446744073709551616.0.0"
Nothing
Numeric pre-releases tags cannot be larger than a 64-bit unsigned integer.
>>>
parseVersion "0.0.0-18446744073709551615"
Just (Version {versionMajor = 0, versionMinor = 0, versionPatch = 0, versionPreReleases = [PreReleaseNumeric 18446744073709551615], versionBuilds = []})>>>
parseVersion "0.0.0-18446744073709551616"
Nothing
Build metadata is not numeric so it does not have any limit.
>>>
parseVersion "0.0.0+18446744073709551615"
Just (Version {versionMajor = 0, versionMinor = 0, versionPatch = 0, versionPreReleases = [], versionBuilds = [Build "18446744073709551615"]})>>>
parseVersion "0.0.0+18446744073709551616"
Just (Version {versionMajor = 0, versionMinor = 0, versionPatch = 0, versionPreReleases = [], versionBuilds = [Build "18446744073709551616"]})
Constraints
Partial version numbers are not allowed.
>>>
parseConstraint "1.2"
Nothing
Wildcards (also known as "x-ranges") are allowed. The exact character used for the wildcard is not round-tripped.
>>>
renderConstraint <$> parseConstraint "1.2.x"
Just "1.2.x">>>
renderConstraint <$> parseConstraint "1.2.X"
Just "1.2.x">>>
renderConstraint <$> parseConstraint "1.2.*"
Just "1.2.x"
An optional equals sign can be included with wildcard constraints.
>>>
renderConstraint <$> parseConstraint "=1.2.x"
Just "1.2.x"
Wildcards can be combined with other constraints.
>>>
renderConstraint <$> parseConstraint "1.2.x 2.3.4"
Just "1.2.x 2.3.4">>>
renderConstraint <$> parseConstraint "1.2.x || 2.3.4"
Just "1.2.x || 2.3.4"
Wildcards are allowed at any position.
>>>
renderConstraint <$> parseConstraint "1.2.x"
Just "1.2.x">>>
renderConstraint <$> parseConstraint "1.x.x"
Just "1.x.x">>>
renderConstraint <$> parseConstraint "x.x.x"
Just "x.x.x"
Non-wildcards cannot come after wildcards.
>>>
parseConstraint "1.x.3"
Nothing>>>
parseConstraint "x.2.3"
Nothing>>>
parseConstraint "x.x.3"
Nothing>>>
parseConstraint "x.2.x"
Nothing
Wildcards cannot be used with other operators.
>>>
parseConstraint "<1.2.x"
Nothing>>>
parseConstraint "<=1.2.x"
Nothing>>>
parseConstraint ">=1.2.x"
Nothing>>>
parseConstraint ">1.2.x"
Nothing>>>
parseConstraint "~1.2.x"
Nothing>>>
parseConstraint "^1.2.x"
Nothing>>>
parseConstraint "1.2.x - 2.3.4"
Nothing>>>
parseConstraint "1.2.3 - 2.3.x"
Nothing
Spaces are allowed in most places. Extra spaces are not round-tripped.
>>>
renderConstraint <$> parseConstraint " 1.2.3 "
Just "1.2.3">>>
renderConstraint <$> parseConstraint "> 1.2.3"
Just ">1.2.3">>>
renderConstraint <$> parseConstraint "1.2.3 - 2.3.4"
Just "1.2.3 - 2.3.4">>>
renderConstraint <$> parseConstraint "1.2.3 2.3.4"
Just "1.2.3 2.3.4">>>
renderConstraint <$> parseConstraint "1.2.3 || 2.3.4"
Just "1.2.3 || 2.3.4"
Parentheses are not allowed. Note that combining two constraints with a
space (and) has higher precedence than combining them with pipes (or). In
other words, "a b || c"
parses as "(a b) || c"
, not "a (b || c)"
.
>>>
parseConstraint "(1.2.3)"
Nothing>>>
parseConstraint "(1.2.3 || >1.2.3) <1.3.0"
Nothing>>>
parseConstraint "(>1.2.3 <1.3.0) || 1.2.3"
Nothing
Most constraints can be round-tripped through parsing and rendering.
>>>
renderConstraint <$> parseConstraint "<1.2.3"
Just "<1.2.3">>>
renderConstraint <$> parseConstraint "<=1.2.3"
Just "<=1.2.3">>>
renderConstraint <$> parseConstraint "1.2.3"
Just "1.2.3">>>
renderConstraint <$> parseConstraint ">=1.2.3"
Just ">=1.2.3">>>
renderConstraint <$> parseConstraint ">1.2.3"
Just ">1.2.3">>>
renderConstraint <$> parseConstraint "1.2.3 - 2.3.4"
Just "1.2.3 - 2.3.4">>>
renderConstraint <$> parseConstraint "~1.2.3"
Just "~1.2.3">>>
renderConstraint <$> parseConstraint "^1.2.3"
Just "^1.2.3">>>
renderConstraint <$> parseConstraint ">1.2.3 <2.0.0"
Just ">1.2.3 <2.0.0">>>
renderConstraint <$> parseConstraint "1.2.3 || >1.2.3"
Just "1.2.3 || >1.2.3"
Explicit equal signs do not get round-tripped.
>>>
renderConstraint <$> parseConstraint "=1.2.3"
Just "1.2.3"
Pre-releases and builds are allowed on any constraints except wildcards.
>>>
renderConstraint <$> parseConstraint "1.2.3-p+b"
Just "1.2.3-p+b">>>
renderConstraint <$> parseConstraint ">1.2.3-p+b"
Just ">1.2.3-p+b">>>
renderConstraint <$> parseConstraint "1.2.3-p+b - 2.3.4-p+b"
Just "1.2.3-p+b - 2.3.4-p+b">>>
renderConstraint <$> parseConstraint "~1.2.3-p+b"
Just "~1.2.3-p+b">>>
renderConstraint <$> parseConstraint "^1.2.3-p+b"
Just "^1.2.3-p+b"
>>>
parseConstraint "1.2.x-p+b"
Nothing
These examples show every type of constraint in a single expression.
>>>
renderConstraint <$> parseConstraint "<1.2.0 <=1.2.1 =1.2.2 >=1.2.3 >1.2.4 1.2.5 1.2.6 - 1.2.7 ~1.2.8 ^1.2.9 1.2.x"
Just "<1.2.0 <=1.2.1 1.2.2 >=1.2.3 >1.2.4 1.2.5 1.2.6 - 1.2.7 ~1.2.8 ^1.2.9 1.2.x">>>
renderConstraint <$> parseConstraint "<1.2.0 <=1.2.1 || =1.2.2 >=1.2.3 || >1.2.4 1.2.5 || 1.2.6 - 1.2.7 ~1.2.8 || ^1.2.9 1.2.x"
Just "<1.2.0 <=1.2.1 || 1.2.2 >=1.2.3 || >1.2.4 1.2.5 || 1.2.6 - 1.2.7 ~1.2.8 || ^1.2.9 1.2.x">>>
renderConstraint <$> parseConstraint "<1.2.0 || <=1.2.1 =1.2.2 || >=1.2.3 >1.2.4 || 1.2.5 1.2.6 - 1.2.7 || ~1.2.8 ^1.2.9 || 1.2.x"
Just "<1.2.0 || <=1.2.1 1.2.2 || >=1.2.3 >1.2.4 || 1.2.5 1.2.6 - 1.2.7 || ~1.2.8 ^1.2.9 || 1.2.x">>>
renderConstraint <$> parseConstraint "<1.2.0 || <=1.2.1 || =1.2.2 || >=1.2.3 || >1.2.4 || 1.2.5 || 1.2.6 - 1.2.7 || ~1.2.8 || ^1.2.9 || 1.2.x"
Just "<1.2.0 || <=1.2.1 || 1.2.2 || >=1.2.3 || >1.2.4 || 1.2.5 || 1.2.6 - 1.2.7 || ~1.2.8 || ^1.2.9 || 1.2.x"
Satisfying constraints
Although in general you should use satisfiesConstraint
, parseVersion
,
and parseConstraint
, doing that here makes it hard to tell what the
examples are doing. An operator makes things clearer.
>>>
satisfiesConstraint <$> parseConstraint "=1.2.3" <*> parseVersion "1.2.3"
Just True>>>
let version ? constraint = satisfiesConstraint (unsafeParseConstraint constraint) (unsafeParseVersion version)
>>>
"1.2.3" ? "=1.2.3"
True
Less than:
>>>
"1.2.2" ? "<1.2.3"
True>>>
"1.2.3" ? "<1.2.3"
False>>>
"1.2.4" ? "<1.2.3"
False>>>
"1.2.3-pre" ? "<1.2.3"
TrueLess than or equal to:
>>>
"1.2.2" ? "<=1.2.3"
True>>>
"1.2.3" ? "<=1.2.3"
True>>>
"1.2.4" ? "<=1.2.3"
FalseEqual to:
>>>
"1.2.2" ? "=1.2.3"
False>>>
"1.2.3" ? "=1.2.3"
True>>>
"1.2.4" ? "=1.2.3"
False>>>
"1.2.3-pre" ? "=1.2.3"
False>>>
"1.2.3+build" ? "=1.2.3"
TrueGreater than or equal to:
>>>
"1.2.2" ? ">=1.2.3"
False>>>
"1.2.3" ? ">=1.2.3"
True>>>
"1.2.4" ? ">=1.2.3"
TrueGreater than:
>>>
"1.2.2" ? ">1.2.3"
False>>>
"1.2.3" ? ">1.2.3"
False>>>
"1.2.4" ? ">1.2.3"
True>>>
"1.2.4-pre" ? ">1.2.3"
True>>>
"1.2.4" ? ">1.2.3-pre"
TrueAnd:
>>>
"1.2.3" ? ">1.2.3 <1.2.5"
False>>>
"1.2.4" ? ">1.2.3 <1.2.5"
True>>>
"1.2.5" ? ">1.2.3 <1.2.5"
FalseOr:
>>>
"1.2.2" ? "1.2.3 || 1.2.4"
False>>>
"1.2.3" ? "1.2.3 || 1.2.4"
True>>>
"1.2.4" ? "1.2.3 || 1.2.4"
True>>>
"1.2.5" ? "1.2.3 || 1.2.4"
FalseAnd & or:
>>>
"1.2.2" ? "1.2.2 || >1.2.3 <1.3.0"
True>>>
"1.2.3" ? "1.2.2 || >1.2.3 <1.3.0"
False>>>
"1.2.4" ? "1.2.2 || >1.2.3 <1.3.0"
True>>>
"1.3.0" ? "1.2.2 || >1.2.3 <1.3.0"
FalseHyphen:
>>>
"1.2.2" ? "1.2.3 - 1.2.4"
False>>>
"1.2.3" ? "1.2.3 - 1.2.4"
True>>>
"1.2.4" ? "1.2.3 - 1.2.4"
True>>>
"1.2.5" ? "1.2.3 - 1.2.4"
FalseTilde:
>>>
"1.2.2" ? "~1.2.3"
False>>>
"1.2.3" ? "~1.2.3"
True>>>
"1.2.4" ? "~1.2.3"
True>>>
"1.3.0" ? "~1.2.3"
FalseCaret:
>>>
"1.2.2" ? "^1.2.3"
False>>>
"1.2.3" ? "^1.2.3"
True>>>
"1.2.4" ? "^1.2.3"
True>>>
"1.3.0" ? "^1.2.3"
True>>>
"2.0.0" ? "^1.2.3"
False>>>
"0.2.2" ? "^0.2.3"
False>>>
"0.2.3" ? "^0.2.3"
True>>>
"0.2.4" ? "^0.2.3"
True>>>
"0.3.0" ? "^0.2.3"
False>>>
"0.0.2" ? "^0.0.3"
False>>>
"0.0.3" ? "^0.0.3"
True>>>
"0.0.4" ? "^0.0.3"
FalseWildcard:
>>>
"1.1.0" ? "1.2.x"
False>>>
"1.2.3" ? "1.2.x"
True>>>
"1.3.0" ? "1.2.x"
False>>>
"0.1.0" ? "1.x.x"
False>>>
"1.0.0" ? "1.x.x"
True>>>
"1.2.3" ? "1.x.x"
True>>>
"2.0.0" ? "1.x.x"
False>>>
"0.0.0" ? "x.x.x"
True>>>
"1.2.3" ? "x.x.x"
True>>>
"2.0.0" ? "x.x.x"
True