{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Distribution.Types.VersionRange.Internal
( VersionRange(..)
, anyVersion, noVersion
, thisVersion, notThisVersion
, laterVersion, earlierVersion
, orLaterVersion, orEarlierVersion
, unionVersionRanges, intersectVersionRanges
, withinVersion
, majorBoundVersion
, VersionRangeF(..)
, projectVersionRange
, embedVersionRange
, cataVersionRange
, anaVersionRange
, hyloVersionRange
, versionRangeParser
, majorUpperBound
) where
import Distribution.Compat.Prelude
import Distribution.Types.Version
import Prelude ()
import Distribution.CabalSpecVersion
import Distribution.Parsec
import Distribution.Pretty
import Text.PrettyPrint ((<+>))
import qualified Distribution.Compat.CharParsing as P
import qualified Distribution.Compat.DList as DList
import qualified Text.PrettyPrint as Disp
data VersionRange
= AnyVersion
| ThisVersion Version
| LaterVersion Version
| OrLaterVersion Version
| EarlierVersion Version
| OrEarlierVersion Version
| WildcardVersion Version
| MajorBoundVersion Version
| UnionVersionRanges VersionRange VersionRange
| IntersectVersionRanges VersionRange VersionRange
| VersionRangeParens VersionRange
deriving ( Typeable VersionRange
DataType
Constr
Typeable VersionRange
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRange -> c VersionRange)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VersionRange)
-> (VersionRange -> Constr)
-> (VersionRange -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VersionRange))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VersionRange))
-> ((forall b. Data b => b -> b) -> VersionRange -> VersionRange)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRange -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRange -> r)
-> (forall u. (forall d. Data d => d -> u) -> VersionRange -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> VersionRange -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VersionRange -> m VersionRange)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VersionRange -> m VersionRange)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VersionRange -> m VersionRange)
-> Data VersionRange
VersionRange -> DataType
VersionRange -> Constr
(forall b. Data b => b -> b) -> VersionRange -> VersionRange
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRange -> c VersionRange
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VersionRange
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) -> VersionRange -> u
forall u. (forall d. Data d => d -> u) -> VersionRange -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRange -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRange -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VersionRange -> m VersionRange
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VersionRange -> m VersionRange
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VersionRange
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRange -> c VersionRange
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VersionRange)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VersionRange)
$cVersionRangeParens :: Constr
$cIntersectVersionRanges :: Constr
$cUnionVersionRanges :: Constr
$cMajorBoundVersion :: Constr
$cWildcardVersion :: Constr
$cOrEarlierVersion :: Constr
$cEarlierVersion :: Constr
$cOrLaterVersion :: Constr
$cLaterVersion :: Constr
$cThisVersion :: Constr
$cAnyVersion :: Constr
$tVersionRange :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VersionRange -> m VersionRange
gmapMp :: (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VersionRange -> m VersionRange
gmapM :: (forall d. Data d => d -> m d) -> VersionRange -> m VersionRange
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VersionRange -> m VersionRange
gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionRange -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VersionRange -> u
gmapQ :: (forall d. Data d => d -> u) -> VersionRange -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VersionRange -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRange -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRange -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRange -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRange -> r
gmapT :: (forall b. Data b => b -> b) -> VersionRange -> VersionRange
$cgmapT :: (forall b. Data b => b -> b) -> VersionRange -> VersionRange
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VersionRange)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VersionRange)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c VersionRange)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VersionRange)
dataTypeOf :: VersionRange -> DataType
$cdataTypeOf :: VersionRange -> DataType
toConstr :: VersionRange -> Constr
$ctoConstr :: VersionRange -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VersionRange
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VersionRange
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRange -> c VersionRange
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRange -> c VersionRange
Instance of class: Data of the constraint type Data VersionRange
External instance of the constraint type Data Version
Instance of class: Data of the constraint type Data VersionRange
External instance of the constraint type Data Version
External instance of the constraint type Data Version
Instance of class: Data of the constraint type Data VersionRange
Data, VersionRange -> VersionRange -> Bool
(VersionRange -> VersionRange -> Bool)
-> (VersionRange -> VersionRange -> Bool) -> Eq VersionRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionRange -> VersionRange -> Bool
$c/= :: VersionRange -> VersionRange -> Bool
== :: VersionRange -> VersionRange -> Bool
$c== :: VersionRange -> VersionRange -> Bool
Instance of class: Eq of the constraint type Eq VersionRange
External instance of the constraint type Eq Version
External instance of the constraint type Eq Version
Instance of class: Eq of the constraint type Eq VersionRange
Eq, (forall x. VersionRange -> Rep VersionRange x)
-> (forall x. Rep VersionRange x -> VersionRange)
-> Generic VersionRange
forall x. Rep VersionRange x -> VersionRange
forall x. VersionRange -> Rep VersionRange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VersionRange x -> VersionRange
$cfrom :: forall x. VersionRange -> Rep VersionRange x
Generic, ReadPrec [VersionRange]
ReadPrec VersionRange
Int -> ReadS VersionRange
ReadS [VersionRange]
(Int -> ReadS VersionRange)
-> ReadS [VersionRange]
-> ReadPrec VersionRange
-> ReadPrec [VersionRange]
-> Read VersionRange
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VersionRange]
$creadListPrec :: ReadPrec [VersionRange]
readPrec :: ReadPrec VersionRange
$creadPrec :: ReadPrec VersionRange
readList :: ReadS [VersionRange]
$creadList :: ReadS [VersionRange]
readsPrec :: Int -> ReadS VersionRange
$creadsPrec :: Int -> ReadS VersionRange
Instance of class: Read of the constraint type Read VersionRange
External instance of the constraint type Read Version
External instance of the constraint type Read Version
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 VersionRange
Read, Int -> VersionRange -> ShowS
[VersionRange] -> ShowS
VersionRange -> String
(Int -> VersionRange -> ShowS)
-> (VersionRange -> String)
-> ([VersionRange] -> ShowS)
-> Show VersionRange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VersionRange] -> ShowS
$cshowList :: [VersionRange] -> ShowS
show :: VersionRange -> String
$cshow :: VersionRange -> String
showsPrec :: Int -> VersionRange -> ShowS
$cshowsPrec :: Int -> VersionRange -> ShowS
Instance of class: Show of the constraint type Show VersionRange
External instance of the constraint type Show Version
External instance of the constraint type Show Version
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 VersionRange
Show, Typeable )
instance Binary VersionRange
instance Structured VersionRange
instance NFData VersionRange where rnf :: VersionRange -> ()
rnf = VersionRange -> ()
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 Version
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 Version
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 Version
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 Version
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 Version
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 Version
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 Version
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 VersionRange
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 VersionRange
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 VersionRange
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 VersionRange
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)
Instance of class: NFData of the constraint type NFData VersionRange
Instance of class: Generic of the constraint type Generic VersionRange
genericRnf
anyVersion :: VersionRange
anyVersion :: VersionRange
anyVersion = VersionRange
AnyVersion
noVersion :: VersionRange
noVersion :: VersionRange
noVersion = VersionRange -> VersionRange -> VersionRange
IntersectVersionRanges (Version -> VersionRange
LaterVersion Version
v) (Version -> VersionRange
EarlierVersion Version
v)
where v :: Version
v = [Int] -> Version
mkVersion [Int
1]
thisVersion :: Version -> VersionRange
thisVersion :: Version -> VersionRange
thisVersion = Version -> VersionRange
ThisVersion
notThisVersion :: Version -> VersionRange
notThisVersion :: Version -> VersionRange
notThisVersion Version
v = VersionRange -> VersionRange -> VersionRange
UnionVersionRanges (Version -> VersionRange
EarlierVersion Version
v) (Version -> VersionRange
LaterVersion Version
v)
laterVersion :: Version -> VersionRange
laterVersion :: Version -> VersionRange
laterVersion = Version -> VersionRange
LaterVersion
orLaterVersion :: Version -> VersionRange
orLaterVersion :: Version -> VersionRange
orLaterVersion = Version -> VersionRange
OrLaterVersion
earlierVersion :: Version -> VersionRange
earlierVersion :: Version -> VersionRange
earlierVersion = Version -> VersionRange
EarlierVersion
orEarlierVersion :: Version -> VersionRange
orEarlierVersion :: Version -> VersionRange
orEarlierVersion = Version -> VersionRange
OrEarlierVersion
unionVersionRanges :: VersionRange -> VersionRange -> VersionRange
unionVersionRanges :: VersionRange -> VersionRange -> VersionRange
unionVersionRanges = VersionRange -> VersionRange -> VersionRange
UnionVersionRanges
intersectVersionRanges :: VersionRange -> VersionRange -> VersionRange
intersectVersionRanges :: VersionRange -> VersionRange -> VersionRange
intersectVersionRanges = VersionRange -> VersionRange -> VersionRange
IntersectVersionRanges
withinVersion :: Version -> VersionRange
withinVersion :: Version -> VersionRange
withinVersion = Version -> VersionRange
WildcardVersion
majorBoundVersion :: Version -> VersionRange
majorBoundVersion :: Version -> VersionRange
majorBoundVersion = Version -> VersionRange
MajorBoundVersion
data VersionRangeF a
= AnyVersionF
| ThisVersionF Version
| LaterVersionF Version
| OrLaterVersionF Version
| EarlierVersionF Version
| OrEarlierVersionF Version
| WildcardVersionF Version
| MajorBoundVersionF Version
| UnionVersionRangesF a a
| IntersectVersionRangesF a a
| VersionRangeParensF a
deriving ( Typeable (VersionRangeF a)
DataType
Constr
Typeable (VersionRangeF a)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRangeF a -> c (VersionRangeF a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VersionRangeF a))
-> (VersionRangeF a -> Constr)
-> (VersionRangeF a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (VersionRangeF a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VersionRangeF a)))
-> ((forall b. Data b => b -> b)
-> VersionRangeF a -> VersionRangeF a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> VersionRangeF a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> VersionRangeF a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a))
-> Data (VersionRangeF a)
VersionRangeF a -> DataType
VersionRangeF a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (VersionRangeF a))
(forall b. Data b => b -> b) -> VersionRangeF a -> VersionRangeF a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRangeF a -> c (VersionRangeF a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VersionRangeF a)
forall {a}. Data a => Typeable (VersionRangeF a)
forall a. Data a => VersionRangeF a -> DataType
forall a. Data a => VersionRangeF a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> VersionRangeF a -> VersionRangeF a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> VersionRangeF a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> VersionRangeF a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VersionRangeF a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRangeF a -> c (VersionRangeF a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (VersionRangeF a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VersionRangeF a))
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) -> VersionRangeF a -> u
forall u. (forall d. Data d => d -> u) -> VersionRangeF a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VersionRangeF a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRangeF a -> c (VersionRangeF a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (VersionRangeF a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VersionRangeF a))
$cVersionRangeParensF :: Constr
$cIntersectVersionRangesF :: Constr
$cUnionVersionRangesF :: Constr
$cMajorBoundVersionF :: Constr
$cWildcardVersionF :: Constr
$cOrEarlierVersionF :: Constr
$cEarlierVersionF :: Constr
$cOrLaterVersionF :: Constr
$cLaterVersionF :: Constr
$cThisVersionF :: Constr
$cAnyVersionF :: Constr
$tVersionRangeF :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a)
gmapMp :: (forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a)
gmapM :: (forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> VersionRangeF a -> m (VersionRangeF a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> VersionRangeF a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> VersionRangeF a -> u
gmapQ :: (forall d. Data d => d -> u) -> VersionRangeF a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> VersionRangeF a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VersionRangeF a -> r
gmapT :: (forall b. Data b => b -> b) -> VersionRangeF a -> VersionRangeF a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> VersionRangeF a -> VersionRangeF a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VersionRangeF a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (VersionRangeF a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (VersionRangeF a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (VersionRangeF a))
dataTypeOf :: VersionRangeF a -> DataType
$cdataTypeOf :: forall a. Data a => VersionRangeF a -> DataType
toConstr :: VersionRangeF a -> Constr
$ctoConstr :: forall a. Data a => VersionRangeF a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VersionRangeF a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (VersionRangeF a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRangeF a -> c (VersionRangeF a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VersionRangeF a -> c (VersionRangeF a)
Evidence bound by a type signature of the constraint type Typeable t
External instance of the constraint type Data Version
External instance of the constraint type Data Version
External instance of the constraint type forall a. Data a => Typeable a
Evidence bound by a type signature of the constraint type Data a
External instance of the constraint type Data Version
External instance of the constraint type forall a. Data a => Typeable a
External instance of the constraint type forall a. Data a => Typeable a
Evidence bound by a type signature of the constraint type Data a
Evidence bound by a type signature of the constraint type Data a
Data, VersionRangeF a -> VersionRangeF a -> Bool
(VersionRangeF a -> VersionRangeF a -> Bool)
-> (VersionRangeF a -> VersionRangeF a -> Bool)
-> Eq (VersionRangeF a)
forall a. Eq a => VersionRangeF a -> VersionRangeF a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionRangeF a -> VersionRangeF a -> Bool
$c/= :: forall a. Eq a => VersionRangeF a -> VersionRangeF a -> Bool
== :: VersionRangeF a -> VersionRangeF a -> Bool
$c== :: forall a. Eq a => VersionRangeF a -> VersionRangeF a -> Bool
External instance of the constraint type Eq Version
External instance of the constraint type Eq Version
Evidence bound by a type signature of the constraint type Eq a
Eq, (forall x. VersionRangeF a -> Rep (VersionRangeF a) x)
-> (forall x. Rep (VersionRangeF a) x -> VersionRangeF a)
-> Generic (VersionRangeF a)
forall x. Rep (VersionRangeF a) x -> VersionRangeF a
forall x. VersionRangeF a -> Rep (VersionRangeF a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (VersionRangeF a) x -> VersionRangeF a
forall a x. VersionRangeF a -> Rep (VersionRangeF a) x
$cto :: forall a x. Rep (VersionRangeF a) x -> VersionRangeF a
$cfrom :: forall a x. VersionRangeF a -> Rep (VersionRangeF a) x
Generic, ReadPrec [VersionRangeF a]
ReadPrec (VersionRangeF a)
Int -> ReadS (VersionRangeF a)
ReadS [VersionRangeF a]
(Int -> ReadS (VersionRangeF a))
-> ReadS [VersionRangeF a]
-> ReadPrec (VersionRangeF a)
-> ReadPrec [VersionRangeF a]
-> Read (VersionRangeF a)
forall a. Read a => ReadPrec [VersionRangeF a]
forall a. Read a => ReadPrec (VersionRangeF a)
forall a. Read a => Int -> ReadS (VersionRangeF a)
forall a. Read a => ReadS [VersionRangeF a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VersionRangeF a]
$creadListPrec :: forall a. Read a => ReadPrec [VersionRangeF a]
readPrec :: ReadPrec (VersionRangeF a)
$creadPrec :: forall a. Read a => ReadPrec (VersionRangeF a)
readList :: ReadS [VersionRangeF a]
$creadList :: forall a. Read a => ReadS [VersionRangeF a]
readsPrec :: Int -> ReadS (VersionRangeF a)
$creadsPrec :: forall a. Read a => Int -> ReadS (VersionRangeF a)
External instance of the constraint type Read Version
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Read Version
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type forall a. Read a => Read (VersionRangeF a)
Evidence bound by a type signature of the constraint type Read a
Read, Int -> VersionRangeF a -> ShowS
[VersionRangeF a] -> ShowS
VersionRangeF a -> String
(Int -> VersionRangeF a -> ShowS)
-> (VersionRangeF a -> String)
-> ([VersionRangeF a] -> ShowS)
-> Show (VersionRangeF a)
forall a. Show a => Int -> VersionRangeF a -> ShowS
forall a. Show a => [VersionRangeF a] -> ShowS
forall a. Show a => VersionRangeF a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VersionRangeF a] -> ShowS
$cshowList :: forall a. Show a => [VersionRangeF a] -> ShowS
show :: VersionRangeF a -> String
$cshow :: forall a. Show a => VersionRangeF a -> String
showsPrec :: Int -> VersionRangeF a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> VersionRangeF a -> ShowS
External instance of the constraint type Show Version
External instance of the constraint type Ord Int
External instance of the constraint type Show Version
External instance of the constraint type Ord Int
Evidence bound by a type signature of the constraint type Show a
Show, Typeable
, a -> VersionRangeF b -> VersionRangeF a
(a -> b) -> VersionRangeF a -> VersionRangeF b
(forall a b. (a -> b) -> VersionRangeF a -> VersionRangeF b)
-> (forall a b. a -> VersionRangeF b -> VersionRangeF a)
-> Functor VersionRangeF
forall a b. a -> VersionRangeF b -> VersionRangeF a
forall a b. (a -> b) -> VersionRangeF a -> VersionRangeF b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> VersionRangeF b -> VersionRangeF a
$c<$ :: forall a b. a -> VersionRangeF b -> VersionRangeF a
fmap :: (a -> b) -> VersionRangeF a -> VersionRangeF b
$cfmap :: forall a b. (a -> b) -> VersionRangeF a -> VersionRangeF b
Functor, VersionRangeF a -> Bool
(a -> m) -> VersionRangeF a -> m
(a -> b -> b) -> b -> VersionRangeF a -> b
(forall m. Monoid m => VersionRangeF m -> m)
-> (forall m a. Monoid m => (a -> m) -> VersionRangeF a -> m)
-> (forall m a. Monoid m => (a -> m) -> VersionRangeF a -> m)
-> (forall a b. (a -> b -> b) -> b -> VersionRangeF a -> b)
-> (forall a b. (a -> b -> b) -> b -> VersionRangeF a -> b)
-> (forall b a. (b -> a -> b) -> b -> VersionRangeF a -> b)
-> (forall b a. (b -> a -> b) -> b -> VersionRangeF a -> b)
-> (forall a. (a -> a -> a) -> VersionRangeF a -> a)
-> (forall a. (a -> a -> a) -> VersionRangeF a -> a)
-> (forall a. VersionRangeF a -> [a])
-> (forall a. VersionRangeF a -> Bool)
-> (forall a. VersionRangeF a -> Int)
-> (forall a. Eq a => a -> VersionRangeF a -> Bool)
-> (forall a. Ord a => VersionRangeF a -> a)
-> (forall a. Ord a => VersionRangeF a -> a)
-> (forall a. Num a => VersionRangeF a -> a)
-> (forall a. Num a => VersionRangeF a -> a)
-> Foldable VersionRangeF
forall a. Eq a => a -> VersionRangeF a -> Bool
forall a. Num a => VersionRangeF a -> a
forall a. Ord a => VersionRangeF a -> a
forall m. Monoid m => VersionRangeF m -> m
forall a. VersionRangeF a -> Bool
forall a. VersionRangeF a -> Int
forall a. VersionRangeF a -> [a]
forall a. (a -> a -> a) -> VersionRangeF a -> a
forall m a. Monoid m => (a -> m) -> VersionRangeF a -> m
forall b a. (b -> a -> b) -> b -> VersionRangeF a -> b
forall a b. (a -> b -> b) -> b -> VersionRangeF a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: VersionRangeF a -> a
$cproduct :: forall a. Num a => VersionRangeF a -> a
sum :: VersionRangeF a -> a
$csum :: forall a. Num a => VersionRangeF a -> a
minimum :: VersionRangeF a -> a
$cminimum :: forall a. Ord a => VersionRangeF a -> a
maximum :: VersionRangeF a -> a
$cmaximum :: forall a. Ord a => VersionRangeF a -> a
elem :: a -> VersionRangeF a -> Bool
$celem :: forall a. Eq a => a -> VersionRangeF a -> Bool
length :: VersionRangeF a -> Int
$clength :: forall a. VersionRangeF a -> Int
null :: VersionRangeF a -> Bool
$cnull :: forall a. VersionRangeF a -> Bool
toList :: VersionRangeF a -> [a]
$ctoList :: forall a. VersionRangeF a -> [a]
foldl1 :: (a -> a -> a) -> VersionRangeF a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> VersionRangeF a -> a
foldr1 :: (a -> a -> a) -> VersionRangeF a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> VersionRangeF a -> a
foldl' :: (b -> a -> b) -> b -> VersionRangeF a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> VersionRangeF a -> b
foldl :: (b -> a -> b) -> b -> VersionRangeF a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> VersionRangeF a -> b
foldr' :: (a -> b -> b) -> b -> VersionRangeF a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> VersionRangeF a -> b
foldr :: (a -> b -> b) -> b -> VersionRangeF a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> VersionRangeF a -> b
foldMap' :: (a -> m) -> VersionRangeF a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> VersionRangeF a -> m
foldMap :: (a -> m) -> VersionRangeF a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> VersionRangeF a -> m
fold :: VersionRangeF m -> m
$cfold :: forall m. Monoid m => VersionRangeF m -> m
Evidence bound by a type signature of the constraint type Monoid m
Foldable, Functor VersionRangeF
Foldable VersionRangeF
Functor VersionRangeF
-> Foldable VersionRangeF
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> VersionRangeF a -> f (VersionRangeF b))
-> (forall (f :: * -> *) a.
Applicative f =>
VersionRangeF (f a) -> f (VersionRangeF a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> VersionRangeF a -> m (VersionRangeF b))
-> (forall (m :: * -> *) a.
Monad m =>
VersionRangeF (m a) -> m (VersionRangeF a))
-> Traversable VersionRangeF
(a -> f b) -> VersionRangeF a -> f (VersionRangeF b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
VersionRangeF (m a) -> m (VersionRangeF a)
forall (f :: * -> *) a.
Applicative f =>
VersionRangeF (f a) -> f (VersionRangeF a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> VersionRangeF a -> m (VersionRangeF b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> VersionRangeF a -> f (VersionRangeF b)
sequence :: VersionRangeF (m a) -> m (VersionRangeF a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
VersionRangeF (m a) -> m (VersionRangeF a)
mapM :: (a -> m b) -> VersionRangeF a -> m (VersionRangeF b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> VersionRangeF a -> m (VersionRangeF b)
sequenceA :: VersionRangeF (f a) -> f (VersionRangeF a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
VersionRangeF (f a) -> f (VersionRangeF a)
traverse :: (a -> f b) -> VersionRangeF a -> f (VersionRangeF b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> VersionRangeF a -> f (VersionRangeF b)
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
Evidence bound by a type signature of the constraint type Applicative f
Instance of class: Foldable of the constraint type Foldable VersionRangeF
Instance of class: Functor of the constraint type Functor VersionRangeF
Instance of class: Functor of the constraint type Functor VersionRangeF
Instance of class: Foldable of the constraint type Foldable VersionRangeF
Traversable )
projectVersionRange :: VersionRange -> VersionRangeF VersionRange
projectVersionRange :: VersionRange -> VersionRangeF VersionRange
projectVersionRange VersionRange
AnyVersion = VersionRangeF VersionRange
forall a. VersionRangeF a
AnyVersionF
projectVersionRange (ThisVersion Version
v) = Version -> VersionRangeF VersionRange
forall a. Version -> VersionRangeF a
ThisVersionF Version
v
projectVersionRange (LaterVersion Version
v) = Version -> VersionRangeF VersionRange
forall a. Version -> VersionRangeF a
LaterVersionF Version
v
projectVersionRange (OrLaterVersion Version
v) = Version -> VersionRangeF VersionRange
forall a. Version -> VersionRangeF a
OrLaterVersionF Version
v
projectVersionRange (EarlierVersion Version
v) = Version -> VersionRangeF VersionRange
forall a. Version -> VersionRangeF a
EarlierVersionF Version
v
projectVersionRange (OrEarlierVersion Version
v) = Version -> VersionRangeF VersionRange
forall a. Version -> VersionRangeF a
OrEarlierVersionF Version
v
projectVersionRange (WildcardVersion Version
v) = Version -> VersionRangeF VersionRange
forall a. Version -> VersionRangeF a
WildcardVersionF Version
v
projectVersionRange (MajorBoundVersion Version
v) = Version -> VersionRangeF VersionRange
forall a. Version -> VersionRangeF a
MajorBoundVersionF Version
v
projectVersionRange (UnionVersionRanges VersionRange
a VersionRange
b) = VersionRange -> VersionRange -> VersionRangeF VersionRange
forall a. a -> a -> VersionRangeF a
UnionVersionRangesF VersionRange
a VersionRange
b
projectVersionRange (IntersectVersionRanges VersionRange
a VersionRange
b) = VersionRange -> VersionRange -> VersionRangeF VersionRange
forall a. a -> a -> VersionRangeF a
IntersectVersionRangesF VersionRange
a VersionRange
b
projectVersionRange (VersionRangeParens VersionRange
a) = VersionRange -> VersionRangeF VersionRange
forall a. a -> VersionRangeF a
VersionRangeParensF VersionRange
a
cataVersionRange :: (VersionRangeF a -> a) -> VersionRange -> a
cataVersionRange :: (VersionRangeF a -> a) -> VersionRange -> a
cataVersionRange VersionRangeF a -> a
f = VersionRange -> a
c where c :: VersionRange -> a
c = VersionRangeF a -> a
f (VersionRangeF a -> a)
-> (VersionRange -> VersionRangeF a) -> VersionRange -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VersionRange -> a)
-> VersionRangeF VersionRange -> VersionRangeF a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type Functor VersionRangeF
fmap VersionRange -> a
c (VersionRangeF VersionRange -> VersionRangeF a)
-> (VersionRange -> VersionRangeF VersionRange)
-> VersionRange
-> VersionRangeF a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VersionRange -> VersionRangeF VersionRange
projectVersionRange
embedVersionRange :: VersionRangeF VersionRange -> VersionRange
embedVersionRange :: VersionRangeF VersionRange -> VersionRange
embedVersionRange VersionRangeF VersionRange
AnyVersionF = VersionRange
AnyVersion
embedVersionRange (ThisVersionF Version
v) = Version -> VersionRange
ThisVersion Version
v
embedVersionRange (LaterVersionF Version
v) = Version -> VersionRange
LaterVersion Version
v
embedVersionRange (OrLaterVersionF Version
v) = Version -> VersionRange
OrLaterVersion Version
v
embedVersionRange (EarlierVersionF Version
v) = Version -> VersionRange
EarlierVersion Version
v
embedVersionRange (OrEarlierVersionF Version
v) = Version -> VersionRange
OrEarlierVersion Version
v
embedVersionRange (WildcardVersionF Version
v) = Version -> VersionRange
WildcardVersion Version
v
embedVersionRange (MajorBoundVersionF Version
v) = Version -> VersionRange
MajorBoundVersion Version
v
embedVersionRange (UnionVersionRangesF VersionRange
a VersionRange
b) = VersionRange -> VersionRange -> VersionRange
UnionVersionRanges VersionRange
a VersionRange
b
embedVersionRange (IntersectVersionRangesF VersionRange
a VersionRange
b) = VersionRange -> VersionRange -> VersionRange
IntersectVersionRanges VersionRange
a VersionRange
b
embedVersionRange (VersionRangeParensF VersionRange
a) = VersionRange -> VersionRange
VersionRangeParens VersionRange
a
anaVersionRange :: (a -> VersionRangeF a) -> a -> VersionRange
anaVersionRange :: (a -> VersionRangeF a) -> a -> VersionRange
anaVersionRange a -> VersionRangeF a
g = a -> VersionRange
a where a :: a -> VersionRange
a = VersionRangeF VersionRange -> VersionRange
embedVersionRange (VersionRangeF VersionRange -> VersionRange)
-> (a -> VersionRangeF VersionRange) -> a -> VersionRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> VersionRange)
-> VersionRangeF a -> VersionRangeF VersionRange
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type Functor VersionRangeF
fmap a -> VersionRange
a (VersionRangeF a -> VersionRangeF VersionRange)
-> (a -> VersionRangeF a) -> a -> VersionRangeF VersionRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> VersionRangeF a
g
hyloVersionRange :: (VersionRangeF VersionRange -> VersionRange)
-> (VersionRange -> VersionRangeF VersionRange)
-> VersionRange -> VersionRange
hyloVersionRange :: (VersionRangeF VersionRange -> VersionRange)
-> (VersionRange -> VersionRangeF VersionRange)
-> VersionRange
-> VersionRange
hyloVersionRange VersionRangeF VersionRange -> VersionRange
f VersionRange -> VersionRangeF VersionRange
g = VersionRange -> VersionRange
h where h :: VersionRange -> VersionRange
h = VersionRangeF VersionRange -> VersionRange
f (VersionRangeF VersionRange -> VersionRange)
-> (VersionRange -> VersionRangeF VersionRange)
-> VersionRange
-> VersionRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VersionRange -> VersionRange)
-> VersionRangeF VersionRange -> VersionRangeF VersionRange
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type Functor VersionRangeF
fmap VersionRange -> VersionRange
h (VersionRangeF VersionRange -> VersionRangeF VersionRange)
-> (VersionRange -> VersionRangeF VersionRange)
-> VersionRange
-> VersionRangeF VersionRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VersionRange -> VersionRangeF VersionRange
g
instance Pretty VersionRange where
pretty :: VersionRange -> Doc
pretty = (Doc, Int) -> Doc
forall a b. (a, b) -> a
fst ((Doc, Int) -> Doc)
-> (VersionRange -> (Doc, Int)) -> VersionRange -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VersionRangeF (Doc, Int) -> (Doc, Int))
-> VersionRange -> (Doc, Int)
forall a. (VersionRangeF a -> a) -> VersionRange -> a
cataVersionRange VersionRangeF (Doc, Int) -> (Doc, Int)
forall {a}. (Ord a, Num a) => VersionRangeF (Doc, a) -> (Doc, Int)
External instance of the constraint type Num Int
External instance of the constraint type Ord Int
alg
where
alg :: VersionRangeF (Doc, a) -> (Doc, Int)
alg VersionRangeF (Doc, a)
AnyVersionF = (String -> Doc
Disp.text String
"-any", Int
0 :: Int)
alg (ThisVersionF Version
v) = (String -> Doc
Disp.text String
"==" Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty Version
pretty Version
v, Int
0)
alg (LaterVersionF Version
v) = (Char -> Doc
Disp.char Char
'>' Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty Version
pretty Version
v, Int
0)
alg (OrLaterVersionF Version
v) = (String -> Doc
Disp.text String
">=" Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty Version
pretty Version
v, Int
0)
alg (EarlierVersionF Version
v) = (Char -> Doc
Disp.char Char
'<' Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty Version
pretty Version
v, Int
0)
alg (OrEarlierVersionF Version
v) = (String -> Doc
Disp.text String
"<=" Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty Version
pretty Version
v, Int
0)
alg (WildcardVersionF Version
v) = (String -> Doc
Disp.text String
"==" Doc -> Doc -> Doc
<<>> Version -> Doc
dispWild Version
v, Int
0)
alg (MajorBoundVersionF Version
v) = (String -> Doc
Disp.text String
"^>=" Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty Version
pretty Version
v, Int
0)
alg (UnionVersionRangesF (Doc
r1, a
p1) (Doc
r2, a
p2)) =
(a -> a -> Doc -> Doc
forall {a}. Ord a => a -> a -> Doc -> Doc
Evidence bound by a type signature of the constraint type Ord a
punct a
1 a
p1 Doc
r1 Doc -> Doc -> Doc
<+> String -> Doc
Disp.text String
"||" Doc -> Doc -> Doc
<+> a -> a -> Doc -> Doc
forall {a}. Ord a => a -> a -> Doc -> Doc
Evidence bound by a type signature of the constraint type Ord a
punct a
2 a
p2 Doc
r2 , Int
2)
alg (IntersectVersionRangesF (Doc
r1, a
p1) (Doc
r2, a
p2)) =
(a -> a -> Doc -> Doc
forall {a}. Ord a => a -> a -> Doc -> Doc
Evidence bound by a type signature of the constraint type Ord a
punct a
0 a
p1 Doc
r1 Doc -> Doc -> Doc
<+> String -> Doc
Disp.text String
"&&" Doc -> Doc -> Doc
<+> a -> a -> Doc -> Doc
forall {a}. Ord a => a -> a -> Doc -> Doc
Evidence bound by a type signature of the constraint type Ord a
punct a
1 a
p2 Doc
r2 , Int
1)
alg (VersionRangeParensF (Doc
r, a
_)) =
(Doc -> Doc
Disp.parens Doc
r, Int
0)
dispWild :: Version -> Doc
dispWild 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))
Doc -> Doc -> Doc
<<>> String -> Doc
Disp.text String
".*"
punct :: a -> a -> Doc -> Doc
punct a
p a
p' | a
p a -> a -> Bool
forall a. Ord a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Ord a
< a
p' = Doc -> Doc
Disp.parens
| Bool
otherwise = Doc -> Doc
forall a. a -> a
id
instance Parsec VersionRange where
parsec :: m VersionRange
parsec = 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 :: * -> *). CabalParsing m => m Int
Evidence bound by a type signature of the constraint type CabalParsing m
versionDigitParser
versionRangeParser :: forall m. CabalParsing m => m Int -> m VersionRange
versionRangeParser :: m Int -> m VersionRange
versionRangeParser m Int
digitParser = m VersionRange
expr
where
expr :: m VersionRange
expr = 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
VersionRange
t <- m VersionRange
term
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
(do String
_ <- 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 ()
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
VersionRange
e <- m VersionRange
expr
VersionRange -> m VersionRange
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 (VersionRange -> VersionRange -> VersionRange
unionVersionRanges VersionRange
t VersionRange
e)
m VersionRange -> m VersionRange -> m VersionRange
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
<|>
VersionRange -> m VersionRange
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 VersionRange
t)
term :: m VersionRange
term = do VersionRange
f <- m VersionRange
factor
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
(do String
_ <- 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 ()
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
VersionRange
t <- m VersionRange
term
VersionRange -> m VersionRange
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 (VersionRange -> VersionRange -> VersionRange
intersectVersionRanges VersionRange
f VersionRange
t)
m VersionRange -> m VersionRange -> m VersionRange
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
<|>
VersionRange -> m VersionRange
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 VersionRange
f)
factor :: m VersionRange
factor = m VersionRange -> m VersionRange
forall {m :: * -> *}.
(Monad m, CharParsing m) =>
m VersionRange -> m VersionRange
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
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
parens m VersionRange
expr m VersionRange -> m VersionRange -> m VersionRange
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 VersionRange
prim
prim :: m VersionRange
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
"-" -> VersionRange
anyVersion VersionRange -> m String -> m VersionRange
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 VersionRange -> m VersionRange -> m VersionRange
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
<|> 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
"none" m String -> m VersionRange -> m VersionRange
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 VersionRange
noVersion'
String
"==" -> 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
(do (Bool
wild, Version
v) <- m (Bool, Version)
CabalParsing m => m (Bool, Version)
Evidence bound by a type signature of the constraint type CabalParsing m
verOrWild
VersionRange -> m VersionRange
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 (VersionRange -> m VersionRange) -> VersionRange -> m VersionRange
forall a b. (a -> b) -> a -> b
$ (if Bool
wild then Version -> VersionRange
withinVersion else Version -> VersionRange
thisVersion) Version
v
m VersionRange -> m VersionRange -> m VersionRange
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
<|>
((Version -> VersionRange) -> NonEmpty Version -> m VersionRange
forall {m :: * -> *} {a}.
CabalParsing m =>
(a -> VersionRange) -> NonEmpty a -> m VersionRange
Evidence bound by a type signature of the constraint type CabalParsing m
verSet' Version -> VersionRange
thisVersion (NonEmpty Version -> m VersionRange)
-> m (NonEmpty Version) -> m VersionRange
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> 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 (NonEmpty Version)
CabalParsing m => m (NonEmpty Version)
Evidence bound by a type signature of the constraint type CabalParsing m
verSet))
String
"^>=" -> 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
(do (Bool
wild, Version
v) <- m (Bool, Version)
CabalParsing m => m (Bool, Version)
Evidence bound by a type signature of the constraint type CabalParsing m
verOrWild
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> 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
when Bool
wild (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> m ()
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 ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$
String
"wild-card version after ^>= operator"
Version -> m VersionRange
forall {m :: * -> *}. CabalParsing m => Version -> m VersionRange
Evidence bound by a type signature of the constraint type CabalParsing m
majorBoundVersion' Version
v
m VersionRange -> m VersionRange -> m VersionRange
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
<|>
((Version -> VersionRange) -> NonEmpty Version -> m VersionRange
forall {m :: * -> *} {a}.
CabalParsing m =>
(a -> VersionRange) -> NonEmpty a -> m VersionRange
Evidence bound by a type signature of the constraint type CabalParsing m
verSet' Version -> VersionRange
majorBoundVersion (NonEmpty Version -> m VersionRange)
-> m (NonEmpty Version) -> m VersionRange
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> 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 (NonEmpty Version)
CabalParsing m => m (NonEmpty Version)
Evidence bound by a type signature of the constraint type CabalParsing m
verSet))
String
_ -> 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
(Bool
wild, Version
v) <- m (Bool, Version)
CabalParsing m => m (Bool, Version)
Evidence bound by a type signature of the constraint type CabalParsing m
verOrWild
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> 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
when Bool
wild (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> m ()
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 ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$
String
"wild-card version after non-== 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
case String
op of
String
">=" -> VersionRange -> m VersionRange
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 (VersionRange -> m VersionRange) -> VersionRange -> m VersionRange
forall a b. (a -> b) -> a -> b
$ Version -> VersionRange
orLaterVersion Version
v
String
"<" -> VersionRange -> m VersionRange
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 (VersionRange -> m VersionRange) -> VersionRange -> m VersionRange
forall a b. (a -> b) -> a -> b
$ Version -> VersionRange
earlierVersion Version
v
String
"<=" -> VersionRange -> m VersionRange
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 (VersionRange -> m VersionRange) -> VersionRange -> m VersionRange
forall a b. (a -> b) -> a -> b
$ Version -> VersionRange
orEarlierVersion Version
v
String
">" -> VersionRange -> m VersionRange
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 (VersionRange -> m VersionRange) -> VersionRange -> m VersionRange
forall a b. (a -> b) -> a -> b
$ Version -> VersionRange
laterVersion Version
v
String
_ -> String -> m VersionRange
forall (m :: * -> *) a. MonadFail m => String -> m a
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadFail m
Evidence bound by a type signature of the constraint type CabalParsing m
fail (String -> m VersionRange) -> String -> m VersionRange
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
noVersion' :: m VersionRange
noVersion' = 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
CabalSpecV1_22
then VersionRange -> m VersionRange
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 VersionRange
noVersion
else String -> m VersionRange
forall (m :: * -> *) a. MonadFail m => String -> m a
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadFail m
Evidence bound by a type signature of the constraint type CabalParsing m
fail (String -> m VersionRange) -> String -> m VersionRange
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords
[ String
"-none version range used."
, String
"To use this syntax the package needs to specify at least 'cabal-version: 1.22'."
, String
"Alternatively, if broader compatibility is important then use"
, String
"<0 or other empty range."
]
majorBoundVersion' :: Version -> m VersionRange
majorBoundVersion' Version
v = 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
CabalSpecV2_0
then VersionRange -> m VersionRange
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 (VersionRange -> m VersionRange) -> VersionRange -> m VersionRange
forall a b. (a -> b) -> a -> b
$ Version -> VersionRange
majorBoundVersion Version
v
else String -> m VersionRange
forall (m :: * -> *) a. MonadFail m => String -> m a
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadFail m
Evidence bound by a type signature of the constraint type CabalParsing m
fail (String -> m VersionRange) -> String -> m VersionRange
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords
[ String
"major bounded version syntax (caret, ^>=) used."
, String
"To use this syntax the package need to specify at least 'cabal-version: 2.0'."
, String
"Alternatively, if broader compatibility is important then use:"
, VersionRange -> String
forall a. Pretty a => a -> String
Instance of class: Pretty of the constraint type Pretty VersionRange
prettyShow (VersionRange -> String) -> VersionRange -> String
forall a b. (a -> b) -> a -> b
$ VersionRange -> VersionRange
eliminateMajorBoundSyntax (VersionRange -> VersionRange) -> VersionRange -> VersionRange
forall a b. (a -> b) -> a -> b
$ Version -> VersionRange
majorBoundVersion Version
v
]
where
eliminateMajorBoundSyntax :: VersionRange -> VersionRange
eliminateMajorBoundSyntax = (VersionRangeF VersionRange -> VersionRange)
-> (VersionRange -> VersionRangeF VersionRange)
-> VersionRange
-> VersionRange
hyloVersionRange VersionRangeF VersionRange -> VersionRange
embed VersionRange -> VersionRangeF VersionRange
projectVersionRange
embed :: VersionRangeF VersionRange -> VersionRange
embed (MajorBoundVersionF Version
u) = VersionRange -> VersionRange -> VersionRange
intersectVersionRanges
(Version -> VersionRange
orLaterVersion Version
u) (Version -> VersionRange
earlierVersion (Version -> Version
majorUpperBound Version
u))
embed VersionRangeF VersionRange
vr = VersionRangeF VersionRange -> VersionRange
embedVersionRange VersionRangeF VersionRange
vr
verSet' :: (a -> VersionRange) -> NonEmpty a -> m VersionRange
verSet' a -> VersionRange
op NonEmpty a
vs = 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 VersionRange -> m VersionRange
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 (VersionRange -> m VersionRange) -> VersionRange -> m VersionRange
forall a b. (a -> b) -> a -> b
$ (VersionRange -> VersionRange -> VersionRange)
-> NonEmpty VersionRange -> VersionRange
forall a. (a -> a -> a) -> NonEmpty a -> a
foldr1 VersionRange -> VersionRange -> VersionRange
unionVersionRanges ((a -> VersionRange) -> NonEmpty a -> NonEmpty VersionRange
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor NonEmpty
fmap a -> VersionRange
op NonEmpty a
vs)
else String -> m VersionRange
forall (m :: * -> *) a. MonadFail m => String -> m a
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadFail m
Evidence bound by a type signature of the constraint type CabalParsing m
fail (String -> m VersionRange) -> String -> m VersionRange
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords
[ String
"version set syntax used."
, String
"To use this syntax the package needs to specify at least 'cabal-version: 3.0'."
, String
"Alternatively, if broader compatibility is important then use"
, String
"a series of single version constraints joined with the || operator:"
, VersionRange -> String
forall a. Pretty a => a -> String
Instance of class: Pretty of the constraint type Pretty VersionRange
prettyShow ((VersionRange -> VersionRange -> VersionRange)
-> NonEmpty VersionRange -> VersionRange
forall a. (a -> a -> a) -> NonEmpty a -> a
foldr1 VersionRange -> VersionRange -> VersionRange
unionVersionRanges ((a -> VersionRange) -> NonEmpty a -> NonEmpty VersionRange
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor NonEmpty
fmap a -> VersionRange
op NonEmpty a
vs))
]
verSet :: CabalParsing m => m (NonEmpty Version)
verSet :: m (NonEmpty Version)
verSet = do
Char
_ <- 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 ()
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
NonEmpty Version
vs <- m Version -> m () -> m (NonEmpty Version)
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 Version
CabalParsing m => m Version
Evidence bound by a type signature of the constraint type CabalParsing m
verPlain 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 ()
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 (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)
Char
_ <- 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
'}'
NonEmpty Version -> m (NonEmpty Version)
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 NonEmpty Version
vs
verPlain :: CabalParsing m => m Version
verPlain :: m Version
verPlain = [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
digitParser (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
'.')
verOrWild :: CabalParsing m => m (Bool, Version)
verOrWild :: m (Bool, Version)
verOrWild = do
Int
x <- m Int
digitParser
DList Int -> m (Bool, Version)
CabalParsing m => DList Int -> m (Bool, Version)
Evidence bound by a type signature of the constraint type CabalParsing m
verLoop (Int -> DList Int
forall a. a -> DList a
DList.singleton Int
x)
verLoop :: CabalParsing m => DList.DList Int -> m (Bool, Version)
verLoop :: DList Int -> m (Bool, Version)
verLoop DList Int
acc = DList Int -> m (Bool, Version)
CabalParsing m => DList Int -> m (Bool, Version)
Evidence bound by a type signature of the constraint type CabalParsing m
verLoop' DList Int
acc
m (Bool, Version) -> m (Bool, Version) -> m (Bool, Version)
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 ()
CabalParsing m => m ()
Evidence bound by a type signature of the constraint type CabalParsing m
tags m () -> m (Bool, Version) -> m (Bool, Version)
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
*> (Bool, Version) -> m (Bool, Version)
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 (Bool
False, [Int] -> Version
mkVersion (DList Int -> [Int]
forall a. DList a -> [a]
DList.toList DList Int
acc)))
verLoop' :: CabalParsing m => DList.DList Int -> m (Bool, Version)
verLoop' :: DList Int -> m (Bool, Version)
verLoop' DList Int
acc = do
Char
_ <- 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
'.'
let digit :: m (Bool, Version)
digit = m Int
digitParser m Int -> (Int -> m (Bool, Version)) -> m (Bool, Version)
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
>>= DList Int -> m (Bool, Version)
CabalParsing m => DList Int -> m (Bool, Version)
Evidence bound by a type signature of the constraint type CabalParsing m
verLoop (DList Int -> m (Bool, Version))
-> (Int -> DList Int) -> Int -> m (Bool, Version)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DList Int -> Int -> DList Int
forall a. DList a -> a -> DList a
DList.snoc DList Int
acc
let wild :: m (Bool, Version)
wild = (Bool
True, [Int] -> Version
mkVersion (DList Int -> [Int]
forall a. DList a -> [a]
DList.toList DList Int
acc)) (Bool, Version) -> m Char -> m (Bool, Version)
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
<$ 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 (Bool, Version)
digit m (Bool, Version) -> m (Bool, Version) -> m (Bool, Version)
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 (Bool, Version)
wild
parens :: m VersionRange -> m VersionRange
parens m VersionRange
p = m () -> m () -> m VersionRange -> m VersionRange
forall (m :: * -> *) bra ket a.
Applicative m =>
m bra -> m ket -> m a -> m a
External instance of the constraint type forall (m :: * -> *). Monad m => Applicative m
Evidence bound by a type signature of the constraint type Monad m
P.between
((Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
Evidence bound by a type signature of the constraint type CharParsing 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
Evidence bound by a type signature of the constraint type CharParsing m
P.<?> String
"opening paren") m Char -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Evidence bound by a type signature of the constraint type Monad m
>> m ()
forall (m :: * -> *). CharParsing m => m ()
Evidence bound by a type signature of the constraint type CharParsing m
P.spaces)
(Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
Evidence bound by a type signature of the constraint type CharParsing m
P.char Char
')' m Char -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
Evidence bound by a type signature of the constraint type Monad m
>> m ()
forall (m :: * -> *). CharParsing m => m ()
Evidence bound by a type signature of the constraint type CharParsing m
P.spaces)
(do VersionRange
a <- m VersionRange
p
m ()
forall (m :: * -> *). CharParsing m => m ()
Evidence bound by a type signature of the constraint type CharParsing m
P.spaces
VersionRange -> m VersionRange
forall (m :: * -> *) a. Monad m => a -> m a
Evidence bound by a type signature of the constraint type Monad m
return (VersionRange -> VersionRange
VersionRangeParens VersionRange
a))
tags :: CabalParsing m => m ()
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"
majorUpperBound :: Version -> Version
majorUpperBound :: Version -> Version
majorUpperBound = ([Int] -> [Int]) -> Version -> Version
alterVersion (([Int] -> [Int]) -> Version -> Version)
-> ([Int] -> [Int]) -> Version -> Version
forall a b. (a -> b) -> a -> b
$ \[Int]
numbers -> case [Int]
numbers of
[] -> [Int
0,Int
1]
[Int
m1] -> [Int
m1,Int
1]
(Int
m1:Int
m2:[Int]
_) -> [Int
m1,Int
m2Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
1]