{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Distribution.Types.PkgconfigVersionRange (
PkgconfigVersionRange (..),
anyPkgconfigVersion,
isAnyPkgconfigVersion,
withinPkgconfigVersionRange,
versionToPkgconfigVersion,
versionRangeToPkgconfigVersionRange,
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.CabalSpecVersion
import Distribution.Parsec
import Distribution.Pretty
import Distribution.Types.PkgconfigVersion
import Distribution.Types.Version
import Distribution.Types.VersionRange
import qualified Data.ByteString.Char8 as BS8
import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as PP
data PkgconfigVersionRange
= PcAnyVersion
| PcThisVersion PkgconfigVersion
| PcLaterVersion PkgconfigVersion
| PcEarlierVersion PkgconfigVersion
| PcOrLaterVersion PkgconfigVersion
| PcOrEarlierVersion PkgconfigVersion
| PcUnionVersionRanges PkgconfigVersionRange PkgconfigVersionRange
| PcIntersectVersionRanges PkgconfigVersionRange PkgconfigVersionRange
deriving ((forall x. PkgconfigVersionRange -> Rep PkgconfigVersionRange x)
-> (forall x. Rep PkgconfigVersionRange x -> PkgconfigVersionRange)
-> Generic PkgconfigVersionRange
forall x. Rep PkgconfigVersionRange x -> PkgconfigVersionRange
forall x. PkgconfigVersionRange -> Rep PkgconfigVersionRange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PkgconfigVersionRange x -> PkgconfigVersionRange
$cfrom :: forall x. PkgconfigVersionRange -> Rep PkgconfigVersionRange x
Generic, ReadPrec [PkgconfigVersionRange]
ReadPrec PkgconfigVersionRange
Int -> ReadS PkgconfigVersionRange
ReadS [PkgconfigVersionRange]
(Int -> ReadS PkgconfigVersionRange)
-> ReadS [PkgconfigVersionRange]
-> ReadPrec PkgconfigVersionRange
-> ReadPrec [PkgconfigVersionRange]
-> Read PkgconfigVersionRange
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PkgconfigVersionRange]
$creadListPrec :: ReadPrec [PkgconfigVersionRange]
readPrec :: ReadPrec PkgconfigVersionRange
$creadPrec :: ReadPrec PkgconfigVersionRange
readList :: ReadS [PkgconfigVersionRange]
$creadList :: ReadS [PkgconfigVersionRange]
readsPrec :: Int -> ReadS PkgconfigVersionRange
$creadsPrec :: Int -> ReadS PkgconfigVersionRange
Instance of class: Read of the constraint type Read PkgconfigVersionRange
External instance of the constraint type Read PkgconfigVersion
External instance of the constraint type Read PkgconfigVersion
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read PkgconfigVersionRange
Read, Int -> PkgconfigVersionRange -> ShowS
[PkgconfigVersionRange] -> ShowS
PkgconfigVersionRange -> String
(Int -> PkgconfigVersionRange -> ShowS)
-> (PkgconfigVersionRange -> String)
-> ([PkgconfigVersionRange] -> ShowS)
-> Show PkgconfigVersionRange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PkgconfigVersionRange] -> ShowS
$cshowList :: [PkgconfigVersionRange] -> ShowS
show :: PkgconfigVersionRange -> String
$cshow :: PkgconfigVersionRange -> String
showsPrec :: Int -> PkgconfigVersionRange -> ShowS
$cshowsPrec :: Int -> PkgconfigVersionRange -> ShowS
Instance of class: Show of the constraint type Show PkgconfigVersionRange
External instance of the constraint type Show PkgconfigVersion
External instance of the constraint type Show PkgconfigVersion
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show PkgconfigVersionRange
Show, PkgconfigVersionRange -> PkgconfigVersionRange -> Bool
(PkgconfigVersionRange -> PkgconfigVersionRange -> Bool)
-> (PkgconfigVersionRange -> PkgconfigVersionRange -> Bool)
-> Eq PkgconfigVersionRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PkgconfigVersionRange -> PkgconfigVersionRange -> Bool
$c/= :: PkgconfigVersionRange -> PkgconfigVersionRange -> Bool
== :: PkgconfigVersionRange -> PkgconfigVersionRange -> Bool
$c== :: PkgconfigVersionRange -> PkgconfigVersionRange -> Bool
External instance of the constraint type Eq PkgconfigVersion
External instance of the constraint type Eq PkgconfigVersion
Instance of class: Eq of the constraint type Eq PkgconfigVersionRange
Eq, Typeable, Typeable PkgconfigVersionRange
DataType
Constr
Typeable PkgconfigVersionRange
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PkgconfigVersionRange
-> c PkgconfigVersionRange)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PkgconfigVersionRange)
-> (PkgconfigVersionRange -> Constr)
-> (PkgconfigVersionRange -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PkgconfigVersionRange))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PkgconfigVersionRange))
-> ((forall b. Data b => b -> b)
-> PkgconfigVersionRange -> PkgconfigVersionRange)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> PkgconfigVersionRange
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> PkgconfigVersionRange
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> PkgconfigVersionRange -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PkgconfigVersionRange -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange)
-> Data PkgconfigVersionRange
PkgconfigVersionRange -> DataType
PkgconfigVersionRange -> Constr
(forall b. Data b => b -> b)
-> PkgconfigVersionRange -> PkgconfigVersionRange
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PkgconfigVersionRange
-> c PkgconfigVersionRange
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PkgconfigVersionRange
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) -> PkgconfigVersionRange -> u
forall u.
(forall d. Data d => d -> u) -> PkgconfigVersionRange -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigVersionRange -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigVersionRange -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PkgconfigVersionRange
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PkgconfigVersionRange
-> c PkgconfigVersionRange
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PkgconfigVersionRange)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PkgconfigVersionRange)
$cPcIntersectVersionRanges :: Constr
$cPcUnionVersionRanges :: Constr
$cPcOrEarlierVersion :: Constr
$cPcOrLaterVersion :: Constr
$cPcEarlierVersion :: Constr
$cPcLaterVersion :: Constr
$cPcThisVersion :: Constr
$cPcAnyVersion :: Constr
$tPkgconfigVersionRange :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange
gmapMp :: (forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange
gmapM :: (forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PkgconfigVersionRange -> m PkgconfigVersionRange
gmapQi :: Int -> (forall d. Data d => d -> u) -> PkgconfigVersionRange -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PkgconfigVersionRange -> u
gmapQ :: (forall d. Data d => d -> u) -> PkgconfigVersionRange -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> PkgconfigVersionRange -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigVersionRange -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigVersionRange -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigVersionRange -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PkgconfigVersionRange -> r
gmapT :: (forall b. Data b => b -> b)
-> PkgconfigVersionRange -> PkgconfigVersionRange
$cgmapT :: (forall b. Data b => b -> b)
-> PkgconfigVersionRange -> PkgconfigVersionRange
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PkgconfigVersionRange)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PkgconfigVersionRange)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PkgconfigVersionRange)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PkgconfigVersionRange)
dataTypeOf :: PkgconfigVersionRange -> DataType
$cdataTypeOf :: PkgconfigVersionRange -> DataType
toConstr :: PkgconfigVersionRange -> Constr
$ctoConstr :: PkgconfigVersionRange -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PkgconfigVersionRange
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PkgconfigVersionRange
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PkgconfigVersionRange
-> c PkgconfigVersionRange
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PkgconfigVersionRange
-> c PkgconfigVersionRange
Instance of class: Data of the constraint type Data PkgconfigVersionRange
External instance of the constraint type Data PkgconfigVersion
Instance of class: Data of the constraint type Data PkgconfigVersionRange
External instance of the constraint type Data PkgconfigVersion
External instance of the constraint type Data PkgconfigVersion
Instance of class: Data of the constraint type Data PkgconfigVersionRange
Data)
instance Binary PkgconfigVersionRange
instance Structured PkgconfigVersionRange
instance NFData PkgconfigVersionRange where rnf :: PkgconfigVersionRange -> ()
rnf = PkgconfigVersionRange -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData PkgconfigVersion
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData PkgconfigVersion
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData PkgconfigVersion
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData PkgconfigVersion
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData PkgconfigVersion
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
Instance of class: NFData of the constraint type NFData PkgconfigVersionRange
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
Instance of class: NFData of the constraint type NFData PkgconfigVersionRange
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :*: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
Instance of class: NFData of the constraint type NFData PkgconfigVersionRange
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
Instance of class: NFData of the constraint type NFData PkgconfigVersionRange
Instance of class: Generic of the constraint type Generic PkgconfigVersionRange
genericRnf
instance Pretty PkgconfigVersionRange where
pretty :: PkgconfigVersionRange -> Doc
pretty = Int -> PkgconfigVersionRange -> Doc
pp Int
0 where
pp :: Int -> PkgconfigVersionRange -> PP.Doc
pp :: Int -> PkgconfigVersionRange -> Doc
pp Int
_ PkgconfigVersionRange
PcAnyVersion = String -> Doc
PP.text String
"-any"
pp Int
_ (PcThisVersion PkgconfigVersion
v) = String -> Doc
PP.text String
"==" Doc -> Doc -> Doc
<<>> PkgconfigVersion -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty PkgconfigVersion
pretty PkgconfigVersion
v
pp Int
_ (PcLaterVersion PkgconfigVersion
v) = String -> Doc
PP.text String
">" Doc -> Doc -> Doc
<<>> PkgconfigVersion -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty PkgconfigVersion
pretty PkgconfigVersion
v
pp Int
_ (PcEarlierVersion PkgconfigVersion
v) = String -> Doc
PP.text String
"<" Doc -> Doc -> Doc
<<>> PkgconfigVersion -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty PkgconfigVersion
pretty PkgconfigVersion
v
pp Int
_ (PcOrLaterVersion PkgconfigVersion
v) = String -> Doc
PP.text String
">=" Doc -> Doc -> Doc
<<>> PkgconfigVersion -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty PkgconfigVersion
pretty PkgconfigVersion
v
pp Int
_ (PcOrEarlierVersion PkgconfigVersion
v) = String -> Doc
PP.text String
"<=" Doc -> Doc -> Doc
<<>> PkgconfigVersion -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty PkgconfigVersion
pretty PkgconfigVersion
v
pp Int
d (PcUnionVersionRanges PkgconfigVersionRange
v PkgconfigVersionRange
u) = Bool -> Doc -> Doc
parens (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
>= Int
1) (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
Int -> PkgconfigVersionRange -> Doc
pp Int
1 PkgconfigVersionRange
v Doc -> Doc -> Doc
PP.<+> String -> Doc
PP.text String
"||" Doc -> Doc -> Doc
PP.<+> Int -> PkgconfigVersionRange -> Doc
pp Int
0 PkgconfigVersionRange
u
pp Int
d (PcIntersectVersionRanges PkgconfigVersionRange
v PkgconfigVersionRange
u) = Bool -> Doc -> Doc
parens (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
>= Int
2) (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
Int -> PkgconfigVersionRange -> Doc
pp Int
2 PkgconfigVersionRange
v Doc -> Doc -> Doc
PP.<+> String -> Doc
PP.text String
"&&" Doc -> Doc -> Doc
PP.<+> Int -> PkgconfigVersionRange -> Doc
pp Int
1 PkgconfigVersionRange
u
parens :: Bool -> Doc -> Doc
parens Bool
True = Doc -> Doc
PP.parens
parens Bool
False = Doc -> Doc
forall a. a -> a
id
instance Parsec PkgconfigVersionRange where
parsec :: m PkgconfigVersionRange
parsec = do
CabalSpecVersion
csv <- m CabalSpecVersion
forall (m :: * -> *). CabalParsing m => m CabalSpecVersion
Evidence bound by a type signature of the constraint type CabalParsing m
askCabalSpecVersion
if CabalSpecVersion
csv CabalSpecVersion -> CabalSpecVersion -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord CabalSpecVersion
>= CabalSpecVersion
CabalSpecV3_0
then m PkgconfigVersionRange
forall (m :: * -> *). CabalParsing m => m PkgconfigVersionRange
Evidence bound by a type signature of the constraint type CabalParsing m
pkgconfigParser
else VersionRange -> PkgconfigVersionRange
versionRangeToPkgconfigVersionRange (VersionRange -> PkgconfigVersionRange)
-> m VersionRange -> m PkgconfigVersionRange
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 VersionRange
forall (m :: * -> *). CabalParsing m => m Int -> m VersionRange
Evidence bound by a type signature of the constraint type CabalParsing m
versionRangeParser m Int
forall (m :: * -> *) a. (CharParsing m, Integral a) => m a
External instance of the constraint type Integral 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
P.integral
pkgconfigParser :: CabalParsing m => m PkgconfigVersionRange
pkgconfigParser :: m PkgconfigVersionRange
pkgconfigParser = m ()
forall (m :: * -> *). CharParsing m => 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.spaces m () -> m PkgconfigVersionRange -> m PkgconfigVersionRange
forall (m :: * -> *) a b. Monad m => m 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
>> m PkgconfigVersionRange
expr where
expr :: m PkgconfigVersionRange
expr = do
NonEmpty PkgconfigVersionRange
ts <- m PkgconfigVersionRange
term m PkgconfigVersionRange
-> m () -> m (NonEmpty PkgconfigVersionRange)
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` (String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
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 String
"||" m String -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m 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
>> m ()
forall (m :: * -> *). CharParsing m => 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.spaces)
PkgconfigVersionRange -> m PkgconfigVersionRange
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 (PkgconfigVersionRange -> m PkgconfigVersionRange)
-> PkgconfigVersionRange -> m PkgconfigVersionRange
forall a b. (a -> b) -> a -> b
$ (PkgconfigVersionRange
-> PkgconfigVersionRange -> PkgconfigVersionRange)
-> NonEmpty PkgconfigVersionRange -> PkgconfigVersionRange
forall a. (a -> a -> a) -> NonEmpty a -> a
foldr1 PkgconfigVersionRange
-> PkgconfigVersionRange -> PkgconfigVersionRange
PcUnionVersionRanges NonEmpty PkgconfigVersionRange
ts
term :: m PkgconfigVersionRange
term = do
NonEmpty PkgconfigVersionRange
fs <- m PkgconfigVersionRange
factor m PkgconfigVersionRange
-> m () -> m (NonEmpty PkgconfigVersionRange)
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` (String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
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 String
"&&" m String -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m 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
>> m ()
forall (m :: * -> *). CharParsing m => 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.spaces)
PkgconfigVersionRange -> m PkgconfigVersionRange
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 (PkgconfigVersionRange -> m PkgconfigVersionRange)
-> PkgconfigVersionRange -> m PkgconfigVersionRange
forall a b. (a -> b) -> a -> b
$ (PkgconfigVersionRange
-> PkgconfigVersionRange -> PkgconfigVersionRange)
-> NonEmpty PkgconfigVersionRange -> PkgconfigVersionRange
forall a. (a -> a -> a) -> NonEmpty a -> a
foldr1 PkgconfigVersionRange
-> PkgconfigVersionRange -> PkgconfigVersionRange
PcIntersectVersionRanges NonEmpty PkgconfigVersionRange
fs
factor :: m PkgconfigVersionRange
factor = m PkgconfigVersionRange -> m PkgconfigVersionRange
forall {a}. m a -> m a
parens m PkgconfigVersionRange
expr m PkgconfigVersionRange
-> m PkgconfigVersionRange -> m PkgconfigVersionRange
forall (f :: * -> *) a. Alternative f => f a -> 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
<|> m PkgconfigVersionRange
prim
prim :: m PkgconfigVersionRange
prim = do
String
op <- (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
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.munch1 (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type Eq Char
External instance of the constraint type Foldable []
`elem` String
"<>=^-") m String -> String -> m String
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
"operator"
case String
op of
String
"-" -> PkgconfigVersionRange
anyPkgconfigVersion PkgconfigVersionRange -> m () -> m PkgconfigVersionRange
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
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
<$ (String -> m String
forall (m :: * -> *). CharParsing m => String -> m String
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 String
"any" m String -> m () -> m ()
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 ()
forall (m :: * -> *). CharParsing m => 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.spaces)
String
"==" -> (PkgconfigVersion -> PkgconfigVersionRange)
-> m PkgconfigVersionRange
forall {m :: * -> *} {t} {b}.
(Parsec t, CabalParsing m) =>
(t -> b) -> m b
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type Parsec PkgconfigVersion
afterOp PkgconfigVersion -> PkgconfigVersionRange
PcThisVersion
String
">" -> (PkgconfigVersion -> PkgconfigVersionRange)
-> m PkgconfigVersionRange
forall {m :: * -> *} {t} {b}.
(Parsec t, CabalParsing m) =>
(t -> b) -> m b
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type Parsec PkgconfigVersion
afterOp PkgconfigVersion -> PkgconfigVersionRange
PcLaterVersion
String
"<" -> (PkgconfigVersion -> PkgconfigVersionRange)
-> m PkgconfigVersionRange
forall {m :: * -> *} {t} {b}.
(Parsec t, CabalParsing m) =>
(t -> b) -> m b
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type Parsec PkgconfigVersion
afterOp PkgconfigVersion -> PkgconfigVersionRange
PcEarlierVersion
String
">=" -> (PkgconfigVersion -> PkgconfigVersionRange)
-> m PkgconfigVersionRange
forall {m :: * -> *} {t} {b}.
(Parsec t, CabalParsing m) =>
(t -> b) -> m b
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type Parsec PkgconfigVersion
afterOp PkgconfigVersion -> PkgconfigVersionRange
PcOrLaterVersion
String
"<=" -> (PkgconfigVersion -> PkgconfigVersionRange)
-> m PkgconfigVersionRange
forall {m :: * -> *} {t} {b}.
(Parsec t, CabalParsing m) =>
(t -> b) -> m b
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type Parsec PkgconfigVersion
afterOp PkgconfigVersion -> PkgconfigVersionRange
PcOrEarlierVersion
String
_ -> String -> m PkgconfigVersionRange
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 -> m PkgconfigVersionRange)
-> String -> m PkgconfigVersionRange
forall a b. (a -> b) -> a -> b
$ String
"Unknown version operator " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
show String
op
afterOp :: (t -> b) -> m b
afterOp t -> b
f = do
m ()
forall (m :: * -> *). CharParsing m => 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.spaces
t
v <- m t
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
Evidence bound by a type signature of the constraint type CabalParsing m
Evidence bound by a type signature of the constraint type Parsec t
parsec
m ()
forall (m :: * -> *). CharParsing m => 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.spaces
b -> m b
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 (t -> b
f t
v)
parens :: m a -> m a
parens = m () -> m () -> m a -> m a
forall (m :: * -> *) bra ket a.
Applicative m =>
m bra -> m ket -> m a -> m 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
P.between
((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 -> String -> m Char
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
"opening paren") m Char -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m 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
>> m ()
forall (m :: * -> *). CharParsing m => 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.spaces)
(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 () -> m ()
forall (m :: * -> *) a b. Monad m => m 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
>> m ()
forall (m :: * -> *). CharParsing m => 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.spaces)
anyPkgconfigVersion :: PkgconfigVersionRange
anyPkgconfigVersion :: PkgconfigVersionRange
anyPkgconfigVersion = PkgconfigVersionRange
PcAnyVersion
isAnyPkgconfigVersion :: PkgconfigVersionRange -> Bool
isAnyPkgconfigVersion :: PkgconfigVersionRange -> Bool
isAnyPkgconfigVersion = (PkgconfigVersionRange -> PkgconfigVersionRange -> Bool
forall a. Eq a => a -> a -> Bool
Instance of class: Eq of the constraint type Eq PkgconfigVersionRange
== PkgconfigVersionRange
PcAnyVersion)
withinPkgconfigVersionRange :: PkgconfigVersion -> PkgconfigVersionRange -> Bool
withinPkgconfigVersionRange :: PkgconfigVersion -> PkgconfigVersionRange -> Bool
withinPkgconfigVersionRange PkgconfigVersion
v = PkgconfigVersionRange -> Bool
go where
go :: PkgconfigVersionRange -> Bool
go PkgconfigVersionRange
PcAnyVersion = Bool
True
go (PcThisVersion PkgconfigVersion
u) = PkgconfigVersion
v PkgconfigVersion -> PkgconfigVersion -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq PkgconfigVersion
== PkgconfigVersion
u
go (PcLaterVersion PkgconfigVersion
u) = PkgconfigVersion
v PkgconfigVersion -> PkgconfigVersion -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord PkgconfigVersion
> PkgconfigVersion
u
go (PcEarlierVersion PkgconfigVersion
u) = PkgconfigVersion
v PkgconfigVersion -> PkgconfigVersion -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord PkgconfigVersion
< PkgconfigVersion
u
go (PcOrLaterVersion PkgconfigVersion
u) = PkgconfigVersion
v PkgconfigVersion -> PkgconfigVersion -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord PkgconfigVersion
>= PkgconfigVersion
u
go (PcOrEarlierVersion PkgconfigVersion
u) = PkgconfigVersion
v PkgconfigVersion -> PkgconfigVersion -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord PkgconfigVersion
<= PkgconfigVersion
u
go (PcUnionVersionRanges PkgconfigVersionRange
a PkgconfigVersionRange
b) = PkgconfigVersionRange -> Bool
go PkgconfigVersionRange
a Bool -> Bool -> Bool
|| PkgconfigVersionRange -> Bool
go PkgconfigVersionRange
b
go (PcIntersectVersionRanges PkgconfigVersionRange
a PkgconfigVersionRange
b) = PkgconfigVersionRange -> Bool
go PkgconfigVersionRange
a Bool -> Bool -> Bool
&& PkgconfigVersionRange -> Bool
go PkgconfigVersionRange
b
versionToPkgconfigVersion :: Version -> PkgconfigVersion
versionToPkgconfigVersion :: Version -> PkgconfigVersion
versionToPkgconfigVersion = ByteString -> PkgconfigVersion
PkgconfigVersion (ByteString -> PkgconfigVersion)
-> (Version -> ByteString) -> Version -> PkgconfigVersion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS8.pack (String -> ByteString)
-> (Version -> String) -> Version -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> String
forall a. Pretty a => a -> String
External instance of the constraint type Pretty Version
prettyShow
versionRangeToPkgconfigVersionRange :: VersionRange -> PkgconfigVersionRange
versionRangeToPkgconfigVersionRange :: VersionRange -> PkgconfigVersionRange
versionRangeToPkgconfigVersionRange = PkgconfigVersionRange
-> (Version -> PkgconfigVersionRange)
-> (Version -> PkgconfigVersionRange)
-> (Version -> PkgconfigVersionRange)
-> (PkgconfigVersionRange
-> PkgconfigVersionRange -> PkgconfigVersionRange)
-> (PkgconfigVersionRange
-> PkgconfigVersionRange -> PkgconfigVersionRange)
-> VersionRange
-> PkgconfigVersionRange
forall a.
a
-> (Version -> a)
-> (Version -> a)
-> (Version -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> VersionRange
-> a
foldVersionRange
PkgconfigVersionRange
anyPkgconfigVersion
(PkgconfigVersion -> PkgconfigVersionRange
PcThisVersion (PkgconfigVersion -> PkgconfigVersionRange)
-> (Version -> PkgconfigVersion)
-> Version
-> PkgconfigVersionRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> PkgconfigVersion
versionToPkgconfigVersion)
(PkgconfigVersion -> PkgconfigVersionRange
PcLaterVersion (PkgconfigVersion -> PkgconfigVersionRange)
-> (Version -> PkgconfigVersion)
-> Version
-> PkgconfigVersionRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> PkgconfigVersion
versionToPkgconfigVersion)
(PkgconfigVersion -> PkgconfigVersionRange
PcEarlierVersion (PkgconfigVersion -> PkgconfigVersionRange)
-> (Version -> PkgconfigVersion)
-> Version
-> PkgconfigVersionRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> PkgconfigVersion
versionToPkgconfigVersion)
PkgconfigVersionRange
-> PkgconfigVersionRange -> PkgconfigVersionRange
PcUnionVersionRanges
PkgconfigVersionRange
-> PkgconfigVersionRange -> PkgconfigVersionRange
PcIntersectVersionRanges