semver-range-0.2.2: An implementation of semver and semantic version ranges.

Safe HaskellNone
LanguageHaskell2010

Data.SemVer

Synopsis

Documentation

data PrereleaseTag Source #

Prerelease tags can either be numbers or text.

Constructors

IntTag Int 
TextTag Text 

newtype PrereleaseTags Source #

Instances

IsList PrereleaseTags Source # 
Eq PrereleaseTags Source # 
Ord PrereleaseTags Source # 
Show PrereleaseTags Source # 
Generic PrereleaseTags Source # 

Associated Types

type Rep PrereleaseTags :: * -> * #

Monoid PrereleaseTags Source # 
Hashable PrereleaseTags Source # 
type Rep PrereleaseTags Source # 
type Rep PrereleaseTags = D1 (MetaData "PrereleaseTags" "Data.SemVer.Types" "semver-range-0.2.2-JAfQZFaJx5YELPyjHOdwy1" True) (C1 (MetaCons "PrereleaseTags" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PrereleaseTag])))
type Item PrereleaseTags Source # 

data SemVer Source #

A SemVer has major, minor and patch versions, and zero or more pre-release version tags.

Instances

Eq SemVer Source # 

Methods

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

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

Ord SemVer Source #

Define an Ord instance which ignores the buildMetaData.

Show SemVer Source # 
Generic SemVer Source # 

Associated Types

type Rep SemVer :: * -> * #

Methods

from :: SemVer -> Rep SemVer x #

to :: Rep SemVer x -> SemVer #

Hashable SemVer Source # 

Methods

hashWithSalt :: Int -> SemVer -> Int #

hash :: SemVer -> Int #

type Rep SemVer Source # 

data SemVerRange Source #

A range specifies bounds on a semver.

Constructors

Eq SemVer infixl 4

Exact equality

Gt SemVer infixl 4

Greater than

Lt SemVer infixl 4

Less than

Geq SemVer infixl 4

Greater than or equal to

Leq SemVer infixl 4

Less than or equal to

And SemVerRange SemVerRange infixl 3

Conjunction

Or SemVerRange SemVerRange infixl 3

Disjunction

versionsOf :: SemVerRange -> [SemVer] Source #

Pull all of the concrete versions out of a range.

semver :: Int -> Int -> Int -> SemVer Source #

Create a SemVer with no version tags.

semver' :: Int -> Int -> Int -> PrereleaseTags -> SemVer Source #

Create a SemVer with tags

semver'' :: Int -> Int -> Int -> PrereleaseTags -> BuildMetaData -> SemVer Source #

Create a SemVer with tags and metadata.

toTuple :: SemVer -> (Int, Int, Int) Source #

Get only the version tuple from a semver.

tuplesOf :: SemVerRange -> [(Int, Int, Int)] Source #

Get a list of tuples from a version range.

rangePrereleaseTags :: SemVerRange -> PrereleaseTags Source #

Get all of the prerelease tags from a version range.

sharedTags :: SemVerRange -> Maybe PrereleaseTags Source #

Get the range prerelease tags if they're all the same; otherwise Nothing.

anyVersion :: SemVerRange Source #

Satisfies any version.

renderSV :: SemVer -> Text Source #

Render a semver as Text.

matches :: SemVerRange -> SemVer -> Bool infixl 2 Source #

Returns whether a given semantic version matches a range. Note that there are special cases when there are prerelease tags. For details see https://github.com/npm/node-semver#prerelease-tags. matches :: SemVerRange -> SemVer -> Bool matches range version = case (sharedTags range, svTags version) of -- This is the simple case, where neither the range nor the version has given -- prerelease tags. Then we can just do regular predicate calculus. (Nothing, PrereleaseTags []) -> matchesSimple range version _ -> undefined -- (Just rTags, PrereleaseTags vTags) -- | rTags == vTags -> matchesSimple range version -- | tuplesOf range /= [toTuple version] -> False -- | otherwise -> matchesTags range rTags vTags -- (_, _) -> False

Simple predicate calculus matching, doing AND and OR combination with numerical comparison.

matchesTags :: SemVerRange -> [PrereleaseTag] -> [PrereleaseTag] -> Bool Source #

Given a range and two sets of tags, the first being a bound on the second, uses the range to compare the tags and see if they match.

bestMatch :: SemVerRange -> [SemVer] -> Either String SemVer Source #

Gets the highest-matching semver in a range.

data Wildcard Source #

A partially specified semantic version. Implicitly defines a range of acceptable versions, as seen in wildcardToRange.

Constructors

Any 
One Int 
Two Int Int 
Full SemVer 

wildcardToSemver :: Wildcard -> SemVer Source #

Fills in zeros in a wildcard.

wildcardToRange :: Wildcard -> SemVerRange Source #

Translates a wildcard (partially specified version) to a range. Ex: 2 := >=2.0.0 <3.0.0 Ex: 1.2.x := 1.2 := >=1.2.0 <1.3.0

tildeToRange :: Wildcard -> SemVerRange Source #

Translates a ~wildcard to a range. Ex: ~1.2.3 := >=1.2.3 :==1.2.3 <1.3.0

caratToRange :: Wildcard -> SemVerRange Source #

Translates a ^wildcard to a range. Ex: ^1.2.x := >=1.2.0 <2.0.0

hyphenatedRange :: Wildcard -> Wildcard -> SemVerRange Source #

Translates two hyphenated wildcards to an actual range. Ex: 1.2.3 - 2.3.4 := >=1.2.3 <=2.3.4 Ex: 1.2 - 2.3.4 := >=1.2.0 <=2.3.4 Ex: 1.2.3 - 2 := >=1.2.3 <3.0.0

parse :: Parser a -> Text -> Either ParseError a Source #

Given a parser and a string, attempts to parse the string.

spaces :: Parser String Source #

Consumes any spaces (not other whitespace).

spaces1 :: Parser String Source #

Consumes at least one space (not other whitespace).

sstring :: String -> Parser String Source #

Parses the given string and any trailing spaces.

schar :: Char -> Parser Char Source #

Parses the given character and any trailing spaces.

lexeme :: Parser a -> Parser a Source #

Parses p and any trailing spaces.

pInt :: Parser Int Source #

Parses an integer.

pInt' :: Parser Int Source #

Parses an integer without consuming trailing spaces.

parseSemVerRange :: Text -> Either ParseError SemVerRange Source #

Parse a string as a version range, or return an error.

parseSemVer :: Text -> Either ParseError SemVer Source #

Parse a string as an explicit version, or return an error.

pSemVer :: Parser SemVer Source #

Parses a semantic version.

cmp :: Parser String Source #

Parses a comparison operator.

pSemVerRangeSingle :: Parser SemVerRange Source #

Parses versions with an explicit range qualifier (gt, lt, etc).

pJoinedSemVerRange :: Parser SemVerRange Source #

Parses semantic version ranges joined with Ands and Ors.

pHyphen :: Parser SemVerRange Source #

Parses a hyphenated range.

pWildCard :: Parser Wildcard Source #

Parses a "wildcard" (which is a possibly partial semantic version).

pTildeRange :: Parser SemVerRange Source #

Parses a tilde range (~1.2.3).

pCaratRange :: Parser SemVerRange Source #

Parses a carat range (^1.2.3).

pSemVerRange :: Parser SemVerRange Source #

Top-level parser. Parses a semantic version range.

fromHaskellVersion :: Version -> Either Text SemVer Source #

Parse a semver from a haskell version. There must be exactly three numbers in the versionBranch field.

matchText :: Text -> Text -> Either Text Bool Source #

Parses the first argument as a range and the second argument as a semver, and returns whether they match.