{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Distribution.Types.SourceRepo (
SourceRepo(..),
RepoKind(..),
RepoType(..),
KnownRepoType (..),
knownRepoTypes,
emptySourceRepo,
classifyRepoType,
classifyRepoKind,
) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Utils.Generic (lowercase)
import Distribution.Pretty
import Distribution.Parsec
import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as Disp
import qualified Data.Map.Strict as M
data SourceRepo = SourceRepo {
SourceRepo -> RepoKind
repoKind :: RepoKind,
SourceRepo -> Maybe RepoType
repoType :: Maybe RepoType,
SourceRepo -> Maybe String
repoLocation :: Maybe String,
SourceRepo -> Maybe String
repoModule :: Maybe String,
SourceRepo -> Maybe String
repoBranch :: Maybe String,
SourceRepo -> Maybe String
repoTag :: Maybe String,
SourceRepo -> Maybe String
repoSubdir :: Maybe FilePath
}
deriving (SourceRepo -> SourceRepo -> Bool
(SourceRepo -> SourceRepo -> Bool)
-> (SourceRepo -> SourceRepo -> Bool) -> Eq SourceRepo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SourceRepo -> SourceRepo -> Bool
== :: SourceRepo -> SourceRepo -> Bool
$c/= :: SourceRepo -> SourceRepo -> Bool
/= :: SourceRepo -> SourceRepo -> Bool
Eq, Eq SourceRepo
Eq SourceRepo
-> (SourceRepo -> SourceRepo -> Ordering)
-> (SourceRepo -> SourceRepo -> Bool)
-> (SourceRepo -> SourceRepo -> Bool)
-> (SourceRepo -> SourceRepo -> Bool)
-> (SourceRepo -> SourceRepo -> Bool)
-> (SourceRepo -> SourceRepo -> SourceRepo)
-> (SourceRepo -> SourceRepo -> SourceRepo)
-> Ord SourceRepo
SourceRepo -> SourceRepo -> Bool
SourceRepo -> SourceRepo -> Ordering
SourceRepo -> SourceRepo -> SourceRepo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SourceRepo -> SourceRepo -> Ordering
compare :: SourceRepo -> SourceRepo -> Ordering
$c< :: SourceRepo -> SourceRepo -> Bool
< :: SourceRepo -> SourceRepo -> Bool
$c<= :: SourceRepo -> SourceRepo -> Bool
<= :: SourceRepo -> SourceRepo -> Bool
$c> :: SourceRepo -> SourceRepo -> Bool
> :: SourceRepo -> SourceRepo -> Bool
$c>= :: SourceRepo -> SourceRepo -> Bool
>= :: SourceRepo -> SourceRepo -> Bool
$cmax :: SourceRepo -> SourceRepo -> SourceRepo
max :: SourceRepo -> SourceRepo -> SourceRepo
$cmin :: SourceRepo -> SourceRepo -> SourceRepo
min :: SourceRepo -> SourceRepo -> SourceRepo
Ord, (forall x. SourceRepo -> Rep SourceRepo x)
-> (forall x. Rep SourceRepo x -> SourceRepo) -> Generic SourceRepo
forall x. Rep SourceRepo x -> SourceRepo
forall x. SourceRepo -> Rep SourceRepo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SourceRepo -> Rep SourceRepo x
from :: forall x. SourceRepo -> Rep SourceRepo x
$cto :: forall x. Rep SourceRepo x -> SourceRepo
to :: forall x. Rep SourceRepo x -> SourceRepo
Generic, ReadPrec [SourceRepo]
ReadPrec SourceRepo
Int -> ReadS SourceRepo
ReadS [SourceRepo]
(Int -> ReadS SourceRepo)
-> ReadS [SourceRepo]
-> ReadPrec SourceRepo
-> ReadPrec [SourceRepo]
-> Read SourceRepo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SourceRepo
readsPrec :: Int -> ReadS SourceRepo
$creadList :: ReadS [SourceRepo]
readList :: ReadS [SourceRepo]
$creadPrec :: ReadPrec SourceRepo
readPrec :: ReadPrec SourceRepo
$creadListPrec :: ReadPrec [SourceRepo]
readListPrec :: ReadPrec [SourceRepo]
Read, Int -> SourceRepo -> ShowS
[SourceRepo] -> ShowS
SourceRepo -> String
(Int -> SourceRepo -> ShowS)
-> (SourceRepo -> String)
-> ([SourceRepo] -> ShowS)
-> Show SourceRepo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SourceRepo -> ShowS
showsPrec :: Int -> SourceRepo -> ShowS
$cshow :: SourceRepo -> String
show :: SourceRepo -> String
$cshowList :: [SourceRepo] -> ShowS
showList :: [SourceRepo] -> ShowS
Show, Typeable, Typeable SourceRepo
Typeable SourceRepo
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourceRepo -> c SourceRepo)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourceRepo)
-> (SourceRepo -> Constr)
-> (SourceRepo -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SourceRepo))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SourceRepo))
-> ((forall b. Data b => b -> b) -> SourceRepo -> SourceRepo)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SourceRepo -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SourceRepo -> r)
-> (forall u. (forall d. Data d => d -> u) -> SourceRepo -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SourceRepo -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo)
-> Data SourceRepo
SourceRepo -> Constr
SourceRepo -> DataType
(forall b. Data b => b -> b) -> SourceRepo -> SourceRepo
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) -> SourceRepo -> u
forall u. (forall d. Data d => d -> u) -> SourceRepo -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SourceRepo -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SourceRepo -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourceRepo
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourceRepo -> c SourceRepo
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SourceRepo)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceRepo)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourceRepo -> c SourceRepo
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourceRepo -> c SourceRepo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourceRepo
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourceRepo
$ctoConstr :: SourceRepo -> Constr
toConstr :: SourceRepo -> Constr
$cdataTypeOf :: SourceRepo -> DataType
dataTypeOf :: SourceRepo -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SourceRepo)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SourceRepo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceRepo)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceRepo)
$cgmapT :: (forall b. Data b => b -> b) -> SourceRepo -> SourceRepo
gmapT :: (forall b. Data b => b -> b) -> SourceRepo -> SourceRepo
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SourceRepo -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SourceRepo -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SourceRepo -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SourceRepo -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SourceRepo -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> SourceRepo -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SourceRepo -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SourceRepo -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo
Data)
emptySourceRepo :: RepoKind -> SourceRepo
emptySourceRepo :: RepoKind -> SourceRepo
emptySourceRepo RepoKind
kind = SourceRepo
{ repoKind :: RepoKind
repoKind = RepoKind
kind
, repoType :: Maybe RepoType
repoType = Maybe RepoType
forall a. Maybe a
Nothing
, repoLocation :: Maybe String
repoLocation = Maybe String
forall a. Maybe a
Nothing
, repoModule :: Maybe String
repoModule = Maybe String
forall a. Maybe a
Nothing
, repoBranch :: Maybe String
repoBranch = Maybe String
forall a. Maybe a
Nothing
, repoTag :: Maybe String
repoTag = Maybe String
forall a. Maybe a
Nothing
, repoSubdir :: Maybe String
repoSubdir = Maybe String
forall a. Maybe a
Nothing
}
instance Binary SourceRepo
instance Structured SourceRepo
instance NFData SourceRepo where rnf :: SourceRepo -> ()
rnf = SourceRepo -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
data RepoKind =
RepoHead
| RepoThis
| RepoKindUnknown String
deriving (RepoKind -> RepoKind -> Bool
(RepoKind -> RepoKind -> Bool)
-> (RepoKind -> RepoKind -> Bool) -> Eq RepoKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RepoKind -> RepoKind -> Bool
== :: RepoKind -> RepoKind -> Bool
$c/= :: RepoKind -> RepoKind -> Bool
/= :: RepoKind -> RepoKind -> Bool
Eq, (forall x. RepoKind -> Rep RepoKind x)
-> (forall x. Rep RepoKind x -> RepoKind) -> Generic RepoKind
forall x. Rep RepoKind x -> RepoKind
forall x. RepoKind -> Rep RepoKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RepoKind -> Rep RepoKind x
from :: forall x. RepoKind -> Rep RepoKind x
$cto :: forall x. Rep RepoKind x -> RepoKind
to :: forall x. Rep RepoKind x -> RepoKind
Generic, Eq RepoKind
Eq RepoKind
-> (RepoKind -> RepoKind -> Ordering)
-> (RepoKind -> RepoKind -> Bool)
-> (RepoKind -> RepoKind -> Bool)
-> (RepoKind -> RepoKind -> Bool)
-> (RepoKind -> RepoKind -> Bool)
-> (RepoKind -> RepoKind -> RepoKind)
-> (RepoKind -> RepoKind -> RepoKind)
-> Ord RepoKind
RepoKind -> RepoKind -> Bool
RepoKind -> RepoKind -> Ordering
RepoKind -> RepoKind -> RepoKind
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RepoKind -> RepoKind -> Ordering
compare :: RepoKind -> RepoKind -> Ordering
$c< :: RepoKind -> RepoKind -> Bool
< :: RepoKind -> RepoKind -> Bool
$c<= :: RepoKind -> RepoKind -> Bool
<= :: RepoKind -> RepoKind -> Bool
$c> :: RepoKind -> RepoKind -> Bool
> :: RepoKind -> RepoKind -> Bool
$c>= :: RepoKind -> RepoKind -> Bool
>= :: RepoKind -> RepoKind -> Bool
$cmax :: RepoKind -> RepoKind -> RepoKind
max :: RepoKind -> RepoKind -> RepoKind
$cmin :: RepoKind -> RepoKind -> RepoKind
min :: RepoKind -> RepoKind -> RepoKind
Ord, ReadPrec [RepoKind]
ReadPrec RepoKind
Int -> ReadS RepoKind
ReadS [RepoKind]
(Int -> ReadS RepoKind)
-> ReadS [RepoKind]
-> ReadPrec RepoKind
-> ReadPrec [RepoKind]
-> Read RepoKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RepoKind
readsPrec :: Int -> ReadS RepoKind
$creadList :: ReadS [RepoKind]
readList :: ReadS [RepoKind]
$creadPrec :: ReadPrec RepoKind
readPrec :: ReadPrec RepoKind
$creadListPrec :: ReadPrec [RepoKind]
readListPrec :: ReadPrec [RepoKind]
Read, Int -> RepoKind -> ShowS
[RepoKind] -> ShowS
RepoKind -> String
(Int -> RepoKind -> ShowS)
-> (RepoKind -> String) -> ([RepoKind] -> ShowS) -> Show RepoKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RepoKind -> ShowS
showsPrec :: Int -> RepoKind -> ShowS
$cshow :: RepoKind -> String
show :: RepoKind -> String
$cshowList :: [RepoKind] -> ShowS
showList :: [RepoKind] -> ShowS
Show, Typeable, Typeable RepoKind
Typeable RepoKind
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoKind -> c RepoKind)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoKind)
-> (RepoKind -> Constr)
-> (RepoKind -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoKind))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoKind))
-> ((forall b. Data b => b -> b) -> RepoKind -> RepoKind)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoKind -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoKind -> r)
-> (forall u. (forall d. Data d => d -> u) -> RepoKind -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> RepoKind -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind)
-> Data RepoKind
RepoKind -> Constr
RepoKind -> DataType
(forall b. Data b => b -> b) -> RepoKind -> RepoKind
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) -> RepoKind -> u
forall u. (forall d. Data d => d -> u) -> RepoKind -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoKind -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoKind -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoKind
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoKind -> c RepoKind
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoKind)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoKind)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoKind -> c RepoKind
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoKind -> c RepoKind
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoKind
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoKind
$ctoConstr :: RepoKind -> Constr
toConstr :: RepoKind -> Constr
$cdataTypeOf :: RepoKind -> DataType
dataTypeOf :: RepoKind -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoKind)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoKind)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoKind)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoKind)
$cgmapT :: (forall b. Data b => b -> b) -> RepoKind -> RepoKind
gmapT :: (forall b. Data b => b -> b) -> RepoKind -> RepoKind
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoKind -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoKind -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoKind -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoKind -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RepoKind -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RepoKind -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RepoKind -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RepoKind -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoKind -> m RepoKind
Data)
instance Binary RepoKind
instance Structured RepoKind
instance NFData RepoKind where rnf :: RepoKind -> ()
rnf = RepoKind -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
data KnownRepoType = Darcs | Git | SVN | CVS
| Mercurial | GnuArch | Bazaar | Monotone
| Pijul
deriving (KnownRepoType -> KnownRepoType -> Bool
(KnownRepoType -> KnownRepoType -> Bool)
-> (KnownRepoType -> KnownRepoType -> Bool) -> Eq KnownRepoType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KnownRepoType -> KnownRepoType -> Bool
== :: KnownRepoType -> KnownRepoType -> Bool
$c/= :: KnownRepoType -> KnownRepoType -> Bool
/= :: KnownRepoType -> KnownRepoType -> Bool
Eq, (forall x. KnownRepoType -> Rep KnownRepoType x)
-> (forall x. Rep KnownRepoType x -> KnownRepoType)
-> Generic KnownRepoType
forall x. Rep KnownRepoType x -> KnownRepoType
forall x. KnownRepoType -> Rep KnownRepoType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. KnownRepoType -> Rep KnownRepoType x
from :: forall x. KnownRepoType -> Rep KnownRepoType x
$cto :: forall x. Rep KnownRepoType x -> KnownRepoType
to :: forall x. Rep KnownRepoType x -> KnownRepoType
Generic, Eq KnownRepoType
Eq KnownRepoType
-> (KnownRepoType -> KnownRepoType -> Ordering)
-> (KnownRepoType -> KnownRepoType -> Bool)
-> (KnownRepoType -> KnownRepoType -> Bool)
-> (KnownRepoType -> KnownRepoType -> Bool)
-> (KnownRepoType -> KnownRepoType -> Bool)
-> (KnownRepoType -> KnownRepoType -> KnownRepoType)
-> (KnownRepoType -> KnownRepoType -> KnownRepoType)
-> Ord KnownRepoType
KnownRepoType -> KnownRepoType -> Bool
KnownRepoType -> KnownRepoType -> Ordering
KnownRepoType -> KnownRepoType -> KnownRepoType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: KnownRepoType -> KnownRepoType -> Ordering
compare :: KnownRepoType -> KnownRepoType -> Ordering
$c< :: KnownRepoType -> KnownRepoType -> Bool
< :: KnownRepoType -> KnownRepoType -> Bool
$c<= :: KnownRepoType -> KnownRepoType -> Bool
<= :: KnownRepoType -> KnownRepoType -> Bool
$c> :: KnownRepoType -> KnownRepoType -> Bool
> :: KnownRepoType -> KnownRepoType -> Bool
$c>= :: KnownRepoType -> KnownRepoType -> Bool
>= :: KnownRepoType -> KnownRepoType -> Bool
$cmax :: KnownRepoType -> KnownRepoType -> KnownRepoType
max :: KnownRepoType -> KnownRepoType -> KnownRepoType
$cmin :: KnownRepoType -> KnownRepoType -> KnownRepoType
min :: KnownRepoType -> KnownRepoType -> KnownRepoType
Ord, ReadPrec [KnownRepoType]
ReadPrec KnownRepoType
Int -> ReadS KnownRepoType
ReadS [KnownRepoType]
(Int -> ReadS KnownRepoType)
-> ReadS [KnownRepoType]
-> ReadPrec KnownRepoType
-> ReadPrec [KnownRepoType]
-> Read KnownRepoType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS KnownRepoType
readsPrec :: Int -> ReadS KnownRepoType
$creadList :: ReadS [KnownRepoType]
readList :: ReadS [KnownRepoType]
$creadPrec :: ReadPrec KnownRepoType
readPrec :: ReadPrec KnownRepoType
$creadListPrec :: ReadPrec [KnownRepoType]
readListPrec :: ReadPrec [KnownRepoType]
Read, Int -> KnownRepoType -> ShowS
[KnownRepoType] -> ShowS
KnownRepoType -> String
(Int -> KnownRepoType -> ShowS)
-> (KnownRepoType -> String)
-> ([KnownRepoType] -> ShowS)
-> Show KnownRepoType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KnownRepoType -> ShowS
showsPrec :: Int -> KnownRepoType -> ShowS
$cshow :: KnownRepoType -> String
show :: KnownRepoType -> String
$cshowList :: [KnownRepoType] -> ShowS
showList :: [KnownRepoType] -> ShowS
Show, Typeable, Typeable KnownRepoType
Typeable KnownRepoType
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KnownRepoType -> c KnownRepoType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KnownRepoType)
-> (KnownRepoType -> Constr)
-> (KnownRepoType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KnownRepoType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c KnownRepoType))
-> ((forall b. Data b => b -> b) -> KnownRepoType -> KnownRepoType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> KnownRepoType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> KnownRepoType -> r)
-> (forall u. (forall d. Data d => d -> u) -> KnownRepoType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> KnownRepoType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType)
-> Data KnownRepoType
KnownRepoType -> Constr
KnownRepoType -> DataType
(forall b. Data b => b -> b) -> KnownRepoType -> KnownRepoType
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) -> KnownRepoType -> u
forall u. (forall d. Data d => d -> u) -> KnownRepoType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> KnownRepoType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> KnownRepoType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KnownRepoType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KnownRepoType -> c KnownRepoType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KnownRepoType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c KnownRepoType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KnownRepoType -> c KnownRepoType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KnownRepoType -> c KnownRepoType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KnownRepoType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KnownRepoType
$ctoConstr :: KnownRepoType -> Constr
toConstr :: KnownRepoType -> Constr
$cdataTypeOf :: KnownRepoType -> DataType
dataTypeOf :: KnownRepoType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KnownRepoType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KnownRepoType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c KnownRepoType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c KnownRepoType)
$cgmapT :: (forall b. Data b => b -> b) -> KnownRepoType -> KnownRepoType
gmapT :: (forall b. Data b => b -> b) -> KnownRepoType -> KnownRepoType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> KnownRepoType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> KnownRepoType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> KnownRepoType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> KnownRepoType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> KnownRepoType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> KnownRepoType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> KnownRepoType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> KnownRepoType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KnownRepoType -> m KnownRepoType
Data, Int -> KnownRepoType
KnownRepoType -> Int
KnownRepoType -> [KnownRepoType]
KnownRepoType -> KnownRepoType
KnownRepoType -> KnownRepoType -> [KnownRepoType]
KnownRepoType -> KnownRepoType -> KnownRepoType -> [KnownRepoType]
(KnownRepoType -> KnownRepoType)
-> (KnownRepoType -> KnownRepoType)
-> (Int -> KnownRepoType)
-> (KnownRepoType -> Int)
-> (KnownRepoType -> [KnownRepoType])
-> (KnownRepoType -> KnownRepoType -> [KnownRepoType])
-> (KnownRepoType -> KnownRepoType -> [KnownRepoType])
-> (KnownRepoType
-> KnownRepoType -> KnownRepoType -> [KnownRepoType])
-> Enum KnownRepoType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: KnownRepoType -> KnownRepoType
succ :: KnownRepoType -> KnownRepoType
$cpred :: KnownRepoType -> KnownRepoType
pred :: KnownRepoType -> KnownRepoType
$ctoEnum :: Int -> KnownRepoType
toEnum :: Int -> KnownRepoType
$cfromEnum :: KnownRepoType -> Int
fromEnum :: KnownRepoType -> Int
$cenumFrom :: KnownRepoType -> [KnownRepoType]
enumFrom :: KnownRepoType -> [KnownRepoType]
$cenumFromThen :: KnownRepoType -> KnownRepoType -> [KnownRepoType]
enumFromThen :: KnownRepoType -> KnownRepoType -> [KnownRepoType]
$cenumFromTo :: KnownRepoType -> KnownRepoType -> [KnownRepoType]
enumFromTo :: KnownRepoType -> KnownRepoType -> [KnownRepoType]
$cenumFromThenTo :: KnownRepoType -> KnownRepoType -> KnownRepoType -> [KnownRepoType]
enumFromThenTo :: KnownRepoType -> KnownRepoType -> KnownRepoType -> [KnownRepoType]
Enum, KnownRepoType
KnownRepoType -> KnownRepoType -> Bounded KnownRepoType
forall a. a -> a -> Bounded a
$cminBound :: KnownRepoType
minBound :: KnownRepoType
$cmaxBound :: KnownRepoType
maxBound :: KnownRepoType
Bounded)
instance Binary KnownRepoType
instance Structured KnownRepoType
instance NFData KnownRepoType where rnf :: KnownRepoType -> ()
rnf = KnownRepoType -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Parsec KnownRepoType where
parsec :: forall (m :: * -> *). CabalParsing m => m KnownRepoType
parsec = do
String
str <- (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
P.munch1 Char -> Bool
isIdent
m KnownRepoType
-> (KnownRepoType -> m KnownRepoType)
-> Maybe KnownRepoType
-> m KnownRepoType
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(String -> m KnownRepoType
forall a. String -> m a
forall (m :: * -> *) a. Parsing m => String -> m a
P.unexpected (String -> m KnownRepoType) -> String -> m KnownRepoType
forall a b. (a -> b) -> a -> b
$ String
"Could not parse KnownRepoType from " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
str)
KnownRepoType -> m KnownRepoType
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(String -> Map String KnownRepoType -> Maybe KnownRepoType
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup String
str Map String KnownRepoType
knownRepoTypeMap)
instance Pretty KnownRepoType where
pretty :: KnownRepoType -> Doc
pretty = String -> Doc
Disp.text (String -> Doc)
-> (KnownRepoType -> String) -> KnownRepoType -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
lowercase ShowS -> (KnownRepoType -> String) -> KnownRepoType -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KnownRepoType -> String
forall a. Show a => a -> String
show
data RepoType = KnownRepoType KnownRepoType
| OtherRepoType String
deriving (RepoType -> RepoType -> Bool
(RepoType -> RepoType -> Bool)
-> (RepoType -> RepoType -> Bool) -> Eq RepoType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RepoType -> RepoType -> Bool
== :: RepoType -> RepoType -> Bool
$c/= :: RepoType -> RepoType -> Bool
/= :: RepoType -> RepoType -> Bool
Eq, (forall x. RepoType -> Rep RepoType x)
-> (forall x. Rep RepoType x -> RepoType) -> Generic RepoType
forall x. Rep RepoType x -> RepoType
forall x. RepoType -> Rep RepoType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RepoType -> Rep RepoType x
from :: forall x. RepoType -> Rep RepoType x
$cto :: forall x. Rep RepoType x -> RepoType
to :: forall x. Rep RepoType x -> RepoType
Generic, Eq RepoType
Eq RepoType
-> (RepoType -> RepoType -> Ordering)
-> (RepoType -> RepoType -> Bool)
-> (RepoType -> RepoType -> Bool)
-> (RepoType -> RepoType -> Bool)
-> (RepoType -> RepoType -> Bool)
-> (RepoType -> RepoType -> RepoType)
-> (RepoType -> RepoType -> RepoType)
-> Ord RepoType
RepoType -> RepoType -> Bool
RepoType -> RepoType -> Ordering
RepoType -> RepoType -> RepoType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RepoType -> RepoType -> Ordering
compare :: RepoType -> RepoType -> Ordering
$c< :: RepoType -> RepoType -> Bool
< :: RepoType -> RepoType -> Bool
$c<= :: RepoType -> RepoType -> Bool
<= :: RepoType -> RepoType -> Bool
$c> :: RepoType -> RepoType -> Bool
> :: RepoType -> RepoType -> Bool
$c>= :: RepoType -> RepoType -> Bool
>= :: RepoType -> RepoType -> Bool
$cmax :: RepoType -> RepoType -> RepoType
max :: RepoType -> RepoType -> RepoType
$cmin :: RepoType -> RepoType -> RepoType
min :: RepoType -> RepoType -> RepoType
Ord, ReadPrec [RepoType]
ReadPrec RepoType
Int -> ReadS RepoType
ReadS [RepoType]
(Int -> ReadS RepoType)
-> ReadS [RepoType]
-> ReadPrec RepoType
-> ReadPrec [RepoType]
-> Read RepoType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RepoType
readsPrec :: Int -> ReadS RepoType
$creadList :: ReadS [RepoType]
readList :: ReadS [RepoType]
$creadPrec :: ReadPrec RepoType
readPrec :: ReadPrec RepoType
$creadListPrec :: ReadPrec [RepoType]
readListPrec :: ReadPrec [RepoType]
Read, Int -> RepoType -> ShowS
[RepoType] -> ShowS
RepoType -> String
(Int -> RepoType -> ShowS)
-> (RepoType -> String) -> ([RepoType] -> ShowS) -> Show RepoType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RepoType -> ShowS
showsPrec :: Int -> RepoType -> ShowS
$cshow :: RepoType -> String
show :: RepoType -> String
$cshowList :: [RepoType] -> ShowS
showList :: [RepoType] -> ShowS
Show, Typeable, Typeable RepoType
Typeable RepoType
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoType -> c RepoType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoType)
-> (RepoType -> Constr)
-> (RepoType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoType))
-> ((forall b. Data b => b -> b) -> RepoType -> RepoType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoType -> r)
-> (forall u. (forall d. Data d => d -> u) -> RepoType -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> RepoType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType)
-> Data RepoType
RepoType -> Constr
RepoType -> DataType
(forall b. Data b => b -> b) -> RepoType -> RepoType
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) -> RepoType -> u
forall u. (forall d. Data d => d -> u) -> RepoType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoType -> c RepoType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoType -> c RepoType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoType -> c RepoType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoType
$ctoConstr :: RepoType -> Constr
toConstr :: RepoType -> Constr
$cdataTypeOf :: RepoType -> DataType
dataTypeOf :: RepoType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoType)
$cgmapT :: (forall b. Data b => b -> b) -> RepoType -> RepoType
gmapT :: (forall b. Data b => b -> b) -> RepoType -> RepoType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RepoType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RepoType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RepoType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RepoType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoType -> m RepoType
Data)
instance Binary RepoType
instance Structured RepoType
instance NFData RepoType where rnf :: RepoType -> ()
rnf = RepoType -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
knownRepoTypes :: [KnownRepoType]
knownRepoTypes :: [KnownRepoType]
knownRepoTypes = [KnownRepoType
forall a. Bounded a => a
minBound .. KnownRepoType
forall a. Bounded a => a
maxBound]
repoTypeAliases :: KnownRepoType -> [String]
repoTypeAliases :: KnownRepoType -> [String]
repoTypeAliases KnownRepoType
Bazaar = [String
"bzr"]
repoTypeAliases KnownRepoType
Mercurial = [String
"hg"]
repoTypeAliases KnownRepoType
GnuArch = [String
"arch"]
repoTypeAliases KnownRepoType
_ = []
instance Pretty RepoKind where
pretty :: RepoKind -> Doc
pretty RepoKind
RepoHead = String -> Doc
Disp.text String
"head"
pretty RepoKind
RepoThis = String -> Doc
Disp.text String
"this"
pretty (RepoKindUnknown String
other) = String -> Doc
Disp.text String
other
instance Parsec RepoKind where
parsec :: forall (m :: * -> *). CabalParsing m => m RepoKind
parsec = String -> RepoKind
classifyRepoKind (String -> RepoKind) -> m String -> m RepoKind
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
P.munch1 Char -> Bool
isIdent
classifyRepoKind :: String -> RepoKind
classifyRepoKind :: String -> RepoKind
classifyRepoKind String
name = case ShowS
lowercase String
name of
String
"head" -> RepoKind
RepoHead
String
"this" -> RepoKind
RepoThis
String
_ -> String -> RepoKind
RepoKindUnknown String
name
instance Parsec RepoType where
parsec :: forall (m :: * -> *). CabalParsing m => m RepoType
parsec = String -> RepoType
classifyRepoType (String -> RepoType) -> m String -> m RepoType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
P.munch1 Char -> Bool
isIdent
instance Pretty RepoType where
pretty :: RepoType -> Doc
pretty (OtherRepoType String
other) = String -> Doc
Disp.text String
other
pretty (KnownRepoType KnownRepoType
t) = KnownRepoType -> Doc
forall a. Pretty a => a -> Doc
pretty KnownRepoType
t
classifyRepoType :: String -> RepoType
classifyRepoType :: String -> RepoType
classifyRepoType String
s =
RepoType
-> (KnownRepoType -> RepoType) -> Maybe KnownRepoType -> RepoType
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(String -> RepoType
OtherRepoType String
s)
KnownRepoType -> RepoType
KnownRepoType
(String -> Map String KnownRepoType -> Maybe KnownRepoType
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (ShowS
lowercase String
s) Map String KnownRepoType
knownRepoTypeMap)
knownRepoTypeMap :: Map String KnownRepoType
knownRepoTypeMap :: Map String KnownRepoType
knownRepoTypeMap =
[(String, KnownRepoType)] -> Map String KnownRepoType
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (String
name, KnownRepoType
repoType')
| KnownRepoType
repoType' <- [KnownRepoType]
knownRepoTypes
, String
name <- KnownRepoType -> String
forall a. Pretty a => a -> String
prettyShow KnownRepoType
repoType' String -> [String] -> [String]
forall a. a -> [a] -> [a]
: KnownRepoType -> [String]
repoTypeAliases KnownRepoType
repoType'
]
isIdent :: Char -> Bool
isIdent :: Char -> Bool
isIdent Char
c = Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-'