versions-6.0.3: Types and parsers for software version numbers.
Copyright(c) Colin Woodbury 2015 - 2023
LicenseBSD3
MaintainerColin Woodbury <colin@fosskers.ca>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Versions

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.

This library implements version 2.0.0 of the SemVer spec.

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

Instances details
Data Versioning Source # 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Versioning -> c Versioning

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Versioning

toConstr :: Versioning -> Constr

dataTypeOf :: Versioning -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Versioning)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Versioning)

gmapT :: (forall b. Data b => b -> b) -> Versioning -> Versioning

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Versioning -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Versioning -> r

gmapQ :: (forall d. Data d => d -> u) -> Versioning -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Versioning -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Versioning -> m Versioning

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Versioning -> m Versioning

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Versioning -> m Versioning

Generic Versioning Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep Versioning :: Type -> Type

Methods

from :: Versioning -> Rep Versioning x

to :: Rep Versioning x -> Versioning

Show Versioning Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> Versioning -> ShowS

show :: Versioning -> String

showList :: [Versioning] -> ShowS

NFData Versioning Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: Versioning -> ()

Eq Versioning Source # 
Instance details

Defined in Data.Versions

Methods

(==) :: Versioning -> Versioning -> Bool

(/=) :: Versioning -> Versioning -> Bool

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

Hashable Versioning Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> Versioning -> Int

hash :: Versioning -> Int

Semantic Versioning Source # 
Instance details

Defined in Data.Versions

Lift Versioning Source # 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => Versioning -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => Versioning -> Code m Versioning

type Rep Versioning Source # 
Instance details

Defined in Data.Versions

type Rep Versioning = D1 ('MetaData "Versioning" "Data.Versions" "versions-6.0.3-F3PyfH85ZwcBZVNAPGE3uF" 'False) (C1 ('MetaCons "Ideal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SemVer)) :+: (C1 ('MetaCons "General" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "Complex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mess))))

isIdeal :: Versioning -> Bool Source #

Short-hand for detecting a SemVer.

isGeneral :: Versioning -> Bool Source #

Short-hand for detecting a Version.

isComplex :: Versioning -> Bool Source #

Short-hand for detecting a Mess.

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 and hyphens.

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

Constructors

SemVer 

Fields

Instances

Instances details
Data SemVer Source # 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SemVer -> c SemVer

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SemVer

toConstr :: SemVer -> Constr

dataTypeOf :: SemVer -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SemVer)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SemVer)

gmapT :: (forall b. Data b => b -> b) -> SemVer -> SemVer

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SemVer -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SemVer -> r

gmapQ :: (forall d. Data d => d -> u) -> SemVer -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> SemVer -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SemVer -> m SemVer

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SemVer -> m SemVer

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SemVer -> m SemVer

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

Show SemVer Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> SemVer -> ShowS

show :: SemVer -> String

showList :: [SemVer] -> ShowS

NFData SemVer Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: SemVer -> ()

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

Methods

compare :: SemVer -> SemVer -> Ordering

(<) :: SemVer -> SemVer -> Bool

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

(>) :: SemVer -> SemVer -> Bool

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

max :: SemVer -> SemVer -> SemVer

min :: SemVer -> SemVer -> 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

Lift SemVer Source # 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => SemVer -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => SemVer -> Code m SemVer

type Rep SemVer Source # 
Instance details

Defined in Data.Versions

type Rep SemVer = D1 ('MetaData "SemVer" "Data.Versions" "versions-6.0.3-F3PyfH85ZwcBZVNAPGE3uF" 'False) (C1 ('MetaCons "SemVer" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_svMajor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "_svMinor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :*: (S1 ('MetaSel ('Just "_svPatch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: (S1 ('MetaSel ('Just "_svPreRel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Release)) :*: S1 ('MetaSel ('Just "_svMeta") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))))))

newtype PVP Source #

A PVP version number specific to the Haskell ecosystem. Like SemVer this is a prescriptive scheme, and follows the PVP spec.

Legal PVP values are of the form: MAJOR(.MAJOR.MINOR)

Example: 1.2.3

Extra Rules:

  1. Each component must be a number.
  2. Only the first MAJOR component is actually necessary. Otherwise, there can be any number of components. 1.2.3.4.5.6.7 is legal.
  3. Unlike SemVer there are two MAJOR components, and both indicate a breaking change. The spec otherwise designates no special meaning to components past the MINOR position.

Constructors

PVP 

Fields

Instances

Instances details
Data PVP Source # 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PVP -> c PVP

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PVP

toConstr :: PVP -> Constr

dataTypeOf :: PVP -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PVP)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PVP)

gmapT :: (forall b. Data b => b -> b) -> PVP -> PVP

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PVP -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PVP -> r

gmapQ :: (forall d. Data d => d -> u) -> PVP -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> PVP -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PVP -> m PVP

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PVP -> m PVP

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PVP -> m PVP

Generic PVP Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep PVP :: Type -> Type

Methods

from :: PVP -> Rep PVP x

to :: Rep PVP x -> PVP

Show PVP Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> PVP -> ShowS

show :: PVP -> String

showList :: [PVP] -> ShowS

NFData PVP Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: PVP -> ()

Eq PVP Source # 
Instance details

Defined in Data.Versions

Methods

(==) :: PVP -> PVP -> Bool

(/=) :: PVP -> PVP -> Bool

Ord PVP Source # 
Instance details

Defined in Data.Versions

Methods

compare :: PVP -> PVP -> Ordering

(<) :: PVP -> PVP -> Bool

(<=) :: PVP -> PVP -> Bool

(>) :: PVP -> PVP -> Bool

(>=) :: PVP -> PVP -> Bool

max :: PVP -> PVP -> PVP

min :: PVP -> PVP -> PVP

Hashable PVP Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> PVP -> Int

hash :: PVP -> Int

Semantic PVP Source # 
Instance details

Defined in Data.Versions

Lift PVP Source # 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => PVP -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => PVP -> Code m PVP

type Rep PVP Source # 
Instance details

Defined in Data.Versions

type Rep PVP = D1 ('MetaData "PVP" "Data.Versions" "versions-6.0.3-F3PyfH85ZwcBZVNAPGE3uF" 'True) (C1 ('MetaCons "PVP" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pComponents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Word))))

data Version Source #

A version number with decent structure and comparison logic.

This is a descriptive scheme, meaning that it encapsulates the most common, unconscious patterns that developers use when assigning version numbers to their software. If not SemVer, most version numbers found in the wild will parse as a Version. These generally conform to the x.x.x-x pattern, and may optionally have an epoch.

Epochs are prefixes marked by a colon, like in 1:2.3.4. When comparing two Version values, epochs take precedent. So 2:1.0.0 > 1:9.9.9. If one of the given Versions has no epoch, its epoch is assumed to be 0.

Examples of Version that are not SemVer: 0.25-2, 8.u51-1, 20150826-1, 1:2.3.4

Constructors

Version 

Fields

Instances

Instances details
Data Version Source # 
Instance details

Defined in Data.Versions

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 :: forall r r'. (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

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

Show Version Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> Version -> ShowS

show :: Version -> String

showList :: [Version] -> ShowS

NFData Version Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: Version -> ()

Eq Version Source # 
Instance details

Defined in Data.Versions

Methods

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

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

Ord Version Source #

Customized. As in SemVer, metadata is ignored for the purpose of comparison.

Instance details

Defined in Data.Versions

Methods

compare :: Version -> Version -> Ordering

(<) :: Version -> Version -> Bool

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

(>) :: Version -> Version -> Bool

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

max :: Version -> Version -> Version

min :: Version -> Version -> 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

Lift Version Source # 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => Version -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => Version -> Code m Version

type Rep Version Source # 
Instance details

Defined in Data.Versions

type Rep Version = D1 ('MetaData "Version" "Data.Versions" "versions-6.0.3-F3PyfH85ZwcBZVNAPGE3uF" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_vEpoch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Word)) :*: S1 ('MetaSel ('Just "_vChunks") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Chunks)) :*: (S1 ('MetaSel ('Just "_vRel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Release)) :*: S1 ('MetaSel ('Just "_vMeta") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))))

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 _-+:

Some Mess values have a shape that is tantalizingly close to a SemVer. Example: 1.6.0a+2014+m872b87e73dfb-1. For values like these, we can extract the semver-compatible values out with messMajor, etc.

Not guaranteed to have well-defined ordering (Ord) behaviour, but so far internal tests show consistency. messMajor, etc., are used internally where appropriate to enhance accuracy.

Constructors

Mess !(NonEmpty MChunk) !(Maybe (VSep, Mess)) 

Instances

Instances details
Data Mess Source # 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Mess -> c Mess

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Mess

toConstr :: Mess -> Constr

dataTypeOf :: Mess -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Mess)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mess)

gmapT :: (forall b. Data b => b -> b) -> Mess -> Mess

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mess -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mess -> r

gmapQ :: (forall d. Data d => d -> u) -> Mess -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Mess -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Mess -> m Mess

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Mess -> m Mess

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Mess -> m Mess

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

Show Mess Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> Mess -> ShowS

show :: Mess -> String

showList :: [Mess] -> ShowS

NFData Mess Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: Mess -> ()

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

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

Lift Mess Source # 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => Mess -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => Mess -> Code m Mess

type Rep Mess Source # 
Instance details

Defined in Data.Versions

type Rep Mess = D1 ('MetaData "Mess" "Data.Versions" "versions-6.0.3-F3PyfH85ZwcBZVNAPGE3uF" 'False) (C1 ('MetaCons "Mess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty MChunk)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (VSep, Mess)))))

messMajor :: Mess -> Maybe Word Source #

Try to extract the "major" version number from Mess, as if it were a SemVer.

messMinor :: Mess -> Maybe Word Source #

Try to extract the "minor" version number from Mess, as if it were a SemVer.

messPatch :: Mess -> Maybe Word Source #

Try to extract the "patch" version number from Mess, as if it were a SemVer.

messPatchChunk :: Mess -> Maybe Chunk Source #

Okay, fine, say messPatch couldn't find a nice value. But some Messes have a "proper" patch-plus-release-candidate value in their patch position, which is parsable as a Chunk.

Example: 1.6.0a+2014+m872b87e73dfb-1 We should be able to extract 0a safely.

newtype Release Source #

Chunks have comparison behaviour according to SemVer's rules for preleases.

Constructors

Release (NonEmpty Chunk) 

Instances

Instances details
Data Release Source # 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Release -> c Release

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Release

toConstr :: Release -> Constr

dataTypeOf :: Release -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Release)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Release)

gmapT :: (forall b. Data b => b -> b) -> Release -> Release

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Release -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Release -> r

gmapQ :: (forall d. Data d => d -> u) -> Release -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Release -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Release -> m Release

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Release -> m Release

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Release -> m Release

Generic Release Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep Release :: Type -> Type

Methods

from :: Release -> Rep Release x

to :: Rep Release x -> Release

Read Release Source # 
Instance details

Defined in Data.Versions

Methods

readsPrec :: Int -> ReadS Release

readList :: ReadS [Release]

readPrec :: ReadPrec Release

readListPrec :: ReadPrec [Release]

Show Release Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> Release -> ShowS

show :: Release -> String

showList :: [Release] -> ShowS

NFData Release Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: Release -> ()

Eq Release Source # 
Instance details

Defined in Data.Versions

Methods

(==) :: Release -> Release -> Bool

(/=) :: Release -> Release -> Bool

Ord Release Source # 
Instance details

Defined in Data.Versions

Methods

compare :: Release -> Release -> Ordering

(<) :: Release -> Release -> Bool

(<=) :: Release -> Release -> Bool

(>) :: Release -> Release -> Bool

(>=) :: Release -> Release -> Bool

max :: Release -> Release -> Release

min :: Release -> Release -> Release

Hashable Release Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> Release -> Int

hash :: Release -> Int

Lift Release Source # 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => Release -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => Release -> Code m Release

type Rep Release Source # 
Instance details

Defined in Data.Versions

type Rep Release = D1 ('MetaData "Release" "Data.Versions" "versions-6.0.3-F3PyfH85ZwcBZVNAPGE3uF" 'True) (C1 ('MetaCons "Release" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Chunk))))

newtype Chunks Source #

Chunks that have a comparison behaviour specific to Version.

Constructors

Chunks (NonEmpty Chunk) 

Instances

Instances details
Data Chunks Source # 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Chunks -> c Chunks

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Chunks

toConstr :: Chunks -> Constr

dataTypeOf :: Chunks -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Chunks)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Chunks)

gmapT :: (forall b. Data b => b -> b) -> Chunks -> Chunks

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Chunks -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Chunks -> r

gmapQ :: (forall d. Data d => d -> u) -> Chunks -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Chunks -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Chunks -> m Chunks

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Chunks -> m Chunks

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Chunks -> m Chunks

Generic Chunks Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep Chunks :: Type -> Type

Methods

from :: Chunks -> Rep Chunks x

to :: Rep Chunks x -> Chunks

Show Chunks Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> Chunks -> ShowS

show :: Chunks -> String

showList :: [Chunks] -> ShowS

NFData Chunks Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: Chunks -> ()

Eq Chunks Source # 
Instance details

Defined in Data.Versions

Methods

(==) :: Chunks -> Chunks -> Bool

(/=) :: Chunks -> Chunks -> Bool

Ord Chunks Source # 
Instance details

Defined in Data.Versions

Methods

compare :: Chunks -> Chunks -> Ordering

(<) :: Chunks -> Chunks -> Bool

(<=) :: Chunks -> Chunks -> Bool

(>) :: Chunks -> Chunks -> Bool

(>=) :: Chunks -> Chunks -> Bool

max :: Chunks -> Chunks -> Chunks

min :: Chunks -> Chunks -> Chunks

Hashable Chunks Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> Chunks -> Int

hash :: Chunks -> Int

Lift Chunks Source # 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => Chunks -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => Chunks -> Code m Chunks

type Rep Chunks Source # 
Instance details

Defined in Data.Versions

type Rep Chunks = D1 ('MetaData "Chunks" "Data.Versions" "versions-6.0.3-F3PyfH85ZwcBZVNAPGE3uF" 'True) (C1 ('MetaCons "Chunks" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Chunk))))

data Chunk Source #

A logical unit of a version number.

Either entirely numerical (with no leading zeroes) or entirely alphanumerical (with a free mixture of numbers, letters, and hyphens.)

Groups of these (like Release) are separated by periods to form a full section of a version number.

Examples:

1
20150826
r3
0rc1-abc3

Constructors

Numeric Word 
Alphanum Text 

Instances

Instances details
Data Chunk Source # 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Chunk -> c Chunk

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Chunk

toConstr :: Chunk -> Constr

dataTypeOf :: Chunk -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Chunk)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Chunk)

gmapT :: (forall b. Data b => b -> b) -> Chunk -> Chunk

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Chunk -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Chunk -> r

gmapQ :: (forall d. Data d => d -> u) -> Chunk -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Chunk -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Chunk -> m Chunk

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Chunk -> m Chunk

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Chunk -> m Chunk

Generic Chunk Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep Chunk :: Type -> Type

Methods

from :: Chunk -> Rep Chunk x

to :: Rep Chunk x -> Chunk

Read Chunk Source # 
Instance details

Defined in Data.Versions

Methods

readsPrec :: Int -> ReadS Chunk

readList :: ReadS [Chunk]

readPrec :: ReadPrec Chunk

readListPrec :: ReadPrec [Chunk]

Show Chunk Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> Chunk -> ShowS

show :: Chunk -> String

showList :: [Chunk] -> ShowS

NFData Chunk Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: Chunk -> ()

Eq Chunk Source # 
Instance details

Defined in Data.Versions

Methods

(==) :: Chunk -> Chunk -> Bool

(/=) :: Chunk -> Chunk -> Bool

Hashable Chunk Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> Chunk -> Int

hash :: Chunk -> Int

Lift Chunk Source # 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => Chunk -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => Chunk -> Code m Chunk

type Rep Chunk Source # 
Instance details

Defined in Data.Versions

type Rep Chunk = D1 ('MetaData "Chunk" "Data.Versions" "versions-6.0.3-F3PyfH85ZwcBZVNAPGE3uF" 'False) (C1 ('MetaCons "Numeric" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)) :+: C1 ('MetaCons "Alphanum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data MChunk Source #

Possible values of a section of a Mess. A numeric value is extracted if it could be, alongside the original text it came from. This preserves both Ord and pretty-print behaviour for versions like 1.003.0.

Constructors

MDigit Word Text

A nice numeric value.

MRev Word Text

A numeric value preceeded by an r, indicating a revision.

MPlain Text

Anything else.

Instances

Instances details
Data MChunk Source # 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MChunk -> c MChunk

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MChunk

toConstr :: MChunk -> Constr

dataTypeOf :: MChunk -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MChunk)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MChunk)

gmapT :: (forall b. Data b => b -> b) -> MChunk -> MChunk

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MChunk -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MChunk -> r

gmapQ :: (forall d. Data d => d -> u) -> MChunk -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> MChunk -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MChunk -> m MChunk

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MChunk -> m MChunk

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MChunk -> m MChunk

Generic MChunk Source # 
Instance details

Defined in Data.Versions

Associated Types

type Rep MChunk :: Type -> Type

Methods

from :: MChunk -> Rep MChunk x

to :: Rep MChunk x -> MChunk

Show MChunk Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> MChunk -> ShowS

show :: MChunk -> String

showList :: [MChunk] -> ShowS

NFData MChunk Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: MChunk -> ()

Eq MChunk Source # 
Instance details

Defined in Data.Versions

Methods

(==) :: MChunk -> MChunk -> Bool

(/=) :: MChunk -> MChunk -> Bool

Ord MChunk Source # 
Instance details

Defined in Data.Versions

Methods

compare :: MChunk -> MChunk -> Ordering

(<) :: MChunk -> MChunk -> Bool

(<=) :: MChunk -> MChunk -> Bool

(>) :: MChunk -> MChunk -> Bool

(>=) :: MChunk -> MChunk -> Bool

max :: MChunk -> MChunk -> MChunk

min :: MChunk -> MChunk -> MChunk

Hashable MChunk Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> MChunk -> Int

hash :: MChunk -> Int

Lift MChunk Source # 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => MChunk -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => MChunk -> Code m MChunk

type Rep MChunk Source # 
Instance details

Defined in Data.Versions

type Rep MChunk = D1 ('MetaData "MChunk" "Data.Versions" "versions-6.0.3-F3PyfH85ZwcBZVNAPGE3uF" 'False) (C1 ('MetaCons "MDigit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "MRev" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "MPlain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

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 tilde (~). Example: 12.0.0-3ubuntu1~20.04.5
  • 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 
VTilde 

Instances

Instances details
Data VSep Source # 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VSep -> c VSep

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VSep

toConstr :: VSep -> Constr

dataTypeOf :: VSep -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VSep)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VSep)

gmapT :: (forall b. Data b => b -> b) -> VSep -> VSep

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VSep -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VSep -> r

gmapQ :: (forall d. Data d => d -> u) -> VSep -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> VSep -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VSep -> m VSep

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VSep -> m VSep

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VSep -> m VSep

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

Show VSep Source # 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> VSep -> ShowS

show :: VSep -> String

showList :: [VSep] -> ShowS

NFData VSep Source # 
Instance details

Defined in Data.Versions

Methods

rnf :: VSep -> ()

Eq VSep Source # 
Instance details

Defined in Data.Versions

Methods

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

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

Hashable VSep Source # 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> VSep -> Int

hash :: VSep -> Int

Lift VSep Source # 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => VSep -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => VSep -> Code m VSep

type Rep VSep Source # 
Instance details

Defined in Data.Versions

type Rep VSep = D1 ('MetaData "VSep" "Data.Versions" "versions-6.0.3-F3PyfH85ZwcBZVNAPGE3uF" '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) :+: C1 ('MetaCons "VTilde" 'PrefixI 'False) (U1 :: Type -> Type))))

Compile-time Constructors

versioningQ :: Text -> Q Exp Source #

Parse a Versioning at compile time.

semverQ :: Text -> Q Exp Source #

Parse a SemVer at compile time.

versionQ :: Text -> Q Exp Source #

Parse a Version at compile time.

messQ :: Text -> Q Exp Source #

Parse a Mess at compile time.

pvpQ :: Text -> Q Exp Source #

Parse a PVP at compile time.

Conversions

versionToPvp :: Version -> Maybe PVP Source #

Convert a Version to a PVP. Fails if there is an epoch present, but otherwise ignores the Release and other metadata. Naturally it also fails if any of the version components contain any non-digits.

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.

pvp :: Text -> Either ParsingError PVP Source #

Parse a (Haskell) PVP, as defined above.

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.

pvp' :: Parsec Void Text PVP Source #

Internal megaparsec parser of pvp.

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.

prettyPVP :: PVP -> Text Source #

Convert a PVP 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 :: (VisualStream s, TraversableStream s, ShowErrorComponent e) => ParseErrorBundle s e -> String #

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 (Maybe Release) Source #

major.minor.patch-PREREL+meta

meta :: Traversal' v (Maybe Text) Source #

major.minor.patch-prerel+META

semantic :: Traversal' v SemVer Source #

A Natural Transformation into an proper SemVer.

Instances

Instances details
Semantic Text Source # 
Instance details

Defined in Data.Versions

Methods

major :: Traversal' Text Word Source #

minor :: Traversal' Text Word Source #

patch :: Traversal' Text Word Source #

release :: Traversal' Text (Maybe Release) Source #

meta :: Traversal' Text (Maybe Text) Source #

semantic :: Traversal' Text SemVer Source #

Semantic Mess Source # 
Instance details

Defined in Data.Versions

Semantic PVP Source # 
Instance details

Defined in Data.Versions

Semantic SemVer Source # 
Instance details

Defined in Data.Versions

Semantic Version 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

_Complex :: Traversal' Versioning Mess Source #

Possibly extract a Mess from a Versioning.

(General) Version Lenses

epoch :: Lens' Version (Maybe Word) Source #

A Version's inner epoch Word.