Copyright | (c) Colin Woodbury 2015 - 2018 |
---|---|
License | BSD3 |
Maintainer | Colin Woodbury <colingw@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
A library for parsing and comparing software version numbers.
We like to give version numbers to our software in a myriad of different ways. Some ways follow strict guidelines for incrementing and comparison. Some follow conventional wisdom and are generally self-consistent. Some are just plain asinine. This library provides a means of parsing and comparing any style of versioning, be it a nice Semantic Version like this:
1.2.3-r1+git123
...or a monstrosity like this:
2:10.2+0.0093r3+1-1
Please switch to Semantic Versioning if you aren't currently using it. It provides consistency in version incrementing and has the best constraints on comparisons.
Using the Parsers
In general, versioning
is the function you want. It attempts to parse
a given Text
using the three individual parsers, semver
, version
and mess
. If one fails, it tries the next. If you know you only want
to parse one specific version type, use that parser directly
(e.g. semver
).
Synopsis
- data Versioning
- data SemVer = SemVer {}
- data Version = Version {}
- data Mess
- data VUnit
- digits :: Word -> VUnit
- str :: Text -> Maybe VUnit
- type VChunk = [VUnit]
- data VSep
- type ParsingError = ParseErrorBundle Text Void
- versioning :: Text -> Either ParsingError Versioning
- semver :: Text -> Either ParsingError SemVer
- version :: Text -> Either ParsingError Version
- mess :: Text -> Either ParsingError Mess
- versioning' :: Parsec Void Text Versioning
- semver' :: Parsec Void Text SemVer
- version' :: Parsec Void Text Version
- mess' :: Parsec Void Text Mess
- prettyV :: Versioning -> Text
- prettySemVer :: SemVer -> Text
- prettyVer :: Version -> Text
- prettyMess :: Mess -> Text
- errorBundlePretty :: (Stream s, ShowErrorComponent e) => ParseErrorBundle s e -> String
- type Lens' s a = forall f. Functor f => (a -> f a) -> s -> f s
- type Traversal' s a = forall f. Applicative f => (a -> f a) -> s -> f s
- class Semantic v where
- _Versioning :: Traversal' Text Versioning
- _SemVer :: Traversal' Text SemVer
- _Version :: Traversal' Text Version
- _Mess :: Traversal' Text Mess
- _Ideal :: Traversal' Versioning SemVer
- _General :: Traversal' Versioning Version
- _Complex :: Traversal' Versioning Mess
- epoch :: Lens' Version (Maybe Word)
- _Digits :: Traversal' VUnit Word
- _Str :: Traversal' VUnit Text
Types
data Versioning Source #
A top-level Versioning type. Acts as a wrapper for the more specific types. This allows each subtype to have its own parser, and for said parsers to be composed. This is useful for specifying custom behaviour for when a certain parser fails.
Instances
An (Ideal) version number that conforms to Semantic Versioning. This is a prescriptive parser, meaning it follows the SemVer standard.
Legal semvers are of the form: MAJOR.MINOR.PATCH-PREREL+META
Example: 1.2.3-r1+commithash
Extra Rules:
- Pre-release versions have lower precedence than normal versions.
- Build metadata does not affect version precedence.
- PREREL and META strings may only contain ASCII alphanumerics.
For more information, see http://semver.org
Instances
A (General) Version.
Not quite as ideal as a SemVer
, but has some internal consistancy
from version to version.
Generally conforms to the x.x.x-x
pattern, and may optionally have an epoch.
These are prefixes marked by a colon, like in 1:2.3.4
.
Examples of Version
that are not SemVer
: 0.25-2, 8.u51-1, 20150826-1, 1:2.3.4
Instances
Eq Version Source # | |
Ord Version Source # | Customized. |
Show Version Source # | |
Generic Version Source # | |
Semigroup Version Source # | |
Monoid Version Source # | |
NFData Version Source # | |
Defined in Data.Versions | |
Hashable Version Source # | |
Defined in Data.Versions | |
Semantic Version Source # | |
type Rep Version Source # | |
Defined in Data.Versions type Rep Version = D1 (MetaData "Version" "Data.Versions" "versions-3.5.0-9PXfYd6LkPmGhgGdn1KXtV" False) (C1 (MetaCons "Version" PrefixI True) (S1 (MetaSel (Just "_vEpoch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Word)) :*: (S1 (MetaSel (Just "_vChunks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [VChunk]) :*: S1 (MetaSel (Just "_vRel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [VChunk])))) |
A (Complex) Mess. This is a descriptive parser, based on examples of stupidly crafted version numbers used in the wild.
Groups of letters/numbers, separated by a period, can be
further separated by the symbols _-+:
Unfortunately, VChunk
s cannot be used here, as some developers have
numbers like 1.003.04
which make parsers quite sad.
Not guaranteed to have well-defined ordering (Ord
) behaviour,
but so far internal tests show consistency.
Instances
Eq Mess Source # | |
Ord Mess Source # | |
Show Mess Source # | |
Generic Mess Source # | |
NFData Mess Source # | |
Defined in Data.Versions | |
Hashable Mess Source # | |
Defined in Data.Versions | |
Semantic Mess Source # | |
type Rep Mess Source # | |
Defined in Data.Versions type Rep Mess = D1 (MetaData "Mess" "Data.Versions" "versions-3.5.0-9PXfYd6LkPmGhgGdn1KXtV" False) (C1 (MetaCons "VLeaf" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])) :+: C1 (MetaCons "VNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VSep) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Mess)))) |
A single unit of a Version. May be digits or a string of characters.
Groups of these are called VChunk
s, and are the identifiers separated
by periods in the source.
Instances
Eq VUnit Source # | |
Ord VUnit Source # | |
Read VUnit Source # | |
Show VUnit Source # | |
Generic VUnit Source # | |
Semigroup VUnit Source # | |
Monoid VUnit Source # | |
NFData VUnit Source # | |
Defined in Data.Versions | |
Hashable VUnit Source # | |
Defined in Data.Versions | |
type Rep VUnit Source # | |
Defined in Data.Versions type Rep VUnit = D1 (MetaData "VUnit" "Data.Versions" "versions-3.5.0-9PXfYd6LkPmGhgGdn1KXtV" False) (C1 (MetaCons "Digits" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)) :+: C1 (MetaCons "Str" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
type VChunk = [VUnit] Source #
A logical unit of a version number. Can consist of multiple letters and numbers.
Developers use a number of symbols to seperate groups of digits/letters in their version numbers. These are:
- A colon (:). Often denotes an "epoch".
- A hyphen (-).
- A plus (+). Stop using this outside of metadata if you are. Example:
10.2+0.93+1-1
- An underscore (_). Stop using this if you are.
Instances
Eq VSep Source # | |
Show VSep Source # | |
Generic VSep Source # | |
NFData VSep Source # | |
Defined in Data.Versions | |
Hashable VSep Source # | |
Defined in Data.Versions | |
type Rep VSep Source # | |
Defined in Data.Versions type Rep VSep = D1 (MetaData "VSep" "Data.Versions" "versions-3.5.0-9PXfYd6LkPmGhgGdn1KXtV" False) ((C1 (MetaCons "VColon" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "VHyphen" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "VPlus" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "VUnder" PrefixI False) (U1 :: * -> *))) |
Parsing Versions
type ParsingError = ParseErrorBundle Text Void Source #
A synonym for the more verbose megaparsec
error type.
Megaparsec Parsers
For when you'd like to mix version parsing into some larger parser.
versioning' :: Parsec Void Text Versioning Source #
Parse a Versioning
. Assumes the version number is the last token in
the string.
Pretty Printing
prettyV :: Versioning -> Text Source #
Convert any parsed Versioning type to its textual representation.
:: (Stream s, ShowErrorComponent e) | |
=> ParseErrorBundle s e | Parse error bundle to display |
-> String | Textual rendition of the bundle |
Pretty-print a ParseErrorBundle
. All ParseError
s in the bundle will
be pretty-printed in order together with the corresponding offending
lines by doing a single efficient pass over the input stream. The
rendered String
always ends with a newline.
Since: megaparsec-7.0.0
Lenses
type Lens' s a = forall f. Functor f => (a -> f a) -> s -> f s Source #
Simple Lenses compatible with both lens and microlens.
type Traversal' s a = forall f. Applicative f => (a -> f a) -> s -> f s Source #
Simple Traversals compatible with both lens and microlens.
class Semantic v where Source #
Version types which sanely and safely yield SemVer
-like information
about themselves. For instances other than SemVer
itself however,
these optics may not yield anything, depending on the actual value being
traversed. Hence, the optics here are all Traversal'
s.
Consider the Version
1.2.3.4.5
. We can imagine wanting to increment
the minor number:
λ "1.2.3.4.5" & minor %~ (+ 1) "1.3.3.4.5"
But of course something like this would fail:
λ "1.e.3.4.5" & minor %~ (+ 1) "1.e.3.4.5"
However!
λ "1.e.3.4.5" & major %~ (+ 1) "2.e.3.4.5"
major :: Traversal' v Word Source #
MAJOR.minor.patch-prerel+meta
minor :: Traversal' v Word Source #
major.MINOR.patch-prerel+meta
patch :: Traversal' v Word Source #
major.minor.PATCH-prerel+meta
release :: Traversal' v [VChunk] Source #
major.minor.patch-PREREL+meta
meta :: Traversal' v [VChunk] Source #
major.minor.patch-prerel+META
semantic :: Traversal' v SemVer Source #
A Natural Transformation into an proper SemVer
.
Traversing Text
When traversing Text
, leveraging its Semantic
instance will
likely benefit you more than using these Traversals directly.
_Versioning :: Traversal' Text Versioning Source #
Traverse some Text for its inner versioning.
λ "1.2.3" & _Versioning . _Ideal . patch %~ (+ 1) -- or just: "1.2.3" & patch %~ (+ 1) "1.2.4"