versions-3.5.1: Types and parsers for software version numbers.

Copyright(c) Colin Woodbury 2015 - 2019
LicenseBSD3
MaintainerColin Woodbury <colingw@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Versions

Contents

Description

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

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
Eq Versioning Source # 
Instance details

Defined in Data.Versions

Ord Versioning Source #

Comparison of Ideals is always well defined.

If comparison of Generals is well-defined, then comparison of Ideal and General is well-defined, as there exists a perfect mapping from Ideal to General.

If comparison of Complexes is well-defined, then comparison of General and Complex is well defined for the same reason. This implies comparison of Ideal and Complex is also well-defined.

Instance details

Defined in Data.Versions

Show Versioning Source # 
Instance details

Defined in Data.Versions

Generic Versioning Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep Versioning :: Type -> Type #

NFData Versioning Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: Versioning -> () #

Hashable Versioning Source # 
Instance details

Defined in Data.Versions

Semantic Versioning Source # 
Instance details

Defined in Data.Versions

type Rep Versioning Source # 
Instance details

Defined in Data.Versions

data SemVer Source #

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:

  1. Pre-release versions have lower precedence than normal versions.
  2. Build metadata does not affect version precedence.
  3. PREREL and META strings may only contain ASCII alphanumerics.

For more information, see http://semver.org

Constructors

SemVer 
Instances
Eq SemVer Source #

Two SemVers are equal if all fields except metadata are equal.

Instance details

Defined in Data.Versions

Methods

(==) :: SemVer -> SemVer -> Bool #

(/=) :: SemVer -> SemVer -> Bool #

Ord SemVer Source #

Build metadata does not affect version precedence.

Instance details

Defined in Data.Versions

Show SemVer Source # 
Instance details

Defined in Data.Versions

Generic SemVer Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep SemVer :: Type -> Type #

Methods

from :: SemVer -> Rep SemVer x #

to :: Rep SemVer x -> SemVer #

Semigroup SemVer Source # 
Instance details

Defined in Data.Versions

Monoid SemVer Source # 
Instance details

Defined in Data.Versions

NFData SemVer Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: SemVer -> () #

Hashable SemVer Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> SemVer -> Int #

hash :: SemVer -> Int #

Semantic SemVer Source # 
Instance details

Defined in Data.Versions

type Rep SemVer Source # 
Instance details

Defined in Data.Versions

data Version Source #

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

Constructors

Version 

Fields

Instances
Eq Version Source # 
Instance details

Defined in Data.Versions

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

Ord Version Source #

Customized.

Instance details

Defined in Data.Versions

Show Version Source # 
Instance details

Defined in Data.Versions

Generic Version Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Semigroup Version Source # 
Instance details

Defined in Data.Versions

Monoid Version Source # 
Instance details

Defined in Data.Versions

NFData Version Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: Version -> () #

Hashable Version Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> Version -> Int #

hash :: Version -> Int #

Semantic Version Source # 
Instance details

Defined in Data.Versions

type Rep Version Source # 
Instance details

Defined in Data.Versions

type Rep Version = D1 (MetaData "Version" "Data.Versions" "versions-3.5.1-HQeJiKULViiDmtGrTnMrBQ" 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]))))

data Mess Source #

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, VChunks 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.

Constructors

VLeaf [Text] 
VNode [Text] VSep Mess 
Instances
Eq Mess Source # 
Instance details

Defined in Data.Versions

Methods

(==) :: Mess -> Mess -> Bool #

(/=) :: Mess -> Mess -> Bool #

Ord Mess Source # 
Instance details

Defined in Data.Versions

Methods

compare :: Mess -> Mess -> Ordering #

(<) :: Mess -> Mess -> Bool #

(<=) :: Mess -> Mess -> Bool #

(>) :: Mess -> Mess -> Bool #

(>=) :: Mess -> Mess -> Bool #

max :: Mess -> Mess -> Mess #

min :: Mess -> Mess -> Mess #

Show Mess Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> Mess -> ShowS #

show :: Mess -> String #

showList :: [Mess] -> ShowS #

Generic Mess Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep Mess :: Type -> Type #

Methods

from :: Mess -> Rep Mess x #

to :: Rep Mess x -> Mess #

NFData Mess Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: Mess -> () #

Hashable Mess Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> Mess -> Int #

hash :: Mess -> Int #

Semantic Mess Source # 
Instance details

Defined in Data.Versions

type Rep Mess Source # 
Instance details

Defined in Data.Versions

data VUnit Source #

A single unit of a Version. May be digits or a string of characters. Groups of these are called VChunks, and are the identifiers separated by periods in the source.

Constructors

Digits Word 
Str Text 
Instances
Eq VUnit Source # 
Instance details

Defined in Data.Versions

Methods

(==) :: VUnit -> VUnit -> Bool #

(/=) :: VUnit -> VUnit -> Bool #

Ord VUnit Source # 
Instance details

Defined in Data.Versions

Methods

compare :: VUnit -> VUnit -> Ordering #

(<) :: VUnit -> VUnit -> Bool #

(<=) :: VUnit -> VUnit -> Bool #

(>) :: VUnit -> VUnit -> Bool #

(>=) :: VUnit -> VUnit -> Bool #

max :: VUnit -> VUnit -> VUnit #

min :: VUnit -> VUnit -> VUnit #

Read VUnit Source # 
Instance details

Defined in Data.Versions

Show VUnit Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> VUnit -> ShowS #

show :: VUnit -> String #

showList :: [VUnit] -> ShowS #

Generic VUnit Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep VUnit :: Type -> Type #

Methods

from :: VUnit -> Rep VUnit x #

to :: Rep VUnit x -> VUnit #

Semigroup VUnit Source # 
Instance details

Defined in Data.Versions

Methods

(<>) :: VUnit -> VUnit -> VUnit #

sconcat :: NonEmpty VUnit -> VUnit #

stimes :: Integral b => b -> VUnit -> VUnit #

Monoid VUnit Source # 
Instance details

Defined in Data.Versions

Methods

mempty :: VUnit #

mappend :: VUnit -> VUnit -> VUnit #

mconcat :: [VUnit] -> VUnit #

NFData VUnit Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: VUnit -> () #

Hashable VUnit Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> VUnit -> Int #

hash :: VUnit -> Int #

type Rep VUnit Source # 
Instance details

Defined in Data.Versions

digits :: Word -> VUnit Source #

Smart constructor for a VUnit made of digits.

str :: Text -> Maybe VUnit Source #

Smart constructor for a VUnit made of letters.

type VChunk = [VUnit] Source #

A logical unit of a version number. Can consist of multiple letters and numbers.

data VSep Source #

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.

Constructors

VColon 
VHyphen 
VPlus 
VUnder 
Instances
Eq VSep Source # 
Instance details

Defined in Data.Versions

Methods

(==) :: VSep -> VSep -> Bool #

(/=) :: VSep -> VSep -> Bool #

Show VSep Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> VSep -> ShowS #

show :: VSep -> String #

showList :: [VSep] -> ShowS #

Generic VSep Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep VSep :: Type -> Type #

Methods

from :: VSep -> Rep VSep x #

to :: Rep VSep x -> VSep #

NFData VSep Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: VSep -> () #

Hashable VSep Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> VSep -> Int #

hash :: VSep -> Int #

type Rep VSep Source # 
Instance details

Defined in Data.Versions

type Rep VSep = D1 (MetaData "VSep" "Data.Versions" "versions-3.5.1-HQeJiKULViiDmtGrTnMrBQ" False) ((C1 (MetaCons "VColon" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VHyphen" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "VPlus" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VUnder" PrefixI False) (U1 :: Type -> Type)))

Parsing Versions

type ParsingError = ParseErrorBundle Text Void Source #

A synonym for the more verbose megaparsec error type.

versioning :: Text -> Either ParsingError Versioning Source #

Parse a piece of Text into either an (Ideal) SemVer, a (General) Version, or a (Complex) Mess.

semver :: Text -> Either ParsingError SemVer Source #

Parse a (Ideal) Semantic Version.

version :: Text -> Either ParsingError Version Source #

Parse a (General) Version, as defined above.

mess :: Text -> Either ParsingError Mess Source #

Parse a (Complex) Mess, as defined above.

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.

semver' :: Parsec Void Text SemVer Source #

Internal megaparsec parser of semver.

version' :: Parsec Void Text Version Source #

Internal megaparsec parser of version.

mess' :: Parsec Void Text Mess Source #

Internal megaparsec parser of mess.

Pretty Printing

prettyV :: Versioning -> Text Source #

Convert any parsed Versioning type to its textual representation.

prettySemVer :: SemVer -> Text Source #

Convert a SemVer back to its textual representation.

prettyVer :: Version -> Text Source #

Convert a Version back to its textual representation.

prettyMess :: Mess -> Text Source #

Convert a Mess back to its textual representation.

errorBundlePretty #

Arguments

:: (Stream s, ShowErrorComponent e) 
=> ParseErrorBundle s e

Parse error bundle to display

-> String

Textual rendition of the bundle

Pretty-print a ParseErrorBundle. All ParseErrors 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"

Methods

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.

Instances
Semantic Text Source # 
Instance details

Defined in Data.Versions

Semantic Mess Source # 
Instance details

Defined in Data.Versions

Semantic Version Source # 
Instance details

Defined in Data.Versions

Semantic SemVer Source # 
Instance details

Defined in Data.Versions

Semantic Versioning Source # 
Instance details

Defined in Data.Versions

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"

_SemVer :: Traversal' Text SemVer Source #

Traverse some Text for its inner SemVer.

_Version :: Traversal' Text Version Source #

Traverse some Text for its inner Version.

_Mess :: Traversal' Text Mess Source #

Traverse some Text for its inner Mess.

Versioning Traversals

(General) Version Lenses

Misc. Lenses / Traversals