{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Distribution.Types.Version (
Version,
mkVersion,
mkVersion',
versionNumbers,
nullVersion,
alterVersion,
version0,
validVersion,
versionDigitParser,
) where
import Data.Bits (shiftL, shiftR, (.&.), (.|.))
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.Parsec
import Distribution.Pretty
import qualified Data.Version as Base
import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as Disp
import qualified Text.Read as Read
data Version = PV0 {-# UNPACK #-} !Word64
| PV1 !Int [Int]
deriving (Typeable Version
DataType
Constr
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 -> DataType
Version -> Constr
(forall b. Data b => b -> b) -> Version -> Version
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Version -> c Version
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cPV1 :: Constr
$cPV0 :: Constr
$tVersion :: DataType
gmapMo :: (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
gmapMp :: (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
gmapM :: (forall d. Data d => d -> m d) -> Version -> m Version
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Version -> m Version
gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Version -> u
gmapQ :: (forall d. Data d => d -> u) -> Version -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Version -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Version -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Version -> r
gmapT :: (forall b. Data b => b -> b) -> Version -> Version
$cgmapT :: (forall b. Data b => b -> b) -> Version -> Version
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Version)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Version)
dataTypeOf :: Version -> DataType
$cdataTypeOf :: Version -> DataType
toConstr :: Version -> Constr
$ctoConstr :: Version -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Version
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Version
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Version -> c Version
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Version -> c Version
External instance of the constraint type Data Int
External instance of the constraint type Data Int
External instance of the constraint type Data Int
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Word64
Data,Version -> Version -> Bool
(Version -> Version -> Bool)
-> (Version -> Version -> Bool) -> Eq Version
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Version -> Version -> Bool
$c/= :: Version -> Version -> Bool
== :: Version -> Version -> Bool
$c== :: Version -> Version -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Int
External instance of the constraint type Eq Int
External instance of the constraint type Eq Word64
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
$cto :: forall x. Rep Version x -> Version
$cfrom :: forall x. Version -> Rep Version x
Generic,Typeable)
instance Ord Version where
compare :: Version -> Version -> Ordering
compare (PV0 Word64
x) (PV0 Word64
y) = Word64 -> Word64 -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Word64
compare Word64
x Word64
y
compare (PV1 Int
x [Int]
xs) (PV1 Int
y [Int]
ys) = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
x Int
y of
Ordering
EQ -> [Int] -> [Int] -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type forall a. Ord a => Ord [a]
External instance of the constraint type Ord Int
compare [Int]
xs [Int]
ys
Ordering
c -> Ordering
c
compare (PV0 Word64
w) (PV1 Int
y [Int]
ys) = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
x Int
y of
Ordering
EQ -> [Int] -> [Int] -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type forall a. Ord a => Ord [a]
External instance of the constraint type Ord Int
compare [Int
x2,Int
x3,Int
x4] [Int]
ys
Ordering
c -> Ordering
c
where
x :: Int
x = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftR` Int
48) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
x2 :: Int
x2 = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftR` Int
32) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
x3 :: Int
x3 = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftR` Int
16) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
x4 :: Int
x4 = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral (Word64
w Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
compare (PV1 Int
x [Int]
xs) (PV0 Word64
w) = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
x Int
y of
Ordering
EQ -> [Int] -> [Int] -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type forall a. Ord a => Ord [a]
External instance of the constraint type Ord Int
compare [Int]
xs [Int
y2,Int
y3,Int
y4]
Ordering
c -> Ordering
c
where
y :: Int
y = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftR` Int
48) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
y2 :: Int
y2 = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftR` Int
32) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
y3 :: Int
y3 = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftR` Int
16) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
y4 :: Int
y4 = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral (Word64
w Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
instance Show Version where
showsPrec :: Int -> Version -> ShowS
showsPrec Int
d Version
v = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
10)
(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"mkVersion "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Int] -> ShowS
forall a. Show a => Int -> a -> ShowS
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Int
showsPrec Int
11 (Version -> [Int]
versionNumbers Version
v)
instance Read Version where
readPrec :: ReadPrec Version
readPrec = ReadPrec Version -> ReadPrec Version
forall a. ReadPrec a -> ReadPrec a
Read.parens (ReadPrec Version -> ReadPrec Version)
-> ReadPrec Version -> ReadPrec Version
forall a b. (a -> b) -> a -> b
$ do
Read.Ident String
"mkVersion" <- ReadPrec Lexeme
Read.lexP
[Int]
v <- ReadPrec [Int] -> ReadPrec [Int]
forall a. ReadPrec a -> ReadPrec a
Read.step ReadPrec [Int]
forall a. Read a => ReadPrec a
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Int
Read.readPrec
Version -> ReadPrec Version
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return ([Int] -> Version
mkVersion [Int]
v)
instance Binary Version
instance Structured Version
instance NFData Version where
rnf :: Version -> ()
rnf (PV0 Word64
_) = ()
rnf (PV1 Int
_ [Int]
ns) = [Int] -> ()
forall a. NFData a => a -> ()
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Int
rnf [Int]
ns
instance Pretty Version where
pretty :: Version -> Doc
pretty Version
ver
= [Doc] -> Doc
Disp.hcat (Doc -> [Doc] -> [Doc]
Disp.punctuate (Char -> Doc
Disp.char Char
'.')
((Int -> Doc) -> [Int] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Doc
Disp.int ([Int] -> [Doc]) -> [Int] -> [Doc]
forall a b. (a -> b) -> a -> b
$ Version -> [Int]
versionNumbers Version
ver))
instance Parsec Version where
parsec :: m Version
parsec = [Int] -> Version
mkVersion ([Int] -> Version)
-> (NonEmpty Int -> [Int]) -> NonEmpty Int -> Version
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> NonEmpty Int -> [Int]
forall (t :: * -> *) a. Foldable t => t a -> [a]
External instance of the constraint type Foldable NonEmpty
toList (NonEmpty Int -> Version) -> m (NonEmpty Int) -> m Version
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
<$> m Int -> m Char -> m (NonEmpty Int)
forall (m :: * -> *) a sep.
Alternative m =>
m a -> m sep -> m (NonEmpty a)
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.sepByNonEmpty m Int
forall (m :: * -> *). CabalParsing m => m Int
Evidence bound by a type signature of the constraint type CabalParsing m
versionDigitParser (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.char Char
'.') m Version -> m () -> m Version
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
<* m ()
tags
where
tags :: m ()
tags = do
[String]
ts <- m String -> m [String]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
many (m String -> m [String]) -> m String -> m [String]
forall a b. (a -> b) -> a -> b
$ Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.char Char
'-' m Char -> m String -> m String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
*> m Char -> m String
forall (f :: * -> *) a. Alternative f => f a -> f [a]
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
some ((Char -> Bool) -> m Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.satisfy Char -> Bool
isAlphaNum)
case [String]
ts of
[] -> () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
pure ()
(String
_ : [String]
_) -> PWarnType -> String -> m ()
forall (m :: * -> *). CabalParsing m => PWarnType -> String -> m ()
Evidence bound by a type signature of the constraint type CabalParsing m
parsecWarning PWarnType
PWTVersionTag String
"version with tags"
versionDigitParser :: CabalParsing m => m Int
versionDigitParser :: m Int
versionDigitParser = (m Int -> m [Int]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
some m Int
forall (m :: * -> *). CharParsing m => m Int
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
d m [Int] -> ([Int] -> m Int) -> m Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
>>= [Int] -> m Int
forall (m :: * -> *). CabalParsing m => [Int] -> m Int
Evidence bound by a type signature of the constraint type CabalParsing m
toNumber) m Int -> String -> m Int
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.<?> String
"version digit (integral without leading zeroes)"
where
toNumber :: CabalParsing m => [Int] -> m Int
toNumber :: [Int] -> m Int
toNumber [Int
0] = Int -> m Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
return Int
0
toNumber (Int
0:[Int]
_) = String -> m Int
forall (m :: * -> *) a. Parsing m => String -> m a
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.unexpected String
"Version digit with leading zero"
toNumber [Int]
xs
| [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
External instance of the constraint type Foldable []
length [Int]
xs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
9 = String -> m Int
forall (m :: * -> *) a. Parsing m => String -> m a
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.unexpected String
"At most 9 numbers are allowed per version number part"
| Bool
otherwise = Int -> m Int
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
return (Int -> m Int) -> Int -> m Int
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Int) -> Int -> [Int] -> Int
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldl' (\Int
a Int
b -> Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
* Int
10 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
b) Int
0 [Int]
xs
d :: P.CharParsing m => m Int
d :: m Int
d = Char -> Int
f (Char -> Int) -> m Char -> m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
Evidence bound by a type signature of the constraint type CharParsing m
<$> Char -> Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> Char -> m Char
Evidence bound by a type signature of the constraint type CharParsing m
P.satisfyRange Char
'0' Char
'9'
f :: Char -> Int
f Char
c = Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Char -> Int
ord Char
'0'
mkVersion :: [Int] -> Version
mkVersion :: [Int] -> Version
mkVersion [] = Version
nullVersion
mkVersion (Int
v1:[])
| Int -> Bool
inWord16VerRep1 Int
v1 = Word64 -> Version
PV0 (Int -> Word64
mkWord64VerRep1 Int
v1)
| Bool
otherwise = Int -> [Int] -> Version
PV1 Int
v1 []
where
inWord16VerRep1 :: Int -> Bool
inWord16VerRep1 Int
x1 = Int -> Bool
inWord16 (Int
x1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. (Int
x1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1))
mkWord64VerRep1 :: Int -> Word64
mkWord64VerRep1 Int
y1 = Int -> Int -> Int -> Int -> Word64
mkWord64VerRep (Int
y1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) Int
0 Int
0 Int
0
mkVersion (Int
v1:vs :: [Int]
vs@(Int
v2:[]))
| Int -> Int -> Bool
inWord16VerRep2 Int
v1 Int
v2 = Word64 -> Version
PV0 (Int -> Int -> Word64
mkWord64VerRep2 Int
v1 Int
v2)
| Bool
otherwise = Int -> [Int] -> Version
PV1 Int
v1 [Int]
vs
where
inWord16VerRep2 :: Int -> Int -> Bool
inWord16VerRep2 Int
x1 Int
x2 = Int -> Bool
inWord16 (Int
x1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. (Int
x1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1)
Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. Int
x2 Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. (Int
x2Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1))
mkWord64VerRep2 :: Int -> Int -> Word64
mkWord64VerRep2 Int
y1 Int
y2 = Int -> Int -> Int -> Int -> Word64
mkWord64VerRep (Int
y1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) (Int
y2Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) Int
0 Int
0
mkVersion (Int
v1:vs :: [Int]
vs@(Int
v2:Int
v3:[]))
| Int -> Int -> Int -> Bool
inWord16VerRep3 Int
v1 Int
v2 Int
v3 = Word64 -> Version
PV0 (Int -> Int -> Int -> Word64
mkWord64VerRep3 Int
v1 Int
v2 Int
v3)
| Bool
otherwise = Int -> [Int] -> Version
PV1 Int
v1 [Int]
vs
where
inWord16VerRep3 :: Int -> Int -> Int -> Bool
inWord16VerRep3 Int
x1 Int
x2 Int
x3 = Int -> Bool
inWord16 (Int
x1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. (Int
x1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1)
Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. Int
x2 Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. (Int
x2Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1)
Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. Int
x3 Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. (Int
x3Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1))
mkWord64VerRep3 :: Int -> Int -> Int -> Word64
mkWord64VerRep3 Int
y1 Int
y2 Int
y3 = Int -> Int -> Int -> Int -> Word64
mkWord64VerRep (Int
y1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) (Int
y2Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) (Int
y3Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) Int
0
mkVersion (Int
v1:vs :: [Int]
vs@(Int
v2:Int
v3:Int
v4:[]))
| Int -> Int -> Int -> Int -> Bool
inWord16VerRep4 Int
v1 Int
v2 Int
v3 Int
v4 = Word64 -> Version
PV0 (Int -> Int -> Int -> Int -> Word64
mkWord64VerRep4 Int
v1 Int
v2 Int
v3 Int
v4)
| Bool
otherwise = Int -> [Int] -> Version
PV1 Int
v1 [Int]
vs
where
inWord16VerRep4 :: Int -> Int -> Int -> Int -> Bool
inWord16VerRep4 Int
x1 Int
x2 Int
x3 Int
x4 = Int -> Bool
inWord16 (Int
x1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. (Int
x1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1)
Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. Int
x2 Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. (Int
x2Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1)
Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. Int
x3 Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. (Int
x3Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1)
Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. Int
x4 Int -> Int -> Int
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Int
.|. (Int
x4Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1))
mkWord64VerRep4 :: Int -> Int -> Int -> Int -> Word64
mkWord64VerRep4 Int
y1 Int
y2 Int
y3 Int
y4 = Int -> Int -> Int -> Int -> Word64
mkWord64VerRep (Int
y1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) (Int
y2Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) (Int
y3Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1) (Int
y4Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1)
mkVersion (Int
v1:[Int]
vs) = Int -> [Int] -> Version
PV1 Int
v1 [Int]
vs
version0 :: Version
version0 :: Version
version0 = [Int] -> Version
mkVersion [Int
0]
{-# INLINE mkWord64VerRep #-}
mkWord64VerRep :: Int -> Int -> Int -> Int -> Word64
mkWord64VerRep :: Int -> Int -> Int -> Int -> Word64
mkWord64VerRep Int
v1 Int
v2 Int
v3 Int
v4 =
(Int -> Word64
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word64
External instance of the constraint type Integral Int
fromIntegral Int
v1 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftL` Int
48)
Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.|. (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word64
External instance of the constraint type Integral Int
fromIntegral Int
v2 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftL` Int
32)
Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.|. (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word64
External instance of the constraint type Integral Int
fromIntegral Int
v3 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftL` Int
16)
Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.|. Int -> Word64
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word64
External instance of the constraint type Integral Int
fromIntegral Int
v4
{-# INLINE inWord16 #-}
inWord16 :: Int -> Bool
inWord16 :: Int -> Bool
inWord16 Int
x = (Int -> Word
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word
External instance of the constraint type Integral Int
fromIntegral Int
x :: Word) Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Word
<= Word
0xffff
mkVersion' :: Base.Version -> Version
mkVersion' :: Version -> Version
mkVersion' = [Int] -> Version
mkVersion ([Int] -> Version) -> (Version -> [Int]) -> Version -> Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> [Int]
Base.versionBranch
versionNumbers :: Version -> [Int]
versionNumbers :: Version -> [Int]
versionNumbers (PV1 Int
n [Int]
ns) = Int
nInt -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
ns
versionNumbers (PV0 Word64
w)
| Int
v1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
0 = []
| Int
v2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
0 = [Int
v1]
| Int
v3 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
0 = [Int
v1,Int
v2]
| Int
v4 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
0 = [Int
v1,Int
v2,Int
v3]
| Bool
otherwise = [Int
v1,Int
v2,Int
v3,Int
v4]
where
v1 :: Int
v1 = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftR` Int
48) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
v2 :: Int
v2 = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftR` Int
32) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
v3 :: Int
v3 = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
External instance of the constraint type Bits Word64
`shiftR` Int
16) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
v4 :: Int
v4 = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Word64
fromIntegral (Word64
w Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
External instance of the constraint type Bits Word64
.&. Word64
0xffff) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1
nullVersion :: Version
nullVersion :: Version
nullVersion = Word64 -> Version
PV0 Word64
0
alterVersion :: ([Int] -> [Int]) -> Version -> Version
alterVersion :: ([Int] -> [Int]) -> Version -> Version
alterVersion [Int] -> [Int]
f = [Int] -> Version
mkVersion ([Int] -> Version) -> (Version -> [Int]) -> Version -> Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Int]
f ([Int] -> [Int]) -> (Version -> [Int]) -> Version -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> [Int]
versionNumbers
validVersion :: Version -> Bool
validVersion :: Version -> Bool
validVersion Version
v = Version
v Version -> Version -> Bool
forall a. Eq a => a -> a -> Bool
Instance of class: Eq of the constraint type Eq Version
/= Version
nullVersion Bool -> Bool -> Bool
&& (Int -> Bool) -> [Int] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
External instance of the constraint type Foldable []
all (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
>=Int
0) (Version -> [Int]
versionNumbers Version
v)