{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Salve.Internal
( Version (..),
PreRelease (..),
Build (..),
Constraint (..),
makeVersion,
initialVersion,
parseVersion,
parsePreRelease,
parseBuild,
parseConstraint,
unsafeParseVersion,
unsafeParsePreRelease,
unsafeParseBuild,
unsafeParseConstraint,
renderVersion,
renderPreRelease,
renderBuild,
renderConstraint,
isUnstable,
isStable,
fromBaseVersion,
toBaseVersion,
bumpMajor,
bumpMinor,
bumpPatch,
satisfiesConstraint,
majorLens,
minorLens,
patchLens,
preReleasesLens,
buildsLens,
Operator (..),
Wildcard (..),
constraintLT,
constraintLE,
constraintEQ,
constraintGE,
constraintGT,
constraintAnd,
constraintOr,
constraintHyphen,
constraintTilde,
constraintCaret,
)
where
import qualified Control.Monad as Monad
import qualified Data.Char as Char
import qualified Data.Data as Data
import qualified Data.List as List
import qualified Data.Maybe as Maybe
import qualified Data.Monoid as Monoid
import qualified Data.Ord as Ord
import qualified Data.Version as Version
import qualified Data.Word as Word
import qualified GHC.Generics as Generics
import qualified Text.ParserCombinators.ReadP as ReadP
data Version = Version
{ Version -> Word64
versionMajor :: Word.Word64,
Version -> Word64
versionMinor :: Word.Word64,
Version -> Word64
versionPatch :: Word.Word64,
Version -> [PreRelease]
versionPreReleases :: [PreRelease],
Version -> [Build]
versionBuilds :: [Build]
}
deriving (Typeable Version
Typeable Version =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Version -> c Version)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Version)
-> (Version -> Constr)
-> (Version -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Version))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version))
-> ((forall b. Data b => b -> b) -> Version -> Version)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Version -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Version -> r)
-> (forall u. (forall d. Data d => d -> u) -> Version -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Version -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Version -> m Version)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Version -> m Version)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Version -> m Version)
-> Data Version
Version -> Constr
Version -> DataType
(forall b. Data b => b -> b) -> Version -> Version
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Version -> u
forall u. (forall d. Data d => d -> u) -> Version -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Version -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Version -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Version -> m Version
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Version -> m Version
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Version
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Version -> c Version
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Version)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Version -> c Version
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Version -> c Version
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Version
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Version
$ctoConstr :: Version -> Constr
toConstr :: Version -> Constr
$cdataTypeOf :: Version -> DataType
dataTypeOf :: Version -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Version)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Version)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version)
$cgmapT :: (forall b. Data b => b -> b) -> Version -> Version
gmapT :: (forall b. Data b => b -> b) -> Version -> Version
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Version -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Version -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Version -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Version -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Version -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Version -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Version -> m Version
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Version -> m Version
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Version -> m Version
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Version -> m Version
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Version -> m Version
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Version -> m Version
Data.Data, Version -> Version -> Bool
(Version -> Version -> Bool)
-> (Version -> Version -> Bool) -> Eq Version
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Version -> Version -> Bool
== :: Version -> Version -> Bool
$c/= :: Version -> Version -> Bool
/= :: Version -> Version -> Bool
Eq, (forall x. Version -> Rep Version x)
-> (forall x. Rep Version x -> Version) -> Generic Version
forall x. Rep Version x -> Version
forall x. Version -> Rep Version x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Version -> Rep Version x
from :: forall x. Version -> Rep Version x
$cto :: forall x. Rep Version x -> Version
to :: forall x. Rep Version x -> Version
Generics.Generic, ReadPrec [Version]
ReadPrec Version
Int -> ReadS Version
ReadS [Version]
(Int -> ReadS Version)
-> ReadS [Version]
-> ReadPrec Version
-> ReadPrec [Version]
-> Read Version
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Version
readsPrec :: Int -> ReadS Version
$creadList :: ReadS [Version]
readList :: ReadS [Version]
$creadPrec :: ReadPrec Version
readPrec :: ReadPrec Version
$creadListPrec :: ReadPrec [Version]
readListPrec :: ReadPrec [Version]
Read, Int -> Version -> ShowS
[Version] -> ShowS
Version -> String
(Int -> Version -> ShowS)
-> (Version -> String) -> ([Version] -> ShowS) -> Show Version
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Version -> ShowS
showsPrec :: Int -> Version -> ShowS
$cshow :: Version -> String
show :: Version -> String
$cshowList :: [Version] -> ShowS
showList :: [Version] -> ShowS
Show)
instance Ord Version where
compare :: Version -> Version -> Ordering
compare Version
x Version
y =
[Ordering] -> Ordering
forall a. Monoid a => [a] -> a
Monoid.mconcat
[ (Version -> Word64) -> Version -> Version -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
Ord.comparing Version -> Word64
versionMajor Version
x Version
y,
(Version -> Word64) -> Version -> Version -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
Ord.comparing Version -> Word64
versionMinor Version
x Version
y,
(Version -> Word64) -> Version -> Version -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
Ord.comparing Version -> Word64
versionPatch Version
x Version
y,
case (Version -> [PreRelease])
-> (Version, Version) -> ([PreRelease], [PreRelease])
forall a b. (a -> b) -> (a, a) -> (b, b)
both Version -> [PreRelease]
versionPreReleases (Version
x, Version
y) of
([], []) -> Ordering
EQ
([], [PreRelease]
_) -> Ordering
GT
([PreRelease]
_, []) -> Ordering
LT
([PreRelease]
p, [PreRelease]
q) -> [PreRelease] -> [PreRelease] -> Ordering
forall a. Ord a => a -> a -> Ordering
compare [PreRelease]
p [PreRelease]
q
]
data PreRelease
= PreReleaseNumeric Word.Word64
| PreReleaseTextual String
deriving (Typeable PreRelease
Typeable PreRelease =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PreRelease -> c PreRelease)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PreRelease)
-> (PreRelease -> Constr)
-> (PreRelease -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PreRelease))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PreRelease))
-> ((forall b. Data b => b -> b) -> PreRelease -> PreRelease)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PreRelease -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PreRelease -> r)
-> (forall u. (forall d. Data d => d -> u) -> PreRelease -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PreRelease -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease)
-> Data PreRelease
PreRelease -> Constr
PreRelease -> DataType
(forall b. Data b => b -> b) -> PreRelease -> PreRelease
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PreRelease -> u
forall u. (forall d. Data d => d -> u) -> PreRelease -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PreRelease -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PreRelease -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PreRelease
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PreRelease -> c PreRelease
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PreRelease)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PreRelease)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PreRelease -> c PreRelease
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PreRelease -> c PreRelease
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PreRelease
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PreRelease
$ctoConstr :: PreRelease -> Constr
toConstr :: PreRelease -> Constr
$cdataTypeOf :: PreRelease -> DataType
dataTypeOf :: PreRelease -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PreRelease)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PreRelease)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PreRelease)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PreRelease)
$cgmapT :: (forall b. Data b => b -> b) -> PreRelease -> PreRelease
gmapT :: (forall b. Data b => b -> b) -> PreRelease -> PreRelease
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PreRelease -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PreRelease -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PreRelease -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PreRelease -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PreRelease -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> PreRelease -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PreRelease -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PreRelease -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PreRelease -> m PreRelease
Data.Data, PreRelease -> PreRelease -> Bool
(PreRelease -> PreRelease -> Bool)
-> (PreRelease -> PreRelease -> Bool) -> Eq PreRelease
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PreRelease -> PreRelease -> Bool
== :: PreRelease -> PreRelease -> Bool
$c/= :: PreRelease -> PreRelease -> Bool
/= :: PreRelease -> PreRelease -> Bool
Eq, (forall x. PreRelease -> Rep PreRelease x)
-> (forall x. Rep PreRelease x -> PreRelease) -> Generic PreRelease
forall x. Rep PreRelease x -> PreRelease
forall x. PreRelease -> Rep PreRelease x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PreRelease -> Rep PreRelease x
from :: forall x. PreRelease -> Rep PreRelease x
$cto :: forall x. Rep PreRelease x -> PreRelease
to :: forall x. Rep PreRelease x -> PreRelease
Generics.Generic, ReadPrec [PreRelease]
ReadPrec PreRelease
Int -> ReadS PreRelease
ReadS [PreRelease]
(Int -> ReadS PreRelease)
-> ReadS [PreRelease]
-> ReadPrec PreRelease
-> ReadPrec [PreRelease]
-> Read PreRelease
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PreRelease
readsPrec :: Int -> ReadS PreRelease
$creadList :: ReadS [PreRelease]
readList :: ReadS [PreRelease]
$creadPrec :: ReadPrec PreRelease
readPrec :: ReadPrec PreRelease
$creadListPrec :: ReadPrec [PreRelease]
readListPrec :: ReadPrec [PreRelease]
Read, Int -> PreRelease -> ShowS
[PreRelease] -> ShowS
PreRelease -> String
(Int -> PreRelease -> ShowS)
-> (PreRelease -> String)
-> ([PreRelease] -> ShowS)
-> Show PreRelease
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PreRelease -> ShowS
showsPrec :: Int -> PreRelease -> ShowS
$cshow :: PreRelease -> String
show :: PreRelease -> String
$cshowList :: [PreRelease] -> ShowS
showList :: [PreRelease] -> ShowS
Show)
instance Ord PreRelease where
compare :: PreRelease -> PreRelease -> Ordering
compare PreRelease
x PreRelease
y = case (PreRelease
x, PreRelease
y) of
(PreReleaseNumeric Word64
n, PreReleaseNumeric Word64
m) -> Word64 -> Word64 -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Word64
n Word64
m
(PreReleaseNumeric Word64
_, PreReleaseTextual String
_) -> Ordering
LT
(PreReleaseTextual String
_, PreReleaseNumeric Word64
_) -> Ordering
GT
(PreReleaseTextual String
s, PreReleaseTextual String
t) -> String -> String -> Ordering
forall a. Ord a => a -> a -> Ordering
compare String
s String
t
newtype Build = Build String
deriving (Typeable Build
Typeable Build =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Build -> c Build)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Build)
-> (Build -> Constr)
-> (Build -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Build))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Build))
-> ((forall b. Data b => b -> b) -> Build -> Build)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Build -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Build -> r)
-> (forall u. (forall d. Data d => d -> u) -> Build -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Build -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Build -> m Build)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Build -> m Build)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Build -> m Build)
-> Data Build
Build -> Constr
Build -> DataType
(forall b. Data b => b -> b) -> Build -> Build
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Build -> u
forall u. (forall d. Data d => d -> u) -> Build -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Build -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Build -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Build -> m Build
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Build -> m Build
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Build
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Build -> c Build
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Build)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Build)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Build -> c Build
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Build -> c Build
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Build
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Build
$ctoConstr :: Build -> Constr
toConstr :: Build -> Constr
$cdataTypeOf :: Build -> DataType
dataTypeOf :: Build -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Build)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Build)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Build)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Build)
$cgmapT :: (forall b. Data b => b -> b) -> Build -> Build
gmapT :: (forall b. Data b => b -> b) -> Build -> Build
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Build -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Build -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Build -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Build -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Build -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Build -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Build -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Build -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Build -> m Build
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Build -> m Build
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Build -> m Build
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Build -> m Build
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Build -> m Build
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Build -> m Build
Data.Data, Build -> Build -> Bool
(Build -> Build -> Bool) -> (Build -> Build -> Bool) -> Eq Build
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Build -> Build -> Bool
== :: Build -> Build -> Bool
$c/= :: Build -> Build -> Bool
/= :: Build -> Build -> Bool
Eq, (forall x. Build -> Rep Build x)
-> (forall x. Rep Build x -> Build) -> Generic Build
forall x. Rep Build x -> Build
forall x. Build -> Rep Build x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Build -> Rep Build x
from :: forall x. Build -> Rep Build x
$cto :: forall x. Rep Build x -> Build
to :: forall x. Rep Build x -> Build
Generics.Generic, ReadPrec [Build]
ReadPrec Build
Int -> ReadS Build
ReadS [Build]
(Int -> ReadS Build)
-> ReadS [Build]
-> ReadPrec Build
-> ReadPrec [Build]
-> Read Build
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Build
readsPrec :: Int -> ReadS Build
$creadList :: ReadS [Build]
readList :: ReadS [Build]
$creadPrec :: ReadPrec Build
readPrec :: ReadPrec Build
$creadListPrec :: ReadPrec [Build]
readListPrec :: ReadPrec [Build]
Read, Int -> Build -> ShowS
[Build] -> ShowS
Build -> String
(Int -> Build -> ShowS)
-> (Build -> String) -> ([Build] -> ShowS) -> Show Build
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Build -> ShowS
showsPrec :: Int -> Build -> ShowS
$cshow :: Build -> String
show :: Build -> String
$cshowList :: [Build] -> ShowS
showList :: [Build] -> ShowS
Show)
data Constraint
= ConstraintOperator Operator Version
| ConstraintHyphen Version Version
| ConstraintWildcard Wildcard
| ConstraintAnd Constraint Constraint
| ConstraintOr Constraint Constraint
deriving (Typeable Constraint
Typeable Constraint =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Constraint -> c Constraint)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Constraint)
-> (Constraint -> Constr)
-> (Constraint -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Constraint))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Constraint))
-> ((forall b. Data b => b -> b) -> Constraint -> Constraint)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Constraint -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Constraint -> r)
-> (forall u. (forall d. Data d => d -> u) -> Constraint -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Constraint -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint)
-> Data Constraint
Constraint -> Constr
Constraint -> DataType
(forall b. Data b => b -> b) -> Constraint -> Constraint
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Constraint -> u
forall u. (forall d. Data d => d -> u) -> Constraint -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Constraint -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Constraint -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Constraint
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Constraint -> c Constraint
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Constraint)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Constraint)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Constraint -> c Constraint
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Constraint -> c Constraint
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Constraint
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Constraint
$ctoConstr :: Constraint -> Constr
toConstr :: Constraint -> Constr
$cdataTypeOf :: Constraint -> DataType
dataTypeOf :: Constraint -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Constraint)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Constraint)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Constraint)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Constraint)
$cgmapT :: (forall b. Data b => b -> b) -> Constraint -> Constraint
gmapT :: (forall b. Data b => b -> b) -> Constraint -> Constraint
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Constraint -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Constraint -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Constraint -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Constraint -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Constraint -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Constraint -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Constraint -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Constraint -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Constraint -> m Constraint
Data.Data, Constraint -> Constraint -> Bool
(Constraint -> Constraint -> Bool)
-> (Constraint -> Constraint -> Bool) -> Eq Constraint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Constraint -> Constraint -> Bool
== :: Constraint -> Constraint -> Bool
$c/= :: Constraint -> Constraint -> Bool
/= :: Constraint -> Constraint -> Bool
Eq, (forall x. Constraint -> Rep Constraint x)
-> (forall x. Rep Constraint x -> Constraint) -> Generic Constraint
forall x. Rep Constraint x -> Constraint
forall x. Constraint -> Rep Constraint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Constraint -> Rep Constraint x
from :: forall x. Constraint -> Rep Constraint x
$cto :: forall x. Rep Constraint x -> Constraint
to :: forall x. Rep Constraint x -> Constraint
Generics.Generic, Eq Constraint
Eq Constraint =>
(Constraint -> Constraint -> Ordering)
-> (Constraint -> Constraint -> Bool)
-> (Constraint -> Constraint -> Bool)
-> (Constraint -> Constraint -> Bool)
-> (Constraint -> Constraint -> Bool)
-> (Constraint -> Constraint -> Constraint)
-> (Constraint -> Constraint -> Constraint)
-> Ord Constraint
Constraint -> Constraint -> Bool
Constraint -> Constraint -> Ordering
Constraint -> Constraint -> Constraint
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Constraint -> Constraint -> Ordering
compare :: Constraint -> Constraint -> Ordering
$c< :: Constraint -> Constraint -> Bool
< :: Constraint -> Constraint -> Bool
$c<= :: Constraint -> Constraint -> Bool
<= :: Constraint -> Constraint -> Bool
$c> :: Constraint -> Constraint -> Bool
> :: Constraint -> Constraint -> Bool
$c>= :: Constraint -> Constraint -> Bool
>= :: Constraint -> Constraint -> Bool
$cmax :: Constraint -> Constraint -> Constraint
max :: Constraint -> Constraint -> Constraint
$cmin :: Constraint -> Constraint -> Constraint
min :: Constraint -> Constraint -> Constraint
Ord, ReadPrec [Constraint]
ReadPrec Constraint
Int -> ReadS Constraint
ReadS [Constraint]
(Int -> ReadS Constraint)
-> ReadS [Constraint]
-> ReadPrec Constraint
-> ReadPrec [Constraint]
-> Read Constraint
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Constraint
readsPrec :: Int -> ReadS Constraint
$creadList :: ReadS [Constraint]
readList :: ReadS [Constraint]
$creadPrec :: ReadPrec Constraint
readPrec :: ReadPrec Constraint
$creadListPrec :: ReadPrec [Constraint]
readListPrec :: ReadPrec [Constraint]
Read, Int -> Constraint -> ShowS
[Constraint] -> ShowS
Constraint -> String
(Int -> Constraint -> ShowS)
-> (Constraint -> String)
-> ([Constraint] -> ShowS)
-> Show Constraint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Constraint -> ShowS
showsPrec :: Int -> Constraint -> ShowS
$cshow :: Constraint -> String
show :: Constraint -> String
$cshowList :: [Constraint] -> ShowS
showList :: [Constraint] -> ShowS
Show)
makeVersion ::
Word.Word64 ->
Word.Word64 ->
Word.Word64 ->
[PreRelease] ->
[Build] ->
Version
makeVersion :: Word64 -> Word64 -> Word64 -> [PreRelease] -> [Build] -> Version
makeVersion Word64
major Word64
minor Word64
patch [PreRelease]
preReleases [Build]
builds =
Version
{ versionMajor :: Word64
versionMajor = Word64
major,
versionMinor :: Word64
versionMinor = Word64
minor,
versionPatch :: Word64
versionPatch = Word64
patch,
versionPreReleases :: [PreRelease]
versionPreReleases = [PreRelease]
preReleases,
versionBuilds :: [Build]
versionBuilds = [Build]
builds
}
initialVersion :: Version
initialVersion :: Version
initialVersion = Word64 -> Word64 -> Word64 -> [PreRelease] -> [Build] -> Version
makeVersion Word64
0 Word64
0 Word64
0 [] []
parseVersion :: String -> Maybe Version
parseVersion :: String -> Maybe Version
parseVersion =
ReadP Version -> String -> Maybe Version
forall a. ReadP a -> String -> Maybe a
parse
( do
ReadP ()
ReadP.skipSpaces
Version
version <- ReadP Version
versionP
ReadP ()
ReadP.skipSpaces
Version -> ReadP Version
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Version
version
)
parsePreRelease :: String -> Maybe PreRelease
parsePreRelease :: String -> Maybe PreRelease
parsePreRelease = ReadP PreRelease -> String -> Maybe PreRelease
forall a. ReadP a -> String -> Maybe a
parse ReadP PreRelease
preReleaseP
parseBuild :: String -> Maybe Build
parseBuild :: String -> Maybe Build
parseBuild = ReadP Build -> String -> Maybe Build
forall a. ReadP a -> String -> Maybe a
parse ReadP Build
buildP
parseConstraint :: String -> Maybe Constraint
parseConstraint :: String -> Maybe Constraint
parseConstraint = ReadP Constraint -> String -> Maybe Constraint
forall a. ReadP a -> String -> Maybe a
parse ReadP Constraint
constraintsP
unsafeParseVersion :: String -> Version
unsafeParseVersion :: String -> Version
unsafeParseVersion String
s = case String -> Maybe Version
parseVersion String
s of
Maybe Version
Nothing -> String -> Version
forall a. HasCallStack => String -> a
error (String
"unsafeParseVersion: invalid version: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> String
show String
s)
Just Version
v -> Version
v
unsafeParsePreRelease :: String -> PreRelease
unsafeParsePreRelease :: String -> PreRelease
unsafeParsePreRelease String
s = case String -> Maybe PreRelease
parsePreRelease String
s of
Maybe PreRelease
Nothing -> String -> PreRelease
forall a. HasCallStack => String -> a
error (String
"unsafeParsePreRelease: invalid pre-release: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> String
show String
s)
Just PreRelease
p -> PreRelease
p
unsafeParseBuild :: String -> Build
unsafeParseBuild :: String -> Build
unsafeParseBuild String
s = case String -> Maybe Build
parseBuild String
s of
Maybe Build
Nothing -> String -> Build
forall a. HasCallStack => String -> a
error (String
"unsafeParseBuild: invalid build: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> String
show String
s)
Just Build
b -> Build
b
unsafeParseConstraint :: String -> Constraint
unsafeParseConstraint :: String -> Constraint
unsafeParseConstraint String
s = case String -> Maybe Constraint
parseConstraint String
s of
Maybe Constraint
Nothing -> String -> Constraint
forall a. HasCallStack => String -> a
error (String
"unsafeParseConstraint: invalid constraint: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. Show a => a -> String
show String
s)
Just Constraint
c -> Constraint
c
renderVersion :: Version -> String
renderVersion :: Version -> String
renderVersion Version
v =
[String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Word64 -> String
forall a. Show a => a -> String
show (Version -> Word64
versionMajor Version
v),
String
".",
Word64 -> String
forall a. Show a => a -> String
show (Version -> Word64
versionMinor Version
v),
String
".",
Word64 -> String
forall a. Show a => a -> String
show (Version -> Word64
versionPatch Version
v),
[PreRelease] -> String
renderPreReleases (Version -> [PreRelease]
versionPreReleases Version
v),
[Build] -> String
renderBuilds (Version -> [Build]
versionBuilds Version
v)
]
renderPreRelease :: PreRelease -> String
renderPreRelease :: PreRelease -> String
renderPreRelease PreRelease
p = case PreRelease
p of
PreReleaseNumeric Word64
n -> Word64 -> String
forall a. Show a => a -> String
show Word64
n
PreReleaseTextual String
s -> String
s
renderBuild :: Build -> String
renderBuild :: Build -> String
renderBuild (Build String
b) = String
b
renderConstraint :: Constraint -> String
renderConstraint :: Constraint -> String
renderConstraint Constraint
c = case Constraint
c of
ConstraintOperator Operator
o Version
v ->
let s :: String
s = Version -> String
renderVersion Version
v
in case Operator
o of
Operator
OperatorLT -> Char
'<' Char -> ShowS
forall a. a -> [a] -> [a]
: String
s
Operator
OperatorLE -> Char
'<' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
'=' Char -> ShowS
forall a. a -> [a] -> [a]
: String
s
Operator
OperatorEQ -> String
s
Operator
OperatorGE -> Char
'>' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
'=' Char -> ShowS
forall a. a -> [a] -> [a]
: String
s
Operator
OperatorGT -> Char
'>' Char -> ShowS
forall a. a -> [a] -> [a]
: String
s
Operator
OperatorTilde -> Char
'~' Char -> ShowS
forall a. a -> [a] -> [a]
: String
s
Operator
OperatorCaret -> Char
'^' Char -> ShowS
forall a. a -> [a] -> [a]
: String
s
ConstraintHyphen Version
l Version
r -> [String] -> String
unwords [Version -> String
renderVersion Version
l, String
"-", Version -> String
renderVersion Version
r]
ConstraintWildcard Wildcard
w -> case Wildcard
w of
Wildcard
WildcardMajor -> String
"x.x.x"
WildcardMinor Word64
m -> Word64 -> String
forall a. Show a => a -> String
show Word64
m String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
".x.x"
WildcardPatch Word64
m Word64
n -> String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
List.intercalate String
"." [Word64 -> String
forall a. Show a => a -> String
show Word64
m, Word64 -> String
forall a. Show a => a -> String
show Word64
n, String
"x"]
ConstraintAnd Constraint
l Constraint
r -> [String] -> String
unwords ((Constraint -> String) -> [Constraint] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Constraint -> String
renderConstraint [Constraint
l, Constraint
r])
ConstraintOr Constraint
l Constraint
r -> [String] -> String
unwords [Constraint -> String
renderConstraint Constraint
l, String
"||", Constraint -> String
renderConstraint Constraint
r]
isUnstable :: Version -> Bool
isUnstable :: Version -> Bool
isUnstable Version
v = Version -> Word64
versionMajor Version
v Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== Word64
0
isStable :: Version -> Bool
isStable :: Version -> Bool
isStable Version
v = Bool -> Bool
not (Version -> Bool
isUnstable Version
v)
fromBaseVersion :: Version.Version -> Version
fromBaseVersion :: Version -> Version
fromBaseVersion Version
v = case Version -> [Int]
Version.versionBranch Version
v of
(Int
m : Int
n : Int
p : [Int]
_) -> Word64 -> Word64 -> Word64 -> Version
mkV (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m) (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
p)
(Int
m : Int
n : [Int]
_) -> Word64 -> Word64 -> Word64 -> Version
mkV (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m) (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) Word64
0
(Int
m : [Int]
_) -> Word64 -> Word64 -> Word64 -> Version
mkV (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m) Word64
0 Word64
0
[Int]
_ -> Word64 -> Word64 -> Word64 -> Version
mkV Word64
0 Word64
0 Word64
0
toBaseVersion :: Version -> Version.Version
toBaseVersion :: Version -> Version
toBaseVersion Version
v =
[Int] -> [String] -> Version
Version.Version
((Word64 -> Int) -> [Word64] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Version -> Word64
versionMajor Version
v, Version -> Word64
versionMinor Version
v, Version -> Word64
versionPatch Version
v])
( [[String]] -> [String]
forall a. Monoid a => [a] -> a
mconcat
[ (PreRelease -> String) -> [PreRelease] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PreRelease -> String
renderPreRelease (Version -> [PreRelease]
versionPreReleases Version
v),
(Build -> String) -> [Build] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Build -> String
renderBuild (Version -> [Build]
versionBuilds Version
v)
]
)
bumpMajor :: Version -> Version
bumpMajor :: Version -> Version
bumpMajor Version
v = Word64 -> Word64 -> Word64 -> [PreRelease] -> [Build] -> Version
makeVersion (Version -> Word64
versionMajor Version
v Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) Word64
0 Word64
0 [] []
bumpMinor :: Version -> Version
bumpMinor :: Version -> Version
bumpMinor Version
v = Word64 -> Word64 -> Word64 -> [PreRelease] -> [Build] -> Version
makeVersion (Version -> Word64
versionMajor Version
v) (Version -> Word64
versionMinor Version
v Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) Word64
0 [] []
bumpPatch :: Version -> Version
bumpPatch :: Version -> Version
bumpPatch Version
v =
Word64 -> Word64 -> Word64 -> [PreRelease] -> [Build] -> Version
makeVersion (Version -> Word64
versionMajor Version
v) (Version -> Word64
versionMinor Version
v) (Version -> Word64
versionPatch Version
v Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) [] []
satisfiesConstraint :: Constraint -> Version -> Bool
satisfiesConstraint :: Constraint -> Version -> Bool
satisfiesConstraint Constraint
c = SimpleConstraint -> Version -> Bool
satisfiesSC (Constraint -> SimpleConstraint
toSC Constraint
c)
majorLens ::
(Functor f) => (Word.Word64 -> f Word.Word64) -> Version -> f Version
majorLens :: forall (f :: * -> *).
Functor f =>
(Word64 -> f Word64) -> Version -> f Version
majorLens Word64 -> f Word64
f Version
v = (Word64 -> Version) -> f Word64 -> f Version
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Word64
m -> Version
v {versionMajor = m}) (Word64 -> f Word64
f (Version -> Word64
versionMajor Version
v))
minorLens ::
(Functor f) => (Word.Word64 -> f Word.Word64) -> Version -> f Version
minorLens :: forall (f :: * -> *).
Functor f =>
(Word64 -> f Word64) -> Version -> f Version
minorLens Word64 -> f Word64
f Version
v = (Word64 -> Version) -> f Word64 -> f Version
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Word64
n -> Version
v {versionMinor = n}) (Word64 -> f Word64
f (Version -> Word64
versionMinor Version
v))
patchLens ::
(Functor f) => (Word.Word64 -> f Word.Word64) -> Version -> f Version
patchLens :: forall (f :: * -> *).
Functor f =>
(Word64 -> f Word64) -> Version -> f Version
patchLens Word64 -> f Word64
f Version
v = (Word64 -> Version) -> f Word64 -> f Version
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Word64
p -> Version
v {versionPatch = p}) (Word64 -> f Word64
f (Version -> Word64
versionPatch Version
v))
preReleasesLens ::
(Functor f) => ([PreRelease] -> f [PreRelease]) -> Version -> f Version
preReleasesLens :: forall (f :: * -> *).
Functor f =>
([PreRelease] -> f [PreRelease]) -> Version -> f Version
preReleasesLens [PreRelease] -> f [PreRelease]
f Version
v =
([PreRelease] -> Version) -> f [PreRelease] -> f Version
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[PreRelease]
ps -> Version
v {versionPreReleases = ps}) ([PreRelease] -> f [PreRelease]
f (Version -> [PreRelease]
versionPreReleases Version
v))
buildsLens :: (Functor f) => ([Build] -> f [Build]) -> Version -> f Version
buildsLens :: forall (f :: * -> *).
Functor f =>
([Build] -> f [Build]) -> Version -> f Version
buildsLens [Build] -> f [Build]
f Version
v = ([Build] -> Version) -> f [Build] -> f Version
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[Build]
bs -> Version
v {versionBuilds = bs}) ([Build] -> f [Build]
f (Version -> [Build]
versionBuilds Version
v))
data Operator
= OperatorLT
| OperatorLE
| OperatorEQ
| OperatorGE
| OperatorGT
| OperatorTilde
| OperatorCaret
deriving (Typeable Operator
Typeable Operator =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operator -> c Operator)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operator)
-> (Operator -> Constr)
-> (Operator -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Operator))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operator))
-> ((forall b. Data b => b -> b) -> Operator -> Operator)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Operator -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Operator -> r)
-> (forall u. (forall d. Data d => d -> u) -> Operator -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Operator -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator)
-> Data Operator
Operator -> Constr
Operator -> DataType
(forall b. Data b => b -> b) -> Operator -> Operator
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Operator -> u
forall u. (forall d. Data d => d -> u) -> Operator -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Operator -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Operator -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operator
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operator -> c Operator
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Operator)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operator)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operator -> c Operator
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Operator -> c Operator
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operator
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Operator
$ctoConstr :: Operator -> Constr
toConstr :: Operator -> Constr
$cdataTypeOf :: Operator -> DataType
dataTypeOf :: Operator -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Operator)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Operator)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operator)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Operator)
$cgmapT :: (forall b. Data b => b -> b) -> Operator -> Operator
gmapT :: (forall b. Data b => b -> b) -> Operator -> Operator
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Operator -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Operator -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Operator -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Operator -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Operator -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Operator -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Operator -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Operator -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Operator -> m Operator
Data.Data, Operator -> Operator -> Bool
(Operator -> Operator -> Bool)
-> (Operator -> Operator -> Bool) -> Eq Operator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Operator -> Operator -> Bool
== :: Operator -> Operator -> Bool
$c/= :: Operator -> Operator -> Bool
/= :: Operator -> Operator -> Bool
Eq, (forall x. Operator -> Rep Operator x)
-> (forall x. Rep Operator x -> Operator) -> Generic Operator
forall x. Rep Operator x -> Operator
forall x. Operator -> Rep Operator x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Operator -> Rep Operator x
from :: forall x. Operator -> Rep Operator x
$cto :: forall x. Rep Operator x -> Operator
to :: forall x. Rep Operator x -> Operator
Generics.Generic, Eq Operator
Eq Operator =>
(Operator -> Operator -> Ordering)
-> (Operator -> Operator -> Bool)
-> (Operator -> Operator -> Bool)
-> (Operator -> Operator -> Bool)
-> (Operator -> Operator -> Bool)
-> (Operator -> Operator -> Operator)
-> (Operator -> Operator -> Operator)
-> Ord Operator
Operator -> Operator -> Bool
Operator -> Operator -> Ordering
Operator -> Operator -> Operator
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Operator -> Operator -> Ordering
compare :: Operator -> Operator -> Ordering
$c< :: Operator -> Operator -> Bool
< :: Operator -> Operator -> Bool
$c<= :: Operator -> Operator -> Bool
<= :: Operator -> Operator -> Bool
$c> :: Operator -> Operator -> Bool
> :: Operator -> Operator -> Bool
$c>= :: Operator -> Operator -> Bool
>= :: Operator -> Operator -> Bool
$cmax :: Operator -> Operator -> Operator
max :: Operator -> Operator -> Operator
$cmin :: Operator -> Operator -> Operator
min :: Operator -> Operator -> Operator
Ord, ReadPrec [Operator]
ReadPrec Operator
Int -> ReadS Operator
ReadS [Operator]
(Int -> ReadS Operator)
-> ReadS [Operator]
-> ReadPrec Operator
-> ReadPrec [Operator]
-> Read Operator
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Operator
readsPrec :: Int -> ReadS Operator
$creadList :: ReadS [Operator]
readList :: ReadS [Operator]
$creadPrec :: ReadPrec Operator
readPrec :: ReadPrec Operator
$creadListPrec :: ReadPrec [Operator]
readListPrec :: ReadPrec [Operator]
Read, Int -> Operator -> ShowS
[Operator] -> ShowS
Operator -> String
(Int -> Operator -> ShowS)
-> (Operator -> String) -> ([Operator] -> ShowS) -> Show Operator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Operator -> ShowS
showsPrec :: Int -> Operator -> ShowS
$cshow :: Operator -> String
show :: Operator -> String
$cshowList :: [Operator] -> ShowS
showList :: [Operator] -> ShowS
Show)
data Wildcard
= WildcardMajor
| WildcardMinor Word.Word64
| WildcardPatch Word.Word64 Word.Word64
deriving (Typeable Wildcard
Typeable Wildcard =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Wildcard -> c Wildcard)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Wildcard)
-> (Wildcard -> Constr)
-> (Wildcard -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Wildcard))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Wildcard))
-> ((forall b. Data b => b -> b) -> Wildcard -> Wildcard)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Wildcard -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Wildcard -> r)
-> (forall u. (forall d. Data d => d -> u) -> Wildcard -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Wildcard -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard)
-> Data Wildcard
Wildcard -> Constr
Wildcard -> DataType
(forall b. Data b => b -> b) -> Wildcard -> Wildcard
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Wildcard -> u
forall u. (forall d. Data d => d -> u) -> Wildcard -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Wildcard -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Wildcard -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Wildcard
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Wildcard -> c Wildcard
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Wildcard)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Wildcard)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Wildcard -> c Wildcard
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Wildcard -> c Wildcard
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Wildcard
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Wildcard
$ctoConstr :: Wildcard -> Constr
toConstr :: Wildcard -> Constr
$cdataTypeOf :: Wildcard -> DataType
dataTypeOf :: Wildcard -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Wildcard)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Wildcard)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Wildcard)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Wildcard)
$cgmapT :: (forall b. Data b => b -> b) -> Wildcard -> Wildcard
gmapT :: (forall b. Data b => b -> b) -> Wildcard -> Wildcard
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Wildcard -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Wildcard -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Wildcard -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Wildcard -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Wildcard -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Wildcard -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Wildcard -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Wildcard -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Wildcard -> m Wildcard
Data.Data, Wildcard -> Wildcard -> Bool
(Wildcard -> Wildcard -> Bool)
-> (Wildcard -> Wildcard -> Bool) -> Eq Wildcard
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Wildcard -> Wildcard -> Bool
== :: Wildcard -> Wildcard -> Bool
$c/= :: Wildcard -> Wildcard -> Bool
/= :: Wildcard -> Wildcard -> Bool
Eq, (forall x. Wildcard -> Rep Wildcard x)
-> (forall x. Rep Wildcard x -> Wildcard) -> Generic Wildcard
forall x. Rep Wildcard x -> Wildcard
forall x. Wildcard -> Rep Wildcard x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Wildcard -> Rep Wildcard x
from :: forall x. Wildcard -> Rep Wildcard x
$cto :: forall x. Rep Wildcard x -> Wildcard
to :: forall x. Rep Wildcard x -> Wildcard
Generics.Generic, Eq Wildcard
Eq Wildcard =>
(Wildcard -> Wildcard -> Ordering)
-> (Wildcard -> Wildcard -> Bool)
-> (Wildcard -> Wildcard -> Bool)
-> (Wildcard -> Wildcard -> Bool)
-> (Wildcard -> Wildcard -> Bool)
-> (Wildcard -> Wildcard -> Wildcard)
-> (Wildcard -> Wildcard -> Wildcard)
-> Ord Wildcard
Wildcard -> Wildcard -> Bool
Wildcard -> Wildcard -> Ordering
Wildcard -> Wildcard -> Wildcard
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Wildcard -> Wildcard -> Ordering
compare :: Wildcard -> Wildcard -> Ordering
$c< :: Wildcard -> Wildcard -> Bool
< :: Wildcard -> Wildcard -> Bool
$c<= :: Wildcard -> Wildcard -> Bool
<= :: Wildcard -> Wildcard -> Bool
$c> :: Wildcard -> Wildcard -> Bool
> :: Wildcard -> Wildcard -> Bool
$c>= :: Wildcard -> Wildcard -> Bool
>= :: Wildcard -> Wildcard -> Bool
$cmax :: Wildcard -> Wildcard -> Wildcard
max :: Wildcard -> Wildcard -> Wildcard
$cmin :: Wildcard -> Wildcard -> Wildcard
min :: Wildcard -> Wildcard -> Wildcard
Ord, ReadPrec [Wildcard]
ReadPrec Wildcard
Int -> ReadS Wildcard
ReadS [Wildcard]
(Int -> ReadS Wildcard)
-> ReadS [Wildcard]
-> ReadPrec Wildcard
-> ReadPrec [Wildcard]
-> Read Wildcard
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Wildcard
readsPrec :: Int -> ReadS Wildcard
$creadList :: ReadS [Wildcard]
readList :: ReadS [Wildcard]
$creadPrec :: ReadPrec Wildcard
readPrec :: ReadPrec Wildcard
$creadListPrec :: ReadPrec [Wildcard]
readListPrec :: ReadPrec [Wildcard]
Read, Int -> Wildcard -> ShowS
[Wildcard] -> ShowS
Wildcard -> String
(Int -> Wildcard -> ShowS)
-> (Wildcard -> String) -> ([Wildcard] -> ShowS) -> Show Wildcard
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Wildcard -> ShowS
showsPrec :: Int -> Wildcard -> ShowS
$cshow :: Wildcard -> String
show :: Wildcard -> String
$cshowList :: [Wildcard] -> ShowS
showList :: [Wildcard] -> ShowS
Show)
constraintLT :: Version -> Constraint
constraintLT :: Version -> Constraint
constraintLT = Operator -> Version -> Constraint
ConstraintOperator Operator
OperatorLT
constraintLE :: Version -> Constraint
constraintLE :: Version -> Constraint
constraintLE = Operator -> Version -> Constraint
ConstraintOperator Operator
OperatorLE
constraintEQ :: Version -> Constraint
constraintEQ :: Version -> Constraint
constraintEQ = Operator -> Version -> Constraint
ConstraintOperator Operator
OperatorEQ
constraintGE :: Version -> Constraint
constraintGE :: Version -> Constraint
constraintGE = Operator -> Version -> Constraint
ConstraintOperator Operator
OperatorGE
constraintGT :: Version -> Constraint
constraintGT :: Version -> Constraint
constraintGT = Operator -> Version -> Constraint
ConstraintOperator Operator
OperatorGT
constraintAnd :: Constraint -> Constraint -> Constraint
constraintAnd :: Constraint -> Constraint -> Constraint
constraintAnd = Constraint -> Constraint -> Constraint
ConstraintAnd
constraintOr :: Constraint -> Constraint -> Constraint
constraintOr :: Constraint -> Constraint -> Constraint
constraintOr = Constraint -> Constraint -> Constraint
ConstraintOr
constraintHyphen :: Version -> Version -> Constraint
constraintHyphen :: Version -> Version -> Constraint
constraintHyphen = Version -> Version -> Constraint
ConstraintHyphen
constraintTilde :: Version -> Constraint
constraintTilde :: Version -> Constraint
constraintTilde = Operator -> Version -> Constraint
ConstraintOperator Operator
OperatorTilde
constraintCaret :: Version -> Constraint
constraintCaret :: Version -> Constraint
constraintCaret = Operator -> Version -> Constraint
ConstraintOperator Operator
OperatorCaret
versionP :: ReadP.ReadP Version
versionP :: ReadP Version
versionP = do
Word64
major <- ReadP Word64
numberP
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'.')
Word64
minor <- ReadP Word64
numberP
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'.')
Word64
patch <- ReadP Word64
numberP
[PreRelease]
preReleases <- ReadP [PreRelease]
preReleasesP
Word64 -> Word64 -> Word64 -> [PreRelease] -> [Build] -> Version
makeVersion Word64
major Word64
minor Word64
patch [PreRelease]
preReleases ([Build] -> Version) -> ReadP [Build] -> ReadP Version
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadP [Build]
buildsP
preReleasesP :: ReadP.ReadP [PreRelease]
preReleasesP :: ReadP [PreRelease]
preReleasesP =
[PreRelease] -> ReadP [PreRelease] -> ReadP [PreRelease]
forall a. a -> ReadP a -> ReadP a
ReadP.option
[]
( do
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'-')
ReadP PreRelease -> ReadP Char -> ReadP [PreRelease]
forall a sep. ReadP a -> ReadP sep -> ReadP [a]
ReadP.sepBy1 ReadP PreRelease
preReleaseP (Char -> ReadP Char
ReadP.char Char
'.')
)
preReleaseP :: ReadP.ReadP PreRelease
preReleaseP :: ReadP PreRelease
preReleaseP = ReadP PreRelease
preReleaseNumberP ReadP PreRelease -> ReadP PreRelease -> ReadP PreRelease
forall a. ReadP a -> ReadP a -> ReadP a
ReadP.<++ ReadP PreRelease
preReleaseStringP
preReleaseNumberP :: ReadP.ReadP PreRelease
preReleaseNumberP :: ReadP PreRelease
preReleaseNumberP = Word64 -> PreRelease
PreReleaseNumeric (Word64 -> PreRelease) -> ReadP Word64 -> ReadP PreRelease
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadP Word64
numberP
preReleaseStringP :: ReadP.ReadP PreRelease
preReleaseStringP :: ReadP PreRelease
preReleaseStringP = do
String
s <- (Char -> Bool) -> ReadP String
ReadP.munch1 Char -> Bool
isIdentifier
if (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
Char.isDigit String
s then ReadP PreRelease
forall a. ReadP a
ReadP.pfail else PreRelease -> ReadP PreRelease
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> PreRelease
PreReleaseTextual String
s)
buildsP :: ReadP.ReadP [Build]
buildsP :: ReadP [Build]
buildsP =
[Build] -> ReadP [Build] -> ReadP [Build]
forall a. a -> ReadP a -> ReadP a
ReadP.option
[]
( do
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'+')
ReadP Build -> ReadP Char -> ReadP [Build]
forall a sep. ReadP a -> ReadP sep -> ReadP [a]
ReadP.sepBy1 ReadP Build
buildP (Char -> ReadP Char
ReadP.char Char
'.')
)
buildP :: ReadP.ReadP Build
buildP :: ReadP Build
buildP = do
String
b <- (Char -> Bool) -> ReadP String
ReadP.munch1 Char -> Bool
isIdentifier
Build -> ReadP Build
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> Build
Build String
b)
numberP :: ReadP.ReadP Word.Word64
numberP :: ReadP Word64
numberP = ReadP Word64
zeroP ReadP Word64 -> ReadP Word64 -> ReadP Word64
forall a. ReadP a -> ReadP a -> ReadP a
ReadP.<++ ReadP Word64
nonZeroP
zeroP :: ReadP.ReadP Word.Word64
zeroP :: ReadP Word64
zeroP = do
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'0')
Word64 -> ReadP Word64
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Word64
0
nonZeroP :: ReadP.ReadP Word.Word64
nonZeroP :: ReadP Word64
nonZeroP = do
Char
x <- (Char -> Bool) -> ReadP Char
ReadP.satisfy Char -> Bool
isAsciiDigitNonZero
String
ys <- (Char -> Bool) -> ReadP String
ReadP.munch Char -> Bool
Char.isDigit
ReadP Word64
-> (Word64 -> ReadP Word64) -> Maybe Word64 -> ReadP Word64
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ReadP Word64
forall a. ReadP a
ReadP.pfail Word64 -> ReadP Word64
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Word64 -> ReadP Word64)
-> (String -> Maybe Word64) -> String -> ReadP Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Maybe Word64
toWord64 (Integer -> Maybe Word64)
-> (String -> Integer) -> String -> Maybe Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Integer
forall a. Integral a => String -> a
stringToIntegral (String -> ReadP Word64) -> String -> ReadP Word64
forall a b. (a -> b) -> a -> b
$ Char
x Char -> ShowS
forall a. a -> [a] -> [a]
: String
ys
constraintsP :: ReadP.ReadP Constraint
constraintsP :: ReadP Constraint
constraintsP = do
ReadP ()
spacesP
[Constraint]
cs <- ReadP Constraint -> ReadP () -> ReadP [Constraint]
forall a sep. ReadP a -> ReadP sep -> ReadP [a]
ReadP.sepBy1 ReadP Constraint
constraintP ReadP ()
orP
ReadP ()
spacesP
Constraint -> ReadP Constraint
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Constraint -> Constraint -> Constraint)
-> [Constraint] -> Constraint
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 Constraint -> Constraint -> Constraint
constraintOr [Constraint]
cs)
constraintP :: ReadP.ReadP Constraint
constraintP :: ReadP Constraint
constraintP = do
[Constraint]
cs <- ReadP Constraint -> ReadP () -> ReadP [Constraint]
forall a sep. ReadP a -> ReadP sep -> ReadP [a]
ReadP.sepBy1 ReadP Constraint
simpleP ReadP ()
spaces1P
Constraint -> ReadP Constraint
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Constraint -> Constraint -> Constraint)
-> [Constraint] -> Constraint
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 Constraint -> Constraint -> Constraint
constraintAnd [Constraint]
cs)
hyphenatedP :: ReadP.ReadP Constraint
hyphenatedP :: ReadP Constraint
hyphenatedP = do
Version
v <- ReadP Version
versionP
ReadP ()
hyphenP
Version -> Version -> Constraint
constraintHyphen Version
v (Version -> Constraint) -> ReadP Version -> ReadP Constraint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadP Version
versionP
simpleP :: ReadP.ReadP Constraint
simpleP :: ReadP Constraint
simpleP = [ReadP Constraint] -> ReadP Constraint
forall a. [ReadP a] -> ReadP a
ReadP.choice [ReadP Constraint
hyphenatedP, ReadP Constraint
wildcardConstraintP, ReadP Constraint
primitiveP]
wildcardConstraintP :: ReadP.ReadP Constraint
wildcardConstraintP :: ReadP Constraint
wildcardConstraintP = do
ReadP Char -> ReadP ()
forall a. ReadP a -> ReadP ()
ReadP.optional (Char -> ReadP Char
ReadP.char Char
'=')
Wildcard -> Constraint
ConstraintWildcard (Wildcard -> Constraint) -> ReadP Wildcard -> ReadP Constraint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadP Wildcard
wildcardP
wildcardP :: ReadP.ReadP Wildcard
wildcardP :: ReadP Wildcard
wildcardP = [ReadP Wildcard] -> ReadP Wildcard
forall a. [ReadP a] -> ReadP a
ReadP.choice [ReadP Wildcard
wildcardPatchP, ReadP Wildcard
wildcardMinorP, ReadP Wildcard
wildcardMajorP]
wildcardPatchP :: ReadP.ReadP Wildcard
wildcardPatchP :: ReadP Wildcard
wildcardPatchP = do
Word64
m <- ReadP Word64
numberP
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'.')
Word64
n <- ReadP Word64
numberP
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'.')
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void ((Char -> Bool) -> ReadP Char
ReadP.satisfy Char -> Bool
isWildcard)
Wildcard -> ReadP Wildcard
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word64 -> Word64 -> Wildcard
WildcardPatch Word64
m Word64
n)
wildcardMinorP :: ReadP.ReadP Wildcard
wildcardMinorP :: ReadP Wildcard
wildcardMinorP = do
Word64
m <- ReadP Word64
numberP
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'.')
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void ((Char -> Bool) -> ReadP Char
ReadP.satisfy Char -> Bool
isWildcard)
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'.')
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void ((Char -> Bool) -> ReadP Char
ReadP.satisfy Char -> Bool
isWildcard)
Wildcard -> ReadP Wildcard
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word64 -> Wildcard
WildcardMinor Word64
m)
wildcardMajorP :: ReadP.ReadP Wildcard
wildcardMajorP :: ReadP Wildcard
wildcardMajorP = do
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void ((Char -> Bool) -> ReadP Char
ReadP.satisfy Char -> Bool
isWildcard)
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'.')
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void ((Char -> Bool) -> ReadP Char
ReadP.satisfy Char -> Bool
isWildcard)
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'.')
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void ((Char -> Bool) -> ReadP Char
ReadP.satisfy Char -> Bool
isWildcard)
Wildcard -> ReadP Wildcard
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Wildcard
WildcardMajor
primitiveP :: ReadP.ReadP Constraint
primitiveP :: ReadP Constraint
primitiveP = do
Operator
o <- ReadP Operator
operatorP
ReadP ()
spacesP
Operator -> Version -> Constraint
ConstraintOperator Operator
o (Version -> Constraint) -> ReadP Version -> ReadP Constraint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadP Version
versionP
operatorP :: ReadP.ReadP Operator
operatorP :: ReadP Operator
operatorP =
[ReadP Operator] -> ReadP Operator
forall a. [ReadP a] -> ReadP a
ReadP.choice
[ String -> ReadP String
ReadP.string String
"<=" ReadP String -> ReadP Operator -> ReadP Operator
forall a b. ReadP a -> ReadP b -> ReadP b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Operator -> ReadP Operator
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Operator
OperatorLE,
String -> ReadP String
ReadP.string String
">=" ReadP String -> ReadP Operator -> ReadP Operator
forall a b. ReadP a -> ReadP b -> ReadP b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Operator -> ReadP Operator
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Operator
OperatorGE,
Char -> ReadP Char
ReadP.char Char
'<' ReadP Char -> ReadP Operator -> ReadP Operator
forall a b. ReadP a -> ReadP b -> ReadP b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Operator -> ReadP Operator
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Operator
OperatorLT,
Char -> ReadP Char
ReadP.char Char
'>' ReadP Char -> ReadP Operator -> ReadP Operator
forall a b. ReadP a -> ReadP b -> ReadP b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Operator -> ReadP Operator
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Operator
OperatorGT,
Char -> ReadP Char
ReadP.char Char
'=' ReadP Char -> ReadP Operator -> ReadP Operator
forall a b. ReadP a -> ReadP b -> ReadP b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Operator -> ReadP Operator
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Operator
OperatorEQ,
Char -> ReadP Char
ReadP.char Char
'^' ReadP Char -> ReadP Operator -> ReadP Operator
forall a b. ReadP a -> ReadP b -> ReadP b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Operator -> ReadP Operator
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Operator
OperatorCaret,
Char -> ReadP Char
ReadP.char Char
'~' ReadP Char -> ReadP Operator -> ReadP Operator
forall a b. ReadP a -> ReadP b -> ReadP b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Operator -> ReadP Operator
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Operator
OperatorTilde,
Operator -> ReadP Operator
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Operator
OperatorEQ
]
hyphenP :: ReadP.ReadP ()
hyphenP :: ReadP ()
hyphenP = do
ReadP ()
spaces1P
ReadP Char -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (Char -> ReadP Char
ReadP.char Char
'-')
ReadP ()
spaces1P
orP :: ReadP.ReadP ()
orP :: ReadP ()
orP = do
ReadP ()
spaces1P
ReadP String -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void (String -> ReadP String
ReadP.string String
"||")
ReadP ()
spaces1P
spaces1P :: ReadP.ReadP ()
spaces1P :: ReadP ()
spaces1P = ReadP String -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void ((Char -> Bool) -> ReadP String
ReadP.munch1 (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' '))
spacesP :: ReadP.ReadP ()
spacesP :: ReadP ()
spacesP = ReadP String -> ReadP ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Monad.void ((Char -> Bool) -> ReadP String
ReadP.munch (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' '))
renderPreReleases :: [PreRelease] -> String
renderPreReleases :: [PreRelease] -> String
renderPreReleases [PreRelease]
ps =
if [PreRelease] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [PreRelease]
ps then String
"" else Char
'-' Char -> ShowS
forall a. a -> [a] -> [a]
: String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
List.intercalate String
"." ((PreRelease -> String) -> [PreRelease] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PreRelease -> String
renderPreRelease [PreRelease]
ps)
renderBuilds :: [Build] -> String
renderBuilds :: [Build] -> String
renderBuilds [Build]
bs =
if [Build] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Build]
bs then String
"" else Char
'+' Char -> ShowS
forall a. a -> [a] -> [a]
: String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
List.intercalate String
"." ((Build -> String) -> [Build] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Build -> String
renderBuild [Build]
bs)
both :: (a -> b) -> (a, a) -> (b, b)
both :: forall a b. (a -> b) -> (a, a) -> (b, b)
both a -> b
f (a
x, a
y) = (a -> b
f a
x, a -> b
f a
y)
isAsciiDigitNonZero :: Char -> Bool
isAsciiDigitNonZero :: Char -> Bool
isAsciiDigitNonZero Char
c = Char -> Bool
Char.isDigit Char
c Bool -> Bool -> Bool
&& (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'0')
isIdentifier :: Char -> Bool
isIdentifier :: Char -> Bool
isIdentifier Char
c = (Char -> Bool
Char.isAscii Char
c Bool -> Bool -> Bool
&& Char -> Bool
Char.isAlphaNum Char
c) Bool -> Bool -> Bool
|| (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-')
isWildcard :: Char -> Bool
isWildcard :: Char -> Bool
isWildcard Char
c = (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'x') Bool -> Bool -> Bool
|| (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'*') Bool -> Bool -> Bool
|| (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'X')
parse :: ReadP.ReadP a -> String -> Maybe a
parse :: forall a. ReadP a -> String -> Maybe a
parse ReadP a
p String
s =
let p' :: ReadS a
p' = ReadP a -> ReadS a
forall a. ReadP a -> ReadS a
ReadP.readP_to_S ReadP a
p
in [a] -> Maybe a
forall a. [a] -> Maybe a
Maybe.listToMaybe
( do
(a
x, String
"") <- ReadS a
p' String
s
a -> [a]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
)
stringToIntegral :: (Integral a) => String -> a
stringToIntegral :: forall a. Integral a => String -> a
stringToIntegral =
(a -> Char -> a) -> a -> String -> a
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\a
n Char
d -> (a
n a -> a -> a
forall a. Num a => a -> a -> a
* a
10) a -> a -> a
forall a. Num a => a -> a -> a
+ (Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
d) a -> a -> a
forall a. Num a => a -> a -> a
- a
48)) a
0
toWord64 :: Integer -> Maybe Word.Word64
toWord64 :: Integer -> Maybe Word64
toWord64 Integer
n
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = Maybe Word64
forall a. Maybe a
Nothing
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
forall a. Bounded a => a
maxBound :: Word.Word64) = Maybe Word64
forall a. Maybe a
Nothing
| Bool
otherwise = Word64 -> Maybe Word64
forall a. a -> Maybe a
Just (Integer -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n)
data SimpleConstraint
= SCLT Version
| SCEQ Version
| SCGT Version
| SCAnd SimpleConstraint SimpleConstraint
| SCOr SimpleConstraint SimpleConstraint
deriving (Typeable SimpleConstraint
Typeable SimpleConstraint =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SimpleConstraint -> c SimpleConstraint)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SimpleConstraint)
-> (SimpleConstraint -> Constr)
-> (SimpleConstraint -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SimpleConstraint))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SimpleConstraint))
-> ((forall b. Data b => b -> b)
-> SimpleConstraint -> SimpleConstraint)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SimpleConstraint -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SimpleConstraint -> r)
-> (forall u.
(forall d. Data d => d -> u) -> SimpleConstraint -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SimpleConstraint -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint)
-> Data SimpleConstraint
SimpleConstraint -> Constr
SimpleConstraint -> DataType
(forall b. Data b => b -> b)
-> SimpleConstraint -> SimpleConstraint
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> SimpleConstraint -> u
forall u. (forall d. Data d => d -> u) -> SimpleConstraint -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SimpleConstraint -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SimpleConstraint -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SimpleConstraint
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SimpleConstraint -> c SimpleConstraint
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SimpleConstraint)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SimpleConstraint)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SimpleConstraint -> c SimpleConstraint
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SimpleConstraint -> c SimpleConstraint
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SimpleConstraint
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SimpleConstraint
$ctoConstr :: SimpleConstraint -> Constr
toConstr :: SimpleConstraint -> Constr
$cdataTypeOf :: SimpleConstraint -> DataType
dataTypeOf :: SimpleConstraint -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SimpleConstraint)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SimpleConstraint)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SimpleConstraint)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SimpleConstraint)
$cgmapT :: (forall b. Data b => b -> b)
-> SimpleConstraint -> SimpleConstraint
gmapT :: (forall b. Data b => b -> b)
-> SimpleConstraint -> SimpleConstraint
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SimpleConstraint -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SimpleConstraint -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SimpleConstraint -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SimpleConstraint -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SimpleConstraint -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> SimpleConstraint -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SimpleConstraint -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SimpleConstraint -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SimpleConstraint -> m SimpleConstraint
Data.Data, SimpleConstraint -> SimpleConstraint -> Bool
(SimpleConstraint -> SimpleConstraint -> Bool)
-> (SimpleConstraint -> SimpleConstraint -> Bool)
-> Eq SimpleConstraint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SimpleConstraint -> SimpleConstraint -> Bool
== :: SimpleConstraint -> SimpleConstraint -> Bool
$c/= :: SimpleConstraint -> SimpleConstraint -> Bool
/= :: SimpleConstraint -> SimpleConstraint -> Bool
Eq, (forall x. SimpleConstraint -> Rep SimpleConstraint x)
-> (forall x. Rep SimpleConstraint x -> SimpleConstraint)
-> Generic SimpleConstraint
forall x. Rep SimpleConstraint x -> SimpleConstraint
forall x. SimpleConstraint -> Rep SimpleConstraint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SimpleConstraint -> Rep SimpleConstraint x
from :: forall x. SimpleConstraint -> Rep SimpleConstraint x
$cto :: forall x. Rep SimpleConstraint x -> SimpleConstraint
to :: forall x. Rep SimpleConstraint x -> SimpleConstraint
Generics.Generic, Eq SimpleConstraint
Eq SimpleConstraint =>
(SimpleConstraint -> SimpleConstraint -> Ordering)
-> (SimpleConstraint -> SimpleConstraint -> Bool)
-> (SimpleConstraint -> SimpleConstraint -> Bool)
-> (SimpleConstraint -> SimpleConstraint -> Bool)
-> (SimpleConstraint -> SimpleConstraint -> Bool)
-> (SimpleConstraint -> SimpleConstraint -> SimpleConstraint)
-> (SimpleConstraint -> SimpleConstraint -> SimpleConstraint)
-> Ord SimpleConstraint
SimpleConstraint -> SimpleConstraint -> Bool
SimpleConstraint -> SimpleConstraint -> Ordering
SimpleConstraint -> SimpleConstraint -> SimpleConstraint
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SimpleConstraint -> SimpleConstraint -> Ordering
compare :: SimpleConstraint -> SimpleConstraint -> Ordering
$c< :: SimpleConstraint -> SimpleConstraint -> Bool
< :: SimpleConstraint -> SimpleConstraint -> Bool
$c<= :: SimpleConstraint -> SimpleConstraint -> Bool
<= :: SimpleConstraint -> SimpleConstraint -> Bool
$c> :: SimpleConstraint -> SimpleConstraint -> Bool
> :: SimpleConstraint -> SimpleConstraint -> Bool
$c>= :: SimpleConstraint -> SimpleConstraint -> Bool
>= :: SimpleConstraint -> SimpleConstraint -> Bool
$cmax :: SimpleConstraint -> SimpleConstraint -> SimpleConstraint
max :: SimpleConstraint -> SimpleConstraint -> SimpleConstraint
$cmin :: SimpleConstraint -> SimpleConstraint -> SimpleConstraint
min :: SimpleConstraint -> SimpleConstraint -> SimpleConstraint
Ord, ReadPrec [SimpleConstraint]
ReadPrec SimpleConstraint
Int -> ReadS SimpleConstraint
ReadS [SimpleConstraint]
(Int -> ReadS SimpleConstraint)
-> ReadS [SimpleConstraint]
-> ReadPrec SimpleConstraint
-> ReadPrec [SimpleConstraint]
-> Read SimpleConstraint
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SimpleConstraint
readsPrec :: Int -> ReadS SimpleConstraint
$creadList :: ReadS [SimpleConstraint]
readList :: ReadS [SimpleConstraint]
$creadPrec :: ReadPrec SimpleConstraint
readPrec :: ReadPrec SimpleConstraint
$creadListPrec :: ReadPrec [SimpleConstraint]
readListPrec :: ReadPrec [SimpleConstraint]
Read, Int -> SimpleConstraint -> ShowS
[SimpleConstraint] -> ShowS
SimpleConstraint -> String
(Int -> SimpleConstraint -> ShowS)
-> (SimpleConstraint -> String)
-> ([SimpleConstraint] -> ShowS)
-> Show SimpleConstraint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SimpleConstraint -> ShowS
showsPrec :: Int -> SimpleConstraint -> ShowS
$cshow :: SimpleConstraint -> String
show :: SimpleConstraint -> String
$cshowList :: [SimpleConstraint] -> ShowS
showList :: [SimpleConstraint] -> ShowS
Show)
mkV :: Word.Word64 -> Word.Word64 -> Word.Word64 -> Version
mkV :: Word64 -> Word64 -> Word64 -> Version
mkV Word64
m Word64
n Word64
p = Word64 -> Word64 -> Word64 -> [PreRelease] -> [Build] -> Version
makeVersion Word64
m Word64
n Word64
p [] []
satisfiesSC :: SimpleConstraint -> Version -> Bool
satisfiesSC :: SimpleConstraint -> Version -> Bool
satisfiesSC SimpleConstraint
c Version
v = case SimpleConstraint
c of
SCLT Version
u -> Version
v Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
< Version
u
SCEQ Version
u -> Version -> Version -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Version
v Version
u Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
EQ
SCGT Version
u -> Version
v Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
> Version
u
SCAnd SimpleConstraint
l SimpleConstraint
r -> SimpleConstraint -> Version -> Bool
satisfiesSC SimpleConstraint
l Version
v Bool -> Bool -> Bool
&& SimpleConstraint -> Version -> Bool
satisfiesSC SimpleConstraint
r Version
v
SCOr SimpleConstraint
l SimpleConstraint
r -> SimpleConstraint -> Version -> Bool
satisfiesSC SimpleConstraint
l Version
v Bool -> Bool -> Bool
|| SimpleConstraint -> Version -> Bool
satisfiesSC SimpleConstraint
r Version
v
scLE :: Version -> SimpleConstraint
scLE :: Version -> SimpleConstraint
scLE Version
v = SimpleConstraint -> SimpleConstraint -> SimpleConstraint
SCOr (Version -> SimpleConstraint
SCLT Version
v) (Version -> SimpleConstraint
SCEQ Version
v)
scGE :: Version -> SimpleConstraint
scGE :: Version -> SimpleConstraint
scGE Version
v = SimpleConstraint -> SimpleConstraint -> SimpleConstraint
SCOr (Version -> SimpleConstraint
SCGT Version
v) (Version -> SimpleConstraint
SCEQ Version
v)
toSC :: Constraint -> SimpleConstraint
toSC :: Constraint -> SimpleConstraint
toSC Constraint
c = case Constraint
c of
ConstraintOperator Operator
o Version
v -> case Operator
o of
Operator
OperatorLT -> Version -> SimpleConstraint
SCLT Version
v
Operator
OperatorLE -> Version -> SimpleConstraint
scLE Version
v
Operator
OperatorEQ -> Version -> SimpleConstraint
SCEQ Version
v
Operator
OperatorGE -> Version -> SimpleConstraint
scGE Version
v
Operator
OperatorGT -> Version -> SimpleConstraint
SCGT Version
v
Operator
OperatorTilde ->
SimpleConstraint -> SimpleConstraint -> SimpleConstraint
SCAnd (Version -> SimpleConstraint
scGE Version
v) (Version -> SimpleConstraint
SCLT (Word64 -> Word64 -> Word64 -> Version
mkV (Version -> Word64
versionMajor Version
v) (Version -> Word64
versionMinor Version
v Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) Word64
0))
Operator
OperatorCaret ->
SimpleConstraint -> SimpleConstraint -> SimpleConstraint
SCAnd
(Version -> SimpleConstraint
scGE Version
v)
( Version -> SimpleConstraint
SCLT
( case (Version -> Word64
versionMajor Version
v, Version -> Word64
versionMinor Version
v, Version -> Word64
versionPatch Version
v) of
(Word64
0, Word64
0, Word64
p) -> Word64 -> Word64 -> Word64 -> Version
mkV Word64
0 Word64
0 (Word64
p Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1)
(Word64
0, Word64
n, Word64
_) -> Word64 -> Word64 -> Word64 -> Version
mkV Word64
0 (Word64
n Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) Word64
0
(Word64
m, Word64
_, Word64
_) -> Word64 -> Word64 -> Word64 -> Version
mkV (Word64
m Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) Word64
0 Word64
0
)
)
ConstraintHyphen Version
l Version
h -> SimpleConstraint -> SimpleConstraint -> SimpleConstraint
SCAnd (Version -> SimpleConstraint
scGE Version
l) (Version -> SimpleConstraint
scLE Version
h)
ConstraintWildcard Wildcard
w -> case Wildcard
w of
Wildcard
WildcardMajor -> Version -> SimpleConstraint
scGE Version
initialVersion
WildcardMinor Word64
m -> SimpleConstraint -> SimpleConstraint -> SimpleConstraint
SCAnd (Version -> SimpleConstraint
scGE (Word64 -> Word64 -> Word64 -> Version
mkV Word64
m Word64
0 Word64
0)) (Version -> SimpleConstraint
SCLT (Word64 -> Word64 -> Word64 -> Version
mkV (Word64
m Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) Word64
0 Word64
0))
WildcardPatch Word64
m Word64
n -> SimpleConstraint -> SimpleConstraint -> SimpleConstraint
SCAnd (Version -> SimpleConstraint
scGE (Word64 -> Word64 -> Word64 -> Version
mkV Word64
m Word64
n Word64
0)) (Version -> SimpleConstraint
SCLT (Word64 -> Word64 -> Word64 -> Version
mkV Word64
m (Word64
n Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1) Word64
0))
ConstraintAnd Constraint
l Constraint
r -> SimpleConstraint -> SimpleConstraint -> SimpleConstraint
SCAnd (Constraint -> SimpleConstraint
toSC Constraint
l) (Constraint -> SimpleConstraint
toSC Constraint
r)
ConstraintOr Constraint
l Constraint
r -> SimpleConstraint -> SimpleConstraint -> SimpleConstraint
SCOr (Constraint -> SimpleConstraint
toSC Constraint
l) (Constraint -> SimpleConstraint
toSC Constraint
r)