Copyright | (c) Colin Woodbury 2015 - 2023 |
---|---|
License | BSD3 |
Maintainer | Colin Woodbury <colin@fosskers.ca> |
Safe Haskell | Safe-Inferred |
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.
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
- data Versioning
- isIdeal :: Versioning -> Bool
- isGeneral :: Versioning -> Bool
- isComplex :: Versioning -> Bool
- data SemVer = SemVer {}
- newtype PVP = PVP {}
- data Version = Version {}
- data Mess = Mess !(NonEmpty MChunk) !(Maybe (VSep, Mess))
- messMajor :: Mess -> Maybe Word
- messMinor :: Mess -> Maybe Word
- messPatch :: Mess -> Maybe Word
- messPatchChunk :: Mess -> Maybe Chunk
- newtype Release = Release (NonEmpty Chunk)
- newtype Chunks = Chunks (NonEmpty Chunk)
- data Chunk
- data MChunk
- data VSep
- versioningQ :: Text -> Q Exp
- semverQ :: Text -> Q Exp
- versionQ :: Text -> Q Exp
- messQ :: Text -> Q Exp
- pvpQ :: Text -> Q Exp
- semverToVersion :: SemVer -> Version
- versionToMess :: Version -> Mess
- versionToPvp :: Version -> Maybe PVP
- type ParsingError = ParseErrorBundle Text Void
- versioning :: Text -> Either ParsingError Versioning
- semver :: Text -> Either ParsingError SemVer
- pvp :: Text -> Either ParsingError PVP
- version :: Text -> Either ParsingError Version
- mess :: Text -> Either ParsingError Mess
- versioning' :: Parsec Void Text Versioning
- semver' :: Parsec Void Text SemVer
- pvp' :: Parsec Void Text PVP
- version' :: Parsec Void Text Version
- mess' :: Parsec Void Text Mess
- prettyV :: Versioning -> Text
- prettySemVer :: SemVer -> Text
- prettyPVP :: PVP -> Text
- prettyVer :: Version -> Text
- prettyMess :: Mess -> Text
- errorBundlePretty :: (VisualStream s, TraversableStream 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
- major :: Traversal' v Word
- minor :: Traversal' v Word
- patch :: Traversal' v Word
- release :: Traversal' v (Maybe Release)
- meta :: Traversal' v (Maybe Text)
- semantic :: Traversal' v SemVer
- _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)
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
Data Versioning Source # | |
Defined in Data.Versions 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 # | |
Defined in Data.Versions type Rep Versioning :: Type -> Type # from :: Versioning -> Rep Versioning x # to :: Rep Versioning x -> Versioning # | |
Show Versioning Source # | |
Defined in Data.Versions showsPrec :: Int -> Versioning -> ShowS # show :: Versioning -> String # showList :: [Versioning] -> ShowS # | |
NFData Versioning Source # | |
Defined in Data.Versions rnf :: Versioning -> () # | |
Eq Versioning Source # | |
Defined in Data.Versions (==) :: Versioning -> Versioning -> Bool # (/=) :: Versioning -> Versioning -> Bool # | |
Ord Versioning Source # | Comparison of If comparison of If comparison of |
Defined in Data.Versions compare :: Versioning -> Versioning -> Ordering # (<) :: Versioning -> Versioning -> Bool # (<=) :: Versioning -> Versioning -> Bool # (>) :: Versioning -> Versioning -> Bool # (>=) :: Versioning -> Versioning -> Bool # max :: Versioning -> Versioning -> Versioning # min :: Versioning -> Versioning -> Versioning # | |
Hashable Versioning Source # | |
Defined in Data.Versions hashWithSalt :: Int -> Versioning -> Int # hash :: Versioning -> Int # | |
Semantic Versioning Source # | |
Defined in Data.Versions | |
Lift Versioning Source # | |
Defined in Data.Versions lift :: Quote m => Versioning -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => Versioning -> Code m Versioning # | |
type Rep Versioning Source # | |
Defined in Data.Versions type Rep Versioning = D1 ('MetaData "Versioning" "Data.Versions" "versions-6.0.7-IQcjoSNMP80AvixmucM8GG" 'False) (C1 ('MetaCons "Ideal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SemVer)) :+: (C1 ('MetaCons "General" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version)) :+: C1 ('MetaCons "Complex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Mess)))) |
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 and hyphens.
For more information, see http://semver.org
Instances
Data SemVer Source # | |
Defined in Data.Versions 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 # | |
Show SemVer Source # | |
NFData SemVer Source # | |
Defined in Data.Versions | |
Eq SemVer Source # | Two SemVers are equal if all fields except metadata are equal. |
Ord SemVer Source # | Build metadata does not affect version precedence. |
Hashable SemVer Source # | |
Defined in Data.Versions | |
Semantic SemVer Source # | |
Lift SemVer Source # | |
type Rep SemVer Source # | |
Defined in Data.Versions type Rep SemVer = D1 ('MetaData "SemVer" "Data.Versions" "versions-6.0.7-IQcjoSNMP80AvixmucM8GG" '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)))))) |
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:
- Each component must be a number.
- 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. - 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.
Instances
Data PVP Source # | |
Defined in Data.Versions 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 # 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 # | |
Show PVP Source # | |
NFData PVP Source # | |
Defined in Data.Versions | |
Eq PVP Source # | |
Ord PVP Source # | |
Hashable PVP Source # | |
Defined in Data.Versions | |
Semantic PVP Source # | |
Lift PVP Source # | |
type Rep PVP Source # | |
Defined in Data.Versions |
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 Version
s 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
Instances
Data Version Source # | |
Defined in Data.Versions 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 # | |
Show Version Source # | |
NFData Version Source # | |
Defined in Data.Versions | |
Eq Version Source # | |
Ord Version Source # | Customized. As in SemVer, metadata is ignored for the purpose of comparison. |
Hashable Version Source # | |
Defined in Data.Versions | |
Semantic Version Source # | |
Lift Version Source # | |
type Rep Version Source # | |
Defined in Data.Versions type Rep Version = D1 ('MetaData "Version" "Data.Versions" "versions-6.0.7-IQcjoSNMP80AvixmucM8GG" '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))))) |
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.
Instances
Data Mess Source # | |
Defined in Data.Versions 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 # 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 # | |
Show Mess Source # | |
NFData Mess Source # | |
Defined in Data.Versions | |
Eq Mess Source # | |
Ord Mess Source # | |
Hashable Mess Source # | |
Defined in Data.Versions | |
Semantic Mess Source # | |
Lift Mess Source # | |
type Rep Mess Source # | |
Defined in Data.Versions type Rep Mess = D1 ('MetaData "Mess" "Data.Versions" "versions-6.0.7-IQcjoSNMP80AvixmucM8GG" '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))))) |
Chunk
s have comparison behaviour according to SemVer's rules for preleases.
Instances
Data Release Source # | |
Defined in Data.Versions 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 # | |
Read Release Source # | |
Show Release Source # | |
NFData Release Source # | |
Defined in Data.Versions | |
Eq Release Source # | |
Ord Release Source # | |
Hashable Release Source # | |
Defined in Data.Versions | |
Lift Release Source # | |
type Rep Release Source # | |
Instances
Data Chunks Source # | |
Defined in Data.Versions 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 # | |
Show Chunks Source # | |
NFData Chunks Source # | |
Defined in Data.Versions | |
Eq Chunks Source # | |
Ord Chunks Source # | |
Hashable Chunks Source # | |
Defined in Data.Versions | |
Lift Chunks Source # | |
type Rep Chunks 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
Instances
Data Chunk Source # | |
Defined in Data.Versions 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 # 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 # | |
Read Chunk Source # | |
Show Chunk Source # | |
NFData Chunk Source # | |
Defined in Data.Versions | |
Eq Chunk Source # | |
Hashable Chunk Source # | |
Defined in Data.Versions | |
Lift Chunk Source # | |
type Rep Chunk Source # | |
Defined in Data.Versions type Rep Chunk = D1 ('MetaData "Chunk" "Data.Versions" "versions-6.0.7-IQcjoSNMP80AvixmucM8GG" 'False) (C1 ('MetaCons "Numeric" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :+: C1 ('MetaCons "Alphanum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |
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
.
MDigit !Word !Text | A nice numeric value. |
MRev !Word !Text | A numeric value preceeded by an |
MPlain !Text | Anything else. |
Instances
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.
Instances
Data VSep Source # | |
Defined in Data.Versions 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 # 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 # | |
Show VSep Source # | |
NFData VSep Source # | |
Defined in Data.Versions | |
Eq VSep Source # | |
Hashable VSep Source # | |
Defined in Data.Versions | |
Lift VSep Source # | |
type Rep VSep Source # | |
Defined in Data.Versions type Rep VSep = D1 ('MetaData "VSep" "Data.Versions" "versions-6.0.7-IQcjoSNMP80AvixmucM8GG" '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.
Conversions
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.
:: (VisualStream s, TraversableStream 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 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 (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
.
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"
Versioning Traversals
_Ideal :: Traversal' Versioning SemVer Source #
Possibly extract a SemVer
from a Versioning
.
_General :: Traversal' Versioning Version Source #
Possibly extract a Version
from a Versioning
.
_Complex :: Traversal' Versioning Mess Source #
Possibly extract a Mess
from a Versioning
.