{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
#define UNSAFE 1
module GitHub.Data.Repos where
import GitHub.Data.Definitions
import GitHub.Data.Id (Id)
import GitHub.Data.Name (Name)
import GitHub.Data.Request (IsPathPart (..))
import GitHub.Data.URL (URL)
import GitHub.Internal.Prelude
import Prelude ()
import qualified Data.HashMap.Strict as HM
import qualified Data.Text as T
#if MIN_VERSION_aeson(1,0,0)
import Data.Aeson.Types (FromJSONKey (..), fromJSONKeyCoerce)
#else
#ifdef UNSAFE
import Unsafe.Coerce (unsafeCoerce)
#endif
#endif
data Repo = Repo
{ Repo -> Id Repo
repoId :: !(Id Repo)
, Repo -> Name Repo
repoName :: !(Name Repo)
, Repo -> SimpleOwner
repoOwner :: !SimpleOwner
, Repo -> Bool
repoPrivate :: !Bool
, Repo -> URL
repoHtmlUrl :: !URL
, Repo -> Maybe Text
repoDescription :: !(Maybe Text)
, Repo -> Maybe Bool
repoFork :: !(Maybe Bool)
, Repo -> URL
repoUrl :: !URL
, Repo -> Maybe URL
repoGitUrl :: !(Maybe URL)
, Repo -> Maybe URL
repoSshUrl :: !(Maybe URL)
, Repo -> Maybe URL
repoCloneUrl :: !(Maybe URL)
, Repo -> URL
repoHooksUrl :: !URL
, Repo -> Maybe URL
repoSvnUrl :: !(Maybe URL)
, Repo -> Maybe Text
repoHomepage :: !(Maybe Text)
, Repo -> Maybe Language
repoLanguage :: !(Maybe Language)
, Repo -> Int
repoForksCount :: !Int
, Repo -> Int
repoStargazersCount :: !Int
, Repo -> Int
repoWatchersCount :: !Int
, Repo -> Maybe Int
repoSize :: !(Maybe Int)
, Repo -> Maybe Text
repoDefaultBranch :: !(Maybe Text)
, Repo -> Int
repoOpenIssuesCount :: !Int
, Repo -> Maybe Bool
repoHasIssues :: !(Maybe Bool)
, Repo -> Maybe Bool
repoHasProjects :: !(Maybe Bool)
, Repo -> Maybe Bool
repoHasWiki :: !(Maybe Bool)
, Repo -> Maybe Bool
repoHasPages :: !(Maybe Bool)
, Repo -> Maybe Bool
repoHasDownloads :: !(Maybe Bool)
, Repo -> Bool
repoArchived :: !Bool
, Repo -> Bool
repoDisabled :: !Bool
, Repo -> Maybe UTCTime
repoPushedAt :: !(Maybe UTCTime)
, Repo -> Maybe UTCTime
repoCreatedAt :: !(Maybe UTCTime)
, Repo -> Maybe UTCTime
repoUpdatedAt :: !(Maybe UTCTime)
, Repo -> Maybe RepoPermissions
repoPermissions :: !(Maybe RepoPermissions)
}
deriving (Int -> Repo -> ShowS
[Repo] -> ShowS
Repo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Repo] -> ShowS
$cshowList :: [Repo] -> ShowS
show :: Repo -> String
$cshow :: Repo -> String
showsPrec :: Int -> Repo -> ShowS
$cshowsPrec :: Int -> Repo -> ShowS
Show, Typeable Repo
Repo -> DataType
Repo -> Constr
(forall b. Data b => b -> b) -> Repo -> Repo
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) -> Repo -> u
forall u. (forall d. Data d => d -> u) -> Repo -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Repo -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Repo -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Repo -> m Repo
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Repo -> m Repo
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Repo
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Repo -> c Repo
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Repo)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Repo)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Repo -> m Repo
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Repo -> m Repo
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Repo -> m Repo
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Repo -> m Repo
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Repo -> m Repo
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Repo -> m Repo
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Repo -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Repo -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Repo -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Repo -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Repo -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Repo -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Repo -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Repo -> r
gmapT :: (forall b. Data b => b -> b) -> Repo -> Repo
$cgmapT :: (forall b. Data b => b -> b) -> Repo -> Repo
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Repo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Repo)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Repo)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Repo)
dataTypeOf :: Repo -> DataType
$cdataTypeOf :: Repo -> DataType
toConstr :: Repo -> Constr
$ctoConstr :: Repo -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Repo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Repo
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Repo -> c Repo
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Repo -> c Repo
Data, Typeable, Repo -> Repo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Repo -> Repo -> Bool
$c/= :: Repo -> Repo -> Bool
== :: Repo -> Repo -> Bool
$c== :: Repo -> Repo -> Bool
Eq, Eq Repo
Repo -> Repo -> Bool
Repo -> Repo -> Ordering
Repo -> Repo -> Repo
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
min :: Repo -> Repo -> Repo
$cmin :: Repo -> Repo -> Repo
max :: Repo -> Repo -> Repo
$cmax :: Repo -> Repo -> Repo
>= :: Repo -> Repo -> Bool
$c>= :: Repo -> Repo -> Bool
> :: Repo -> Repo -> Bool
$c> :: Repo -> Repo -> Bool
<= :: Repo -> Repo -> Bool
$c<= :: Repo -> Repo -> Bool
< :: Repo -> Repo -> Bool
$c< :: Repo -> Repo -> Bool
compare :: Repo -> Repo -> Ordering
$ccompare :: Repo -> Repo -> Ordering
Ord, forall x. Rep Repo x -> Repo
forall x. Repo -> Rep Repo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Repo x -> Repo
$cfrom :: forall x. Repo -> Rep Repo x
Generic)
instance NFData Repo where rnf :: Repo -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary Repo
data CodeSearchRepo = CodeSearchRepo
{ CodeSearchRepo -> Id Repo
codeSearchRepoId :: !(Id Repo)
, CodeSearchRepo -> Name Repo
codeSearchRepoName :: !(Name Repo)
, CodeSearchRepo -> SimpleOwner
codeSearchRepoOwner :: !SimpleOwner
, CodeSearchRepo -> Bool
codeSearchRepoPrivate :: !Bool
, CodeSearchRepo -> URL
codeSearchRepoHtmlUrl :: !URL
, CodeSearchRepo -> Maybe Text
codeSearchRepoDescription :: !(Maybe Text)
, CodeSearchRepo -> Maybe Bool
codeSearchRepoFork :: !(Maybe Bool)
, CodeSearchRepo -> URL
codeSearchRepoUrl :: !URL
, CodeSearchRepo -> Maybe URL
codeSearchRepoGitUrl :: !(Maybe URL)
, CodeSearchRepo -> Maybe URL
codeSearchRepoSshUrl :: !(Maybe URL)
, CodeSearchRepo -> Maybe URL
codeSearchRepoCloneUrl :: !(Maybe URL)
, CodeSearchRepo -> URL
codeSearchRepoHooksUrl :: !URL
, CodeSearchRepo -> Maybe URL
codeSearchRepoSvnUrl :: !(Maybe URL)
, CodeSearchRepo -> Maybe Text
codeSearchRepoHomepage :: !(Maybe Text)
, CodeSearchRepo -> Maybe Language
codeSearchRepoLanguage :: !(Maybe Language)
, CodeSearchRepo -> Maybe Int
codeSearchRepoSize :: !(Maybe Int)
, CodeSearchRepo -> Maybe Text
codeSearchRepoDefaultBranch :: !(Maybe Text)
, CodeSearchRepo -> Maybe Bool
codeSearchRepoHasIssues :: !(Maybe Bool)
, CodeSearchRepo -> Maybe Bool
codeSearchRepoHasProjects :: !(Maybe Bool)
, CodeSearchRepo -> Maybe Bool
codeSearchRepoHasWiki :: !(Maybe Bool)
, CodeSearchRepo -> Maybe Bool
codeSearchRepoHasPages :: !(Maybe Bool)
, CodeSearchRepo -> Maybe Bool
codeSearchRepoHasDownloads :: !(Maybe Bool)
, CodeSearchRepo -> Bool
codeSearchRepoArchived :: !Bool
, CodeSearchRepo -> Bool
codeSearchRepoDisabled :: !Bool
, CodeSearchRepo -> Maybe UTCTime
codeSearchRepoPushedAt :: !(Maybe UTCTime)
, CodeSearchRepo -> Maybe UTCTime
codeSearchRepoCreatedAt :: !(Maybe UTCTime)
, CodeSearchRepo -> Maybe UTCTime
codeSearchRepoUpdatedAt :: !(Maybe UTCTime)
, CodeSearchRepo -> Maybe RepoPermissions
codeSearchRepoPermissions :: !(Maybe RepoPermissions)
}
deriving (Int -> CodeSearchRepo -> ShowS
[CodeSearchRepo] -> ShowS
CodeSearchRepo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeSearchRepo] -> ShowS
$cshowList :: [CodeSearchRepo] -> ShowS
show :: CodeSearchRepo -> String
$cshow :: CodeSearchRepo -> String
showsPrec :: Int -> CodeSearchRepo -> ShowS
$cshowsPrec :: Int -> CodeSearchRepo -> ShowS
Show, Typeable CodeSearchRepo
CodeSearchRepo -> DataType
CodeSearchRepo -> Constr
(forall b. Data b => b -> b) -> CodeSearchRepo -> CodeSearchRepo
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) -> CodeSearchRepo -> u
forall u. (forall d. Data d => d -> u) -> CodeSearchRepo -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CodeSearchRepo -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CodeSearchRepo -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CodeSearchRepo -> m CodeSearchRepo
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CodeSearchRepo -> m CodeSearchRepo
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CodeSearchRepo
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CodeSearchRepo -> c CodeSearchRepo
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CodeSearchRepo)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CodeSearchRepo)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CodeSearchRepo -> m CodeSearchRepo
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CodeSearchRepo -> m CodeSearchRepo
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CodeSearchRepo -> m CodeSearchRepo
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CodeSearchRepo -> m CodeSearchRepo
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CodeSearchRepo -> m CodeSearchRepo
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CodeSearchRepo -> m CodeSearchRepo
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CodeSearchRepo -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CodeSearchRepo -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> CodeSearchRepo -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CodeSearchRepo -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CodeSearchRepo -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CodeSearchRepo -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CodeSearchRepo -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CodeSearchRepo -> r
gmapT :: (forall b. Data b => b -> b) -> CodeSearchRepo -> CodeSearchRepo
$cgmapT :: (forall b. Data b => b -> b) -> CodeSearchRepo -> CodeSearchRepo
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CodeSearchRepo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CodeSearchRepo)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CodeSearchRepo)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CodeSearchRepo)
dataTypeOf :: CodeSearchRepo -> DataType
$cdataTypeOf :: CodeSearchRepo -> DataType
toConstr :: CodeSearchRepo -> Constr
$ctoConstr :: CodeSearchRepo -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CodeSearchRepo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CodeSearchRepo
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CodeSearchRepo -> c CodeSearchRepo
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CodeSearchRepo -> c CodeSearchRepo
Data, Typeable, CodeSearchRepo -> CodeSearchRepo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeSearchRepo -> CodeSearchRepo -> Bool
$c/= :: CodeSearchRepo -> CodeSearchRepo -> Bool
== :: CodeSearchRepo -> CodeSearchRepo -> Bool
$c== :: CodeSearchRepo -> CodeSearchRepo -> Bool
Eq, Eq CodeSearchRepo
CodeSearchRepo -> CodeSearchRepo -> Bool
CodeSearchRepo -> CodeSearchRepo -> Ordering
CodeSearchRepo -> CodeSearchRepo -> CodeSearchRepo
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
min :: CodeSearchRepo -> CodeSearchRepo -> CodeSearchRepo
$cmin :: CodeSearchRepo -> CodeSearchRepo -> CodeSearchRepo
max :: CodeSearchRepo -> CodeSearchRepo -> CodeSearchRepo
$cmax :: CodeSearchRepo -> CodeSearchRepo -> CodeSearchRepo
>= :: CodeSearchRepo -> CodeSearchRepo -> Bool
$c>= :: CodeSearchRepo -> CodeSearchRepo -> Bool
> :: CodeSearchRepo -> CodeSearchRepo -> Bool
$c> :: CodeSearchRepo -> CodeSearchRepo -> Bool
<= :: CodeSearchRepo -> CodeSearchRepo -> Bool
$c<= :: CodeSearchRepo -> CodeSearchRepo -> Bool
< :: CodeSearchRepo -> CodeSearchRepo -> Bool
$c< :: CodeSearchRepo -> CodeSearchRepo -> Bool
compare :: CodeSearchRepo -> CodeSearchRepo -> Ordering
$ccompare :: CodeSearchRepo -> CodeSearchRepo -> Ordering
Ord, forall x. Rep CodeSearchRepo x -> CodeSearchRepo
forall x. CodeSearchRepo -> Rep CodeSearchRepo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CodeSearchRepo x -> CodeSearchRepo
$cfrom :: forall x. CodeSearchRepo -> Rep CodeSearchRepo x
Generic)
instance NFData CodeSearchRepo where rnf :: CodeSearchRepo -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary CodeSearchRepo
data RepoPermissions = RepoPermissions
{ RepoPermissions -> Bool
repoPermissionAdmin :: !Bool
, RepoPermissions -> Bool
repoPermissionPush :: !Bool
, RepoPermissions -> Bool
repoPermissionPull :: !Bool
}
deriving (Int -> RepoPermissions -> ShowS
[RepoPermissions] -> ShowS
RepoPermissions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepoPermissions] -> ShowS
$cshowList :: [RepoPermissions] -> ShowS
show :: RepoPermissions -> String
$cshow :: RepoPermissions -> String
showsPrec :: Int -> RepoPermissions -> ShowS
$cshowsPrec :: Int -> RepoPermissions -> ShowS
Show, Typeable RepoPermissions
RepoPermissions -> DataType
RepoPermissions -> Constr
(forall b. Data b => b -> b) -> RepoPermissions -> RepoPermissions
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) -> RepoPermissions -> u
forall u. (forall d. Data d => d -> u) -> RepoPermissions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPermissions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPermissions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RepoPermissions -> m RepoPermissions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RepoPermissions -> m RepoPermissions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoPermissions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoPermissions -> c RepoPermissions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoPermissions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepoPermissions)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RepoPermissions -> m RepoPermissions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RepoPermissions -> m RepoPermissions
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RepoPermissions -> m RepoPermissions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RepoPermissions -> m RepoPermissions
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RepoPermissions -> m RepoPermissions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RepoPermissions -> m RepoPermissions
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RepoPermissions -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RepoPermissions -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> RepoPermissions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RepoPermissions -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPermissions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPermissions -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPermissions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPermissions -> r
gmapT :: (forall b. Data b => b -> b) -> RepoPermissions -> RepoPermissions
$cgmapT :: (forall b. Data b => b -> b) -> RepoPermissions -> RepoPermissions
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepoPermissions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepoPermissions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoPermissions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoPermissions)
dataTypeOf :: RepoPermissions -> DataType
$cdataTypeOf :: RepoPermissions -> DataType
toConstr :: RepoPermissions -> Constr
$ctoConstr :: RepoPermissions -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoPermissions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoPermissions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoPermissions -> c RepoPermissions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoPermissions -> c RepoPermissions
Data, Typeable, RepoPermissions -> RepoPermissions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepoPermissions -> RepoPermissions -> Bool
$c/= :: RepoPermissions -> RepoPermissions -> Bool
== :: RepoPermissions -> RepoPermissions -> Bool
$c== :: RepoPermissions -> RepoPermissions -> Bool
Eq, Eq RepoPermissions
RepoPermissions -> RepoPermissions -> Bool
RepoPermissions -> RepoPermissions -> Ordering
RepoPermissions -> RepoPermissions -> RepoPermissions
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
min :: RepoPermissions -> RepoPermissions -> RepoPermissions
$cmin :: RepoPermissions -> RepoPermissions -> RepoPermissions
max :: RepoPermissions -> RepoPermissions -> RepoPermissions
$cmax :: RepoPermissions -> RepoPermissions -> RepoPermissions
>= :: RepoPermissions -> RepoPermissions -> Bool
$c>= :: RepoPermissions -> RepoPermissions -> Bool
> :: RepoPermissions -> RepoPermissions -> Bool
$c> :: RepoPermissions -> RepoPermissions -> Bool
<= :: RepoPermissions -> RepoPermissions -> Bool
$c<= :: RepoPermissions -> RepoPermissions -> Bool
< :: RepoPermissions -> RepoPermissions -> Bool
$c< :: RepoPermissions -> RepoPermissions -> Bool
compare :: RepoPermissions -> RepoPermissions -> Ordering
$ccompare :: RepoPermissions -> RepoPermissions -> Ordering
Ord, forall x. Rep RepoPermissions x -> RepoPermissions
forall x. RepoPermissions -> Rep RepoPermissions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RepoPermissions x -> RepoPermissions
$cfrom :: forall x. RepoPermissions -> Rep RepoPermissions x
Generic)
instance NFData RepoPermissions where rnf :: RepoPermissions -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary RepoPermissions
data RepoRef = RepoRef
{ RepoRef -> SimpleOwner
repoRefOwner :: !SimpleOwner
, RepoRef -> Name Repo
repoRefRepo :: !(Name Repo)
}
deriving (Int -> RepoRef -> ShowS
[RepoRef] -> ShowS
RepoRef -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepoRef] -> ShowS
$cshowList :: [RepoRef] -> ShowS
show :: RepoRef -> String
$cshow :: RepoRef -> String
showsPrec :: Int -> RepoRef -> ShowS
$cshowsPrec :: Int -> RepoRef -> ShowS
Show, Typeable RepoRef
RepoRef -> DataType
RepoRef -> Constr
(forall b. Data b => b -> b) -> RepoRef -> RepoRef
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) -> RepoRef -> u
forall u. (forall d. Data d => d -> u) -> RepoRef -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoRef -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoRef -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoRef -> m RepoRef
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoRef -> m RepoRef
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoRef
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoRef -> c RepoRef
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoRef)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoRef)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoRef -> m RepoRef
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoRef -> m RepoRef
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoRef -> m RepoRef
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoRef -> m RepoRef
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoRef -> m RepoRef
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoRef -> m RepoRef
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RepoRef -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RepoRef -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> RepoRef -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RepoRef -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoRef -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoRef -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoRef -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoRef -> r
gmapT :: (forall b. Data b => b -> b) -> RepoRef -> RepoRef
$cgmapT :: (forall b. Data b => b -> b) -> RepoRef -> RepoRef
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoRef)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoRef)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoRef)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoRef)
dataTypeOf :: RepoRef -> DataType
$cdataTypeOf :: RepoRef -> DataType
toConstr :: RepoRef -> Constr
$ctoConstr :: RepoRef -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoRef
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoRef
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoRef -> c RepoRef
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoRef -> c RepoRef
Data, Typeable, RepoRef -> RepoRef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepoRef -> RepoRef -> Bool
$c/= :: RepoRef -> RepoRef -> Bool
== :: RepoRef -> RepoRef -> Bool
$c== :: RepoRef -> RepoRef -> Bool
Eq, Eq RepoRef
RepoRef -> RepoRef -> Bool
RepoRef -> RepoRef -> Ordering
RepoRef -> RepoRef -> RepoRef
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
min :: RepoRef -> RepoRef -> RepoRef
$cmin :: RepoRef -> RepoRef -> RepoRef
max :: RepoRef -> RepoRef -> RepoRef
$cmax :: RepoRef -> RepoRef -> RepoRef
>= :: RepoRef -> RepoRef -> Bool
$c>= :: RepoRef -> RepoRef -> Bool
> :: RepoRef -> RepoRef -> Bool
$c> :: RepoRef -> RepoRef -> Bool
<= :: RepoRef -> RepoRef -> Bool
$c<= :: RepoRef -> RepoRef -> Bool
< :: RepoRef -> RepoRef -> Bool
$c< :: RepoRef -> RepoRef -> Bool
compare :: RepoRef -> RepoRef -> Ordering
$ccompare :: RepoRef -> RepoRef -> Ordering
Ord, forall x. Rep RepoRef x -> RepoRef
forall x. RepoRef -> Rep RepoRef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RepoRef x -> RepoRef
$cfrom :: forall x. RepoRef -> Rep RepoRef x
Generic)
instance NFData RepoRef where rnf :: RepoRef -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary RepoRef
data NewRepo = NewRepo
{ NewRepo -> Name Repo
newRepoName :: !(Name Repo)
, NewRepo -> Maybe Text
newRepoDescription :: !(Maybe Text)
, NewRepo -> Maybe Text
newRepoHomepage :: !(Maybe Text)
, NewRepo -> Maybe Bool
newRepoPrivate :: !(Maybe Bool)
, NewRepo -> Maybe Bool
newRepoHasIssues :: !(Maybe Bool)
, NewRepo -> Maybe Bool
newRepoHasProjects :: !(Maybe Bool)
, NewRepo -> Maybe Bool
newRepoHasWiki :: !(Maybe Bool)
, NewRepo -> Maybe Bool
newRepoAutoInit :: !(Maybe Bool)
, NewRepo -> Maybe Text
newRepoGitignoreTemplate :: !(Maybe Text)
, NewRepo -> Maybe Text
newRepoLicenseTemplate :: !(Maybe Text)
, NewRepo -> Maybe Bool
newRepoAllowSquashMerge :: !(Maybe Bool)
, NewRepo -> Maybe Bool
newRepoAllowMergeCommit :: !(Maybe Bool)
, NewRepo -> Maybe Bool
newRepoAllowRebaseMerge :: !(Maybe Bool)
} deriving (NewRepo -> NewRepo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewRepo -> NewRepo -> Bool
$c/= :: NewRepo -> NewRepo -> Bool
== :: NewRepo -> NewRepo -> Bool
$c== :: NewRepo -> NewRepo -> Bool
Eq, Eq NewRepo
NewRepo -> NewRepo -> Bool
NewRepo -> NewRepo -> Ordering
NewRepo -> NewRepo -> NewRepo
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
min :: NewRepo -> NewRepo -> NewRepo
$cmin :: NewRepo -> NewRepo -> NewRepo
max :: NewRepo -> NewRepo -> NewRepo
$cmax :: NewRepo -> NewRepo -> NewRepo
>= :: NewRepo -> NewRepo -> Bool
$c>= :: NewRepo -> NewRepo -> Bool
> :: NewRepo -> NewRepo -> Bool
$c> :: NewRepo -> NewRepo -> Bool
<= :: NewRepo -> NewRepo -> Bool
$c<= :: NewRepo -> NewRepo -> Bool
< :: NewRepo -> NewRepo -> Bool
$c< :: NewRepo -> NewRepo -> Bool
compare :: NewRepo -> NewRepo -> Ordering
$ccompare :: NewRepo -> NewRepo -> Ordering
Ord, Int -> NewRepo -> ShowS
[NewRepo] -> ShowS
NewRepo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewRepo] -> ShowS
$cshowList :: [NewRepo] -> ShowS
show :: NewRepo -> String
$cshow :: NewRepo -> String
showsPrec :: Int -> NewRepo -> ShowS
$cshowsPrec :: Int -> NewRepo -> ShowS
Show, Typeable NewRepo
NewRepo -> DataType
NewRepo -> Constr
(forall b. Data b => b -> b) -> NewRepo -> NewRepo
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) -> NewRepo -> u
forall u. (forall d. Data d => d -> u) -> NewRepo -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewRepo -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewRepo -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewRepo -> m NewRepo
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewRepo -> m NewRepo
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewRepo
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewRepo -> c NewRepo
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewRepo)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewRepo)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewRepo -> m NewRepo
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewRepo -> m NewRepo
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewRepo -> m NewRepo
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NewRepo -> m NewRepo
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewRepo -> m NewRepo
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NewRepo -> m NewRepo
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewRepo -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NewRepo -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> NewRepo -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NewRepo -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewRepo -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NewRepo -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewRepo -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NewRepo -> r
gmapT :: (forall b. Data b => b -> b) -> NewRepo -> NewRepo
$cgmapT :: (forall b. Data b => b -> b) -> NewRepo -> NewRepo
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewRepo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewRepo)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewRepo)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NewRepo)
dataTypeOf :: NewRepo -> DataType
$cdataTypeOf :: NewRepo -> DataType
toConstr :: NewRepo -> Constr
$ctoConstr :: NewRepo -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewRepo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NewRepo
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewRepo -> c NewRepo
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NewRepo -> c NewRepo
Data, Typeable, forall x. Rep NewRepo x -> NewRepo
forall x. NewRepo -> Rep NewRepo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NewRepo x -> NewRepo
$cfrom :: forall x. NewRepo -> Rep NewRepo x
Generic)
instance NFData NewRepo where rnf :: NewRepo -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary NewRepo
newRepo :: Name Repo -> NewRepo
newRepo :: Name Repo -> NewRepo
newRepo Name Repo
name = Name Repo
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> NewRepo
NewRepo Name Repo
name forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing
data EditRepo = EditRepo
{ EditRepo -> Maybe (Name Repo)
editName :: !(Maybe (Name Repo))
, EditRepo -> Maybe Text
editDescription :: !(Maybe Text)
, EditRepo -> Maybe Text
editHomepage :: !(Maybe Text)
, EditRepo -> Maybe Bool
editPrivate :: !(Maybe Bool)
, EditRepo -> Maybe Bool
editHasIssues :: !(Maybe Bool)
, EditRepo -> Maybe Bool
editHasProjects :: !(Maybe Bool)
, EditRepo -> Maybe Bool
editHasWiki :: !(Maybe Bool)
, EditRepo -> Maybe Text
editDefaultBranch :: !(Maybe Text)
, EditRepo -> Maybe Bool
editAllowSquashMerge :: !(Maybe Bool)
, EditRepo -> Maybe Bool
editAllowMergeCommit :: !(Maybe Bool)
, EditRepo -> Maybe Bool
editAllowRebaseMerge :: !(Maybe Bool)
, EditRepo -> Maybe Bool
editArchived :: !(Maybe Bool)
}
deriving (EditRepo -> EditRepo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditRepo -> EditRepo -> Bool
$c/= :: EditRepo -> EditRepo -> Bool
== :: EditRepo -> EditRepo -> Bool
$c== :: EditRepo -> EditRepo -> Bool
Eq, Eq EditRepo
EditRepo -> EditRepo -> Bool
EditRepo -> EditRepo -> Ordering
EditRepo -> EditRepo -> EditRepo
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
min :: EditRepo -> EditRepo -> EditRepo
$cmin :: EditRepo -> EditRepo -> EditRepo
max :: EditRepo -> EditRepo -> EditRepo
$cmax :: EditRepo -> EditRepo -> EditRepo
>= :: EditRepo -> EditRepo -> Bool
$c>= :: EditRepo -> EditRepo -> Bool
> :: EditRepo -> EditRepo -> Bool
$c> :: EditRepo -> EditRepo -> Bool
<= :: EditRepo -> EditRepo -> Bool
$c<= :: EditRepo -> EditRepo -> Bool
< :: EditRepo -> EditRepo -> Bool
$c< :: EditRepo -> EditRepo -> Bool
compare :: EditRepo -> EditRepo -> Ordering
$ccompare :: EditRepo -> EditRepo -> Ordering
Ord, Int -> EditRepo -> ShowS
[EditRepo] -> ShowS
EditRepo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditRepo] -> ShowS
$cshowList :: [EditRepo] -> ShowS
show :: EditRepo -> String
$cshow :: EditRepo -> String
showsPrec :: Int -> EditRepo -> ShowS
$cshowsPrec :: Int -> EditRepo -> ShowS
Show, Typeable EditRepo
EditRepo -> DataType
EditRepo -> Constr
(forall b. Data b => b -> b) -> EditRepo -> EditRepo
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) -> EditRepo -> u
forall u. (forall d. Data d => d -> u) -> EditRepo -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EditRepo -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EditRepo -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EditRepo -> m EditRepo
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EditRepo -> m EditRepo
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EditRepo
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EditRepo -> c EditRepo
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EditRepo)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EditRepo)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EditRepo -> m EditRepo
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EditRepo -> m EditRepo
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EditRepo -> m EditRepo
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> EditRepo -> m EditRepo
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EditRepo -> m EditRepo
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> EditRepo -> m EditRepo
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> EditRepo -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> EditRepo -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> EditRepo -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> EditRepo -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EditRepo -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> EditRepo -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EditRepo -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> EditRepo -> r
gmapT :: (forall b. Data b => b -> b) -> EditRepo -> EditRepo
$cgmapT :: (forall b. Data b => b -> b) -> EditRepo -> EditRepo
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EditRepo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EditRepo)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EditRepo)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c EditRepo)
dataTypeOf :: EditRepo -> DataType
$cdataTypeOf :: EditRepo -> DataType
toConstr :: EditRepo -> Constr
$ctoConstr :: EditRepo -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EditRepo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c EditRepo
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EditRepo -> c EditRepo
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> EditRepo -> c EditRepo
Data, Typeable, forall x. Rep EditRepo x -> EditRepo
forall x. EditRepo -> Rep EditRepo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EditRepo x -> EditRepo
$cfrom :: forall x. EditRepo -> Rep EditRepo x
Generic)
instance NFData EditRepo where rnf :: EditRepo -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary EditRepo
data RepoPublicity
= RepoPublicityAll
| RepoPublicityOwner
| RepoPublicityPublic
| RepoPublicityPrivate
| RepoPublicityMember
deriving (Int -> RepoPublicity -> ShowS
[RepoPublicity] -> ShowS
RepoPublicity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepoPublicity] -> ShowS
$cshowList :: [RepoPublicity] -> ShowS
show :: RepoPublicity -> String
$cshow :: RepoPublicity -> String
showsPrec :: Int -> RepoPublicity -> ShowS
$cshowsPrec :: Int -> RepoPublicity -> ShowS
Show, RepoPublicity -> RepoPublicity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepoPublicity -> RepoPublicity -> Bool
$c/= :: RepoPublicity -> RepoPublicity -> Bool
== :: RepoPublicity -> RepoPublicity -> Bool
$c== :: RepoPublicity -> RepoPublicity -> Bool
Eq, Eq RepoPublicity
RepoPublicity -> RepoPublicity -> Bool
RepoPublicity -> RepoPublicity -> Ordering
RepoPublicity -> RepoPublicity -> RepoPublicity
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
min :: RepoPublicity -> RepoPublicity -> RepoPublicity
$cmin :: RepoPublicity -> RepoPublicity -> RepoPublicity
max :: RepoPublicity -> RepoPublicity -> RepoPublicity
$cmax :: RepoPublicity -> RepoPublicity -> RepoPublicity
>= :: RepoPublicity -> RepoPublicity -> Bool
$c>= :: RepoPublicity -> RepoPublicity -> Bool
> :: RepoPublicity -> RepoPublicity -> Bool
$c> :: RepoPublicity -> RepoPublicity -> Bool
<= :: RepoPublicity -> RepoPublicity -> Bool
$c<= :: RepoPublicity -> RepoPublicity -> Bool
< :: RepoPublicity -> RepoPublicity -> Bool
$c< :: RepoPublicity -> RepoPublicity -> Bool
compare :: RepoPublicity -> RepoPublicity -> Ordering
$ccompare :: RepoPublicity -> RepoPublicity -> Ordering
Ord, Int -> RepoPublicity
RepoPublicity -> Int
RepoPublicity -> [RepoPublicity]
RepoPublicity -> RepoPublicity
RepoPublicity -> RepoPublicity -> [RepoPublicity]
RepoPublicity -> RepoPublicity -> RepoPublicity -> [RepoPublicity]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: RepoPublicity -> RepoPublicity -> RepoPublicity -> [RepoPublicity]
$cenumFromThenTo :: RepoPublicity -> RepoPublicity -> RepoPublicity -> [RepoPublicity]
enumFromTo :: RepoPublicity -> RepoPublicity -> [RepoPublicity]
$cenumFromTo :: RepoPublicity -> RepoPublicity -> [RepoPublicity]
enumFromThen :: RepoPublicity -> RepoPublicity -> [RepoPublicity]
$cenumFromThen :: RepoPublicity -> RepoPublicity -> [RepoPublicity]
enumFrom :: RepoPublicity -> [RepoPublicity]
$cenumFrom :: RepoPublicity -> [RepoPublicity]
fromEnum :: RepoPublicity -> Int
$cfromEnum :: RepoPublicity -> Int
toEnum :: Int -> RepoPublicity
$ctoEnum :: Int -> RepoPublicity
pred :: RepoPublicity -> RepoPublicity
$cpred :: RepoPublicity -> RepoPublicity
succ :: RepoPublicity -> RepoPublicity
$csucc :: RepoPublicity -> RepoPublicity
Enum, RepoPublicity
forall a. a -> a -> Bounded a
maxBound :: RepoPublicity
$cmaxBound :: RepoPublicity
minBound :: RepoPublicity
$cminBound :: RepoPublicity
Bounded, Typeable, Typeable RepoPublicity
RepoPublicity -> DataType
RepoPublicity -> Constr
(forall b. Data b => b -> b) -> RepoPublicity -> RepoPublicity
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) -> RepoPublicity -> u
forall u. (forall d. Data d => d -> u) -> RepoPublicity -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPublicity -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPublicity -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoPublicity
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoPublicity -> c RepoPublicity
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoPublicity)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepoPublicity)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RepoPublicity -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RepoPublicity -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> RepoPublicity -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RepoPublicity -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPublicity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPublicity -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPublicity -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RepoPublicity -> r
gmapT :: (forall b. Data b => b -> b) -> RepoPublicity -> RepoPublicity
$cgmapT :: (forall b. Data b => b -> b) -> RepoPublicity -> RepoPublicity
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepoPublicity)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RepoPublicity)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoPublicity)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RepoPublicity)
dataTypeOf :: RepoPublicity -> DataType
$cdataTypeOf :: RepoPublicity -> DataType
toConstr :: RepoPublicity -> Constr
$ctoConstr :: RepoPublicity -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoPublicity
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RepoPublicity
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoPublicity -> c RepoPublicity
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RepoPublicity -> c RepoPublicity
Data, forall x. Rep RepoPublicity x -> RepoPublicity
forall x. RepoPublicity -> Rep RepoPublicity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RepoPublicity x -> RepoPublicity
$cfrom :: forall x. RepoPublicity -> Rep RepoPublicity x
Generic)
type Languages = HM.HashMap Language Int
newtype Language = Language Text
deriving (Int -> Language -> ShowS
[Language] -> ShowS
Language -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Language] -> ShowS
$cshowList :: [Language] -> ShowS
show :: Language -> String
$cshow :: Language -> String
showsPrec :: Int -> Language -> ShowS
$cshowsPrec :: Int -> Language -> ShowS
Show, Typeable Language
Language -> DataType
Language -> Constr
(forall b. Data b => b -> b) -> Language -> Language
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) -> Language -> u
forall u. (forall d. Data d => d -> u) -> Language -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Language -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Language -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Language -> m Language
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Language -> m Language
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Language
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Language -> c Language
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Language)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Language)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Language -> m Language
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Language -> m Language
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Language -> m Language
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Language -> m Language
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Language -> m Language
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Language -> m Language
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Language -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Language -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Language -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Language -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Language -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Language -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Language -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Language -> r
gmapT :: (forall b. Data b => b -> b) -> Language -> Language
$cgmapT :: (forall b. Data b => b -> b) -> Language -> Language
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Language)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Language)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Language)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Language)
dataTypeOf :: Language -> DataType
$cdataTypeOf :: Language -> DataType
toConstr :: Language -> Constr
$ctoConstr :: Language -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Language
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Language
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Language -> c Language
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Language -> c Language
Data, Typeable, Language -> Language -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Language -> Language -> Bool
$c/= :: Language -> Language -> Bool
== :: Language -> Language -> Bool
$c== :: Language -> Language -> Bool
Eq, Eq Language
Language -> Language -> Bool
Language -> Language -> Ordering
Language -> Language -> Language
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
min :: Language -> Language -> Language
$cmin :: Language -> Language -> Language
max :: Language -> Language -> Language
$cmax :: Language -> Language -> Language
>= :: Language -> Language -> Bool
$c>= :: Language -> Language -> Bool
> :: Language -> Language -> Bool
$c> :: Language -> Language -> Bool
<= :: Language -> Language -> Bool
$c<= :: Language -> Language -> Bool
< :: Language -> Language -> Bool
$c< :: Language -> Language -> Bool
compare :: Language -> Language -> Ordering
$ccompare :: Language -> Language -> Ordering
Ord, forall x. Rep Language x -> Language
forall x. Language -> Rep Language x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Language x -> Language
$cfrom :: forall x. Language -> Rep Language x
Generic)
getLanguage :: Language -> Text
getLanguage :: Language -> Text
getLanguage (Language Text
l) = Text
l
instance NFData Language where rnf :: Language -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary Language
instance Hashable Language where
hashWithSalt :: Int -> Language -> Int
hashWithSalt Int
salt (Language Text
l) = forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt Text
l
instance IsString Language where
fromString :: String -> Language
fromString = Text -> Language
Language forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString
data Contributor
= KnownContributor !Int !URL !(Name User) !URL !(Id User) !Text
| AnonymousContributor !Int !Text
deriving (Int -> Contributor -> ShowS
[Contributor] -> ShowS
Contributor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Contributor] -> ShowS
$cshowList :: [Contributor] -> ShowS
show :: Contributor -> String
$cshow :: Contributor -> String
showsPrec :: Int -> Contributor -> ShowS
$cshowsPrec :: Int -> Contributor -> ShowS
Show, Typeable Contributor
Contributor -> DataType
Contributor -> Constr
(forall b. Data b => b -> b) -> Contributor -> Contributor
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) -> Contributor -> u
forall u. (forall d. Data d => d -> u) -> Contributor -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Contributor -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Contributor -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Contributor -> m Contributor
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contributor -> m Contributor
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Contributor
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Contributor -> c Contributor
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Contributor)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Contributor)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contributor -> m Contributor
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contributor -> m Contributor
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contributor -> m Contributor
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Contributor -> m Contributor
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Contributor -> m Contributor
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Contributor -> m Contributor
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Contributor -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Contributor -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Contributor -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Contributor -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Contributor -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Contributor -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Contributor -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Contributor -> r
gmapT :: (forall b. Data b => b -> b) -> Contributor -> Contributor
$cgmapT :: (forall b. Data b => b -> b) -> Contributor -> Contributor
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Contributor)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Contributor)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Contributor)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Contributor)
dataTypeOf :: Contributor -> DataType
$cdataTypeOf :: Contributor -> DataType
toConstr :: Contributor -> Constr
$ctoConstr :: Contributor -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Contributor
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Contributor
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Contributor -> c Contributor
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Contributor -> c Contributor
Data, Typeable, Contributor -> Contributor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Contributor -> Contributor -> Bool
$c/= :: Contributor -> Contributor -> Bool
== :: Contributor -> Contributor -> Bool
$c== :: Contributor -> Contributor -> Bool
Eq, Eq Contributor
Contributor -> Contributor -> Bool
Contributor -> Contributor -> Ordering
Contributor -> Contributor -> Contributor
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
min :: Contributor -> Contributor -> Contributor
$cmin :: Contributor -> Contributor -> Contributor
max :: Contributor -> Contributor -> Contributor
$cmax :: Contributor -> Contributor -> Contributor
>= :: Contributor -> Contributor -> Bool
$c>= :: Contributor -> Contributor -> Bool
> :: Contributor -> Contributor -> Bool
$c> :: Contributor -> Contributor -> Bool
<= :: Contributor -> Contributor -> Bool
$c<= :: Contributor -> Contributor -> Bool
< :: Contributor -> Contributor -> Bool
$c< :: Contributor -> Contributor -> Bool
compare :: Contributor -> Contributor -> Ordering
$ccompare :: Contributor -> Contributor -> Ordering
Ord, forall x. Rep Contributor x -> Contributor
forall x. Contributor -> Rep Contributor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Contributor x -> Contributor
$cfrom :: forall x. Contributor -> Rep Contributor x
Generic)
instance NFData Contributor where rnf :: Contributor -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary Contributor
contributorToSimpleUser :: Contributor -> Maybe SimpleUser
contributorToSimpleUser :: Contributor -> Maybe SimpleUser
contributorToSimpleUser (AnonymousContributor Int
_ Text
_) = forall a. Maybe a
Nothing
contributorToSimpleUser (KnownContributor Int
_contributions URL
avatarUrl Name User
name URL
url Id User
uid Text
_gravatarid) =
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Id User -> Name User -> URL -> URL -> SimpleUser
SimpleUser Id User
uid Name User
name URL
avatarUrl URL
url
data CollaboratorPermission
= CollaboratorPermissionAdmin
| CollaboratorPermissionWrite
| CollaboratorPermissionRead
| CollaboratorPermissionNone
deriving (Int -> CollaboratorPermission -> ShowS
[CollaboratorPermission] -> ShowS
CollaboratorPermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CollaboratorPermission] -> ShowS
$cshowList :: [CollaboratorPermission] -> ShowS
show :: CollaboratorPermission -> String
$cshow :: CollaboratorPermission -> String
showsPrec :: Int -> CollaboratorPermission -> ShowS
$cshowsPrec :: Int -> CollaboratorPermission -> ShowS
Show, Typeable CollaboratorPermission
CollaboratorPermission -> DataType
CollaboratorPermission -> Constr
(forall b. Data b => b -> b)
-> CollaboratorPermission -> CollaboratorPermission
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) -> CollaboratorPermission -> u
forall u.
(forall d. Data d => d -> u) -> CollaboratorPermission -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorPermission
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorPermission
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CollaboratorPermission -> m CollaboratorPermission
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollaboratorPermission -> m CollaboratorPermission
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CollaboratorPermission
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollaboratorPermission
-> c CollaboratorPermission
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CollaboratorPermission)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CollaboratorPermission)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollaboratorPermission -> m CollaboratorPermission
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollaboratorPermission -> m CollaboratorPermission
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollaboratorPermission -> m CollaboratorPermission
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollaboratorPermission -> m CollaboratorPermission
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CollaboratorPermission -> m CollaboratorPermission
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CollaboratorPermission -> m CollaboratorPermission
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CollaboratorPermission -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CollaboratorPermission -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> CollaboratorPermission -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> CollaboratorPermission -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorPermission
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorPermission
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorPermission
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorPermission
-> r
gmapT :: (forall b. Data b => b -> b)
-> CollaboratorPermission -> CollaboratorPermission
$cgmapT :: (forall b. Data b => b -> b)
-> CollaboratorPermission -> CollaboratorPermission
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CollaboratorPermission)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CollaboratorPermission)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CollaboratorPermission)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CollaboratorPermission)
dataTypeOf :: CollaboratorPermission -> DataType
$cdataTypeOf :: CollaboratorPermission -> DataType
toConstr :: CollaboratorPermission -> Constr
$ctoConstr :: CollaboratorPermission -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CollaboratorPermission
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CollaboratorPermission
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollaboratorPermission
-> c CollaboratorPermission
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollaboratorPermission
-> c CollaboratorPermission
Data, Int -> CollaboratorPermission
CollaboratorPermission -> Int
CollaboratorPermission -> [CollaboratorPermission]
CollaboratorPermission -> CollaboratorPermission
CollaboratorPermission
-> CollaboratorPermission -> [CollaboratorPermission]
CollaboratorPermission
-> CollaboratorPermission
-> CollaboratorPermission
-> [CollaboratorPermission]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: CollaboratorPermission
-> CollaboratorPermission
-> CollaboratorPermission
-> [CollaboratorPermission]
$cenumFromThenTo :: CollaboratorPermission
-> CollaboratorPermission
-> CollaboratorPermission
-> [CollaboratorPermission]
enumFromTo :: CollaboratorPermission
-> CollaboratorPermission -> [CollaboratorPermission]
$cenumFromTo :: CollaboratorPermission
-> CollaboratorPermission -> [CollaboratorPermission]
enumFromThen :: CollaboratorPermission
-> CollaboratorPermission -> [CollaboratorPermission]
$cenumFromThen :: CollaboratorPermission
-> CollaboratorPermission -> [CollaboratorPermission]
enumFrom :: CollaboratorPermission -> [CollaboratorPermission]
$cenumFrom :: CollaboratorPermission -> [CollaboratorPermission]
fromEnum :: CollaboratorPermission -> Int
$cfromEnum :: CollaboratorPermission -> Int
toEnum :: Int -> CollaboratorPermission
$ctoEnum :: Int -> CollaboratorPermission
pred :: CollaboratorPermission -> CollaboratorPermission
$cpred :: CollaboratorPermission -> CollaboratorPermission
succ :: CollaboratorPermission -> CollaboratorPermission
$csucc :: CollaboratorPermission -> CollaboratorPermission
Enum, CollaboratorPermission
forall a. a -> a -> Bounded a
maxBound :: CollaboratorPermission
$cmaxBound :: CollaboratorPermission
minBound :: CollaboratorPermission
$cminBound :: CollaboratorPermission
Bounded, Typeable, CollaboratorPermission -> CollaboratorPermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CollaboratorPermission -> CollaboratorPermission -> Bool
$c/= :: CollaboratorPermission -> CollaboratorPermission -> Bool
== :: CollaboratorPermission -> CollaboratorPermission -> Bool
$c== :: CollaboratorPermission -> CollaboratorPermission -> Bool
Eq, Eq CollaboratorPermission
CollaboratorPermission -> CollaboratorPermission -> Bool
CollaboratorPermission -> CollaboratorPermission -> Ordering
CollaboratorPermission
-> CollaboratorPermission -> CollaboratorPermission
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
min :: CollaboratorPermission
-> CollaboratorPermission -> CollaboratorPermission
$cmin :: CollaboratorPermission
-> CollaboratorPermission -> CollaboratorPermission
max :: CollaboratorPermission
-> CollaboratorPermission -> CollaboratorPermission
$cmax :: CollaboratorPermission
-> CollaboratorPermission -> CollaboratorPermission
>= :: CollaboratorPermission -> CollaboratorPermission -> Bool
$c>= :: CollaboratorPermission -> CollaboratorPermission -> Bool
> :: CollaboratorPermission -> CollaboratorPermission -> Bool
$c> :: CollaboratorPermission -> CollaboratorPermission -> Bool
<= :: CollaboratorPermission -> CollaboratorPermission -> Bool
$c<= :: CollaboratorPermission -> CollaboratorPermission -> Bool
< :: CollaboratorPermission -> CollaboratorPermission -> Bool
$c< :: CollaboratorPermission -> CollaboratorPermission -> Bool
compare :: CollaboratorPermission -> CollaboratorPermission -> Ordering
$ccompare :: CollaboratorPermission -> CollaboratorPermission -> Ordering
Ord, forall x. Rep CollaboratorPermission x -> CollaboratorPermission
forall x. CollaboratorPermission -> Rep CollaboratorPermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CollaboratorPermission x -> CollaboratorPermission
$cfrom :: forall x. CollaboratorPermission -> Rep CollaboratorPermission x
Generic)
instance NFData CollaboratorPermission where rnf :: CollaboratorPermission -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary CollaboratorPermission
data CollaboratorWithPermission
= CollaboratorWithPermission SimpleUser CollaboratorPermission
deriving (Int -> CollaboratorWithPermission -> ShowS
[CollaboratorWithPermission] -> ShowS
CollaboratorWithPermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CollaboratorWithPermission] -> ShowS
$cshowList :: [CollaboratorWithPermission] -> ShowS
show :: CollaboratorWithPermission -> String
$cshow :: CollaboratorWithPermission -> String
showsPrec :: Int -> CollaboratorWithPermission -> ShowS
$cshowsPrec :: Int -> CollaboratorWithPermission -> ShowS
Show, Typeable CollaboratorWithPermission
CollaboratorWithPermission -> DataType
CollaboratorWithPermission -> Constr
(forall b. Data b => b -> b)
-> CollaboratorWithPermission -> CollaboratorWithPermission
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) -> CollaboratorWithPermission -> u
forall u.
(forall d. Data d => d -> u) -> CollaboratorWithPermission -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorWithPermission
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorWithPermission
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CollaboratorWithPermission -> m CollaboratorWithPermission
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollaboratorWithPermission -> m CollaboratorWithPermission
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CollaboratorWithPermission
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollaboratorWithPermission
-> c CollaboratorWithPermission
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c CollaboratorWithPermission)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CollaboratorWithPermission)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollaboratorWithPermission -> m CollaboratorWithPermission
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollaboratorWithPermission -> m CollaboratorWithPermission
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollaboratorWithPermission -> m CollaboratorWithPermission
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CollaboratorWithPermission -> m CollaboratorWithPermission
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CollaboratorWithPermission -> m CollaboratorWithPermission
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CollaboratorWithPermission -> m CollaboratorWithPermission
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> CollaboratorWithPermission -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> CollaboratorWithPermission -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> CollaboratorWithPermission -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> CollaboratorWithPermission -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorWithPermission
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorWithPermission
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorWithPermission
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> CollaboratorWithPermission
-> r
gmapT :: (forall b. Data b => b -> b)
-> CollaboratorWithPermission -> CollaboratorWithPermission
$cgmapT :: (forall b. Data b => b -> b)
-> CollaboratorWithPermission -> CollaboratorWithPermission
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CollaboratorWithPermission)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CollaboratorWithPermission)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c CollaboratorWithPermission)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c CollaboratorWithPermission)
dataTypeOf :: CollaboratorWithPermission -> DataType
$cdataTypeOf :: CollaboratorWithPermission -> DataType
toConstr :: CollaboratorWithPermission -> Constr
$ctoConstr :: CollaboratorWithPermission -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CollaboratorWithPermission
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CollaboratorWithPermission
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollaboratorWithPermission
-> c CollaboratorWithPermission
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CollaboratorWithPermission
-> c CollaboratorWithPermission
Data, Typeable, CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
$c/= :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
== :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
$c== :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
Eq, Eq CollaboratorWithPermission
CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
CollaboratorWithPermission
-> CollaboratorWithPermission -> Ordering
CollaboratorWithPermission
-> CollaboratorWithPermission -> CollaboratorWithPermission
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
min :: CollaboratorWithPermission
-> CollaboratorWithPermission -> CollaboratorWithPermission
$cmin :: CollaboratorWithPermission
-> CollaboratorWithPermission -> CollaboratorWithPermission
max :: CollaboratorWithPermission
-> CollaboratorWithPermission -> CollaboratorWithPermission
$cmax :: CollaboratorWithPermission
-> CollaboratorWithPermission -> CollaboratorWithPermission
>= :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
$c>= :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
> :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
$c> :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
<= :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
$c<= :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
< :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
$c< :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool
compare :: CollaboratorWithPermission
-> CollaboratorWithPermission -> Ordering
$ccompare :: CollaboratorWithPermission
-> CollaboratorWithPermission -> Ordering
Ord, forall x.
Rep CollaboratorWithPermission x -> CollaboratorWithPermission
forall x.
CollaboratorWithPermission -> Rep CollaboratorWithPermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CollaboratorWithPermission x -> CollaboratorWithPermission
$cfrom :: forall x.
CollaboratorWithPermission -> Rep CollaboratorWithPermission x
Generic)
instance NFData CollaboratorWithPermission where rnf :: CollaboratorWithPermission -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary CollaboratorWithPermission
instance FromJSON Repo where
parseJSON :: Value -> Parser Repo
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Repo" forall a b. (a -> b) -> a -> b
$ \Object
o -> Id Repo
-> Name Repo
-> SimpleOwner
-> Bool
-> URL
-> Maybe Text
-> Maybe Bool
-> URL
-> Maybe URL
-> Maybe URL
-> Maybe URL
-> URL
-> Maybe URL
-> Maybe Text
-> Maybe Language
-> Int
-> Int
-> Int
-> Maybe Int
-> Maybe Text
-> Int
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Bool
-> Bool
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe RepoPermissions
-> Repo
Repo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"owner"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"private"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"html_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fork"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"git_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ssh_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"clone_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"hooks_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"svn_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"homepage"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"language"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"forks_count"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"stargazers_count"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"watchers_count"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"size"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"default_branch"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"open_issues_count"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_issues"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_projects"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_wiki"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_pages"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_downloads"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"archived" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disabled" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"pushed_at"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"created_at"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"updated_at"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"permissions"
instance FromJSON CodeSearchRepo where
parseJSON :: Value -> Parser CodeSearchRepo
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Repo" forall a b. (a -> b) -> a -> b
$ \Object
o -> Id Repo
-> Name Repo
-> SimpleOwner
-> Bool
-> URL
-> Maybe Text
-> Maybe Bool
-> URL
-> Maybe URL
-> Maybe URL
-> Maybe URL
-> URL
-> Maybe URL
-> Maybe Text
-> Maybe Language
-> Maybe Int
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Bool
-> Bool
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe RepoPermissions
-> CodeSearchRepo
CodeSearchRepo forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"owner"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"private"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"html_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fork"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"git_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ssh_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"clone_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"hooks_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"svn_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"homepage"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"language"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"size"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"default_branch"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_issues"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_projects"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_wiki"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_pages"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"has_downloads"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"archived" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"disabled" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"pushed_at"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"created_at"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"updated_at"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"permissions"
instance ToJSON NewRepo where
toJSON :: NewRepo -> Value
toJSON (NewRepo { newRepoName :: NewRepo -> Name Repo
newRepoName = Name Repo
name
, newRepoDescription :: NewRepo -> Maybe Text
newRepoDescription = Maybe Text
description
, newRepoHomepage :: NewRepo -> Maybe Text
newRepoHomepage = Maybe Text
homepage
, newRepoPrivate :: NewRepo -> Maybe Bool
newRepoPrivate = Maybe Bool
private
, newRepoHasIssues :: NewRepo -> Maybe Bool
newRepoHasIssues = Maybe Bool
hasIssues
, newRepoHasProjects :: NewRepo -> Maybe Bool
newRepoHasProjects = Maybe Bool
hasProjects
, newRepoHasWiki :: NewRepo -> Maybe Bool
newRepoHasWiki = Maybe Bool
hasWiki
, newRepoAutoInit :: NewRepo -> Maybe Bool
newRepoAutoInit = Maybe Bool
autoInit
, newRepoGitignoreTemplate :: NewRepo -> Maybe Text
newRepoGitignoreTemplate = Maybe Text
gitignoreTemplate
, newRepoLicenseTemplate :: NewRepo -> Maybe Text
newRepoLicenseTemplate = Maybe Text
licenseTemplate
, newRepoAllowSquashMerge :: NewRepo -> Maybe Bool
newRepoAllowSquashMerge = Maybe Bool
allowSquashMerge
, newRepoAllowMergeCommit :: NewRepo -> Maybe Bool
newRepoAllowMergeCommit = Maybe Bool
allowMergeCommit
, newRepoAllowRebaseMerge :: NewRepo -> Maybe Bool
newRepoAllowRebaseMerge = Maybe Bool
allowRebaseMerge
}) = [Pair] -> Value
object
[ Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Name Repo
name
, Key
"description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
description
, Key
"homepage" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
homepage
, Key
"private" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
private
, Key
"has_issues" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
hasIssues
, Key
"has_projects" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
hasProjects
, Key
"has_wiki" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
hasWiki
, Key
"auto_init" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
autoInit
, Key
"gitignore_template" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
gitignoreTemplate
, Key
"license_template" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
licenseTemplate
, Key
"allow_squash_merge" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
allowSquashMerge
, Key
"allow_merge_commit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
allowMergeCommit
, Key
"allow_rebase_merge" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
allowRebaseMerge
]
instance ToJSON EditRepo where
toJSON :: EditRepo -> Value
toJSON (EditRepo { editName :: EditRepo -> Maybe (Name Repo)
editName = Maybe (Name Repo)
name
, editDescription :: EditRepo -> Maybe Text
editDescription = Maybe Text
description
, editHomepage :: EditRepo -> Maybe Text
editHomepage = Maybe Text
homepage
, editPrivate :: EditRepo -> Maybe Bool
editPrivate = Maybe Bool
private
, editHasIssues :: EditRepo -> Maybe Bool
editHasIssues = Maybe Bool
hasIssues
, editHasProjects :: EditRepo -> Maybe Bool
editHasProjects = Maybe Bool
hasProjects
, editHasWiki :: EditRepo -> Maybe Bool
editHasWiki = Maybe Bool
hasWiki
, editDefaultBranch :: EditRepo -> Maybe Text
editDefaultBranch = Maybe Text
defaultBranch
, editAllowSquashMerge :: EditRepo -> Maybe Bool
editAllowSquashMerge = Maybe Bool
allowSquashMerge
, editAllowMergeCommit :: EditRepo -> Maybe Bool
editAllowMergeCommit = Maybe Bool
allowMergeCommit
, editAllowRebaseMerge :: EditRepo -> Maybe Bool
editAllowRebaseMerge = Maybe Bool
allowRebaseMerge
, editArchived :: EditRepo -> Maybe Bool
editArchived = Maybe Bool
archived
}) = [Pair] -> Value
object
[ Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe (Name Repo)
name
, Key
"description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
description
, Key
"homepage" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
homepage
, Key
"private" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
private
, Key
"has_issues" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
hasIssues
, Key
"has_projects" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
hasProjects
, Key
"has_wiki" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
hasWiki
, Key
"default_branch" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
defaultBranch
, Key
"allow_squash_merge" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
allowSquashMerge
, Key
"allow_merge_commit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
allowMergeCommit
, Key
"allow_rebase_merge" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
allowRebaseMerge
, Key
"archived" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
archived
]
instance FromJSON RepoPermissions where
parseJSON :: Value -> Parser RepoPermissions
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RepoPermissions" forall a b. (a -> b) -> a -> b
$ \Object
o -> Bool -> Bool -> Bool -> RepoPermissions
RepoPermissions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"admin"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"push"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"pull"
instance FromJSON RepoRef where
parseJSON :: Value -> Parser RepoRef
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RepoRef" forall a b. (a -> b) -> a -> b
$ \Object
o -> SimpleOwner -> Name Repo -> RepoRef
RepoRef
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"owner"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
instance FromJSON Contributor where
parseJSON :: Value -> Parser Contributor
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Contributor" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Text
t <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
case (Text
t :: Text) of
Text
"Anonymous" -> Int -> Text -> Contributor
AnonymousContributor
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"contributions"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Text
_ -> Int -> URL -> Name User -> URL -> Id User -> Text -> Contributor
KnownContributor
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"contributions"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"avatar_url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"login"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"gravatar_id"
instance FromJSON Language where
parseJSON :: Value -> Parser Language
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"Language" (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Language
Language)
instance ToJSON Language where
toJSON :: Language -> Value
toJSON = forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. Language -> Text
getLanguage
#if MIN_VERSION_aeson(1,0,0)
instance FromJSONKey Language where
fromJSONKey :: FromJSONKeyFunction Language
fromJSONKey = forall a. Coercible Text a => FromJSONKeyFunction a
fromJSONKeyCoerce
#else
instance FromJSON a => FromJSON (HM.HashMap Language a) where
parseJSON = fmap mapKeyLanguage . parseJSON
where
mapKeyLanguage :: HM.HashMap Text a -> HM.HashMap Language a
#ifdef UNSAFE
mapKeyLanguage = unsafeCoerce
#else
mapKeyLanguage = mapKey Language
mapKey :: (Eq k2, Hashable k2) => (k1 -> k2) -> HM.HashMap k1 a -> HM.HashMap k2 a
mapKey f = HM.fromList . map (first f) . HM.toList
#endif
#endif
data ArchiveFormat
= ArchiveFormatTarball
| ArchiveFormatZipball
deriving (Int -> ArchiveFormat -> ShowS
[ArchiveFormat] -> ShowS
ArchiveFormat -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ArchiveFormat] -> ShowS
$cshowList :: [ArchiveFormat] -> ShowS
show :: ArchiveFormat -> String
$cshow :: ArchiveFormat -> String
showsPrec :: Int -> ArchiveFormat -> ShowS
$cshowsPrec :: Int -> ArchiveFormat -> ShowS
Show, ArchiveFormat -> ArchiveFormat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArchiveFormat -> ArchiveFormat -> Bool
$c/= :: ArchiveFormat -> ArchiveFormat -> Bool
== :: ArchiveFormat -> ArchiveFormat -> Bool
$c== :: ArchiveFormat -> ArchiveFormat -> Bool
Eq, Eq ArchiveFormat
ArchiveFormat -> ArchiveFormat -> Bool
ArchiveFormat -> ArchiveFormat -> Ordering
ArchiveFormat -> ArchiveFormat -> ArchiveFormat
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
min :: ArchiveFormat -> ArchiveFormat -> ArchiveFormat
$cmin :: ArchiveFormat -> ArchiveFormat -> ArchiveFormat
max :: ArchiveFormat -> ArchiveFormat -> ArchiveFormat
$cmax :: ArchiveFormat -> ArchiveFormat -> ArchiveFormat
>= :: ArchiveFormat -> ArchiveFormat -> Bool
$c>= :: ArchiveFormat -> ArchiveFormat -> Bool
> :: ArchiveFormat -> ArchiveFormat -> Bool
$c> :: ArchiveFormat -> ArchiveFormat -> Bool
<= :: ArchiveFormat -> ArchiveFormat -> Bool
$c<= :: ArchiveFormat -> ArchiveFormat -> Bool
< :: ArchiveFormat -> ArchiveFormat -> Bool
$c< :: ArchiveFormat -> ArchiveFormat -> Bool
compare :: ArchiveFormat -> ArchiveFormat -> Ordering
$ccompare :: ArchiveFormat -> ArchiveFormat -> Ordering
Ord, Int -> ArchiveFormat
ArchiveFormat -> Int
ArchiveFormat -> [ArchiveFormat]
ArchiveFormat -> ArchiveFormat
ArchiveFormat -> ArchiveFormat -> [ArchiveFormat]
ArchiveFormat -> ArchiveFormat -> ArchiveFormat -> [ArchiveFormat]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ArchiveFormat -> ArchiveFormat -> ArchiveFormat -> [ArchiveFormat]
$cenumFromThenTo :: ArchiveFormat -> ArchiveFormat -> ArchiveFormat -> [ArchiveFormat]
enumFromTo :: ArchiveFormat -> ArchiveFormat -> [ArchiveFormat]
$cenumFromTo :: ArchiveFormat -> ArchiveFormat -> [ArchiveFormat]
enumFromThen :: ArchiveFormat -> ArchiveFormat -> [ArchiveFormat]
$cenumFromThen :: ArchiveFormat -> ArchiveFormat -> [ArchiveFormat]
enumFrom :: ArchiveFormat -> [ArchiveFormat]
$cenumFrom :: ArchiveFormat -> [ArchiveFormat]
fromEnum :: ArchiveFormat -> Int
$cfromEnum :: ArchiveFormat -> Int
toEnum :: Int -> ArchiveFormat
$ctoEnum :: Int -> ArchiveFormat
pred :: ArchiveFormat -> ArchiveFormat
$cpred :: ArchiveFormat -> ArchiveFormat
succ :: ArchiveFormat -> ArchiveFormat
$csucc :: ArchiveFormat -> ArchiveFormat
Enum, ArchiveFormat
forall a. a -> a -> Bounded a
maxBound :: ArchiveFormat
$cmaxBound :: ArchiveFormat
minBound :: ArchiveFormat
$cminBound :: ArchiveFormat
Bounded, Typeable, Typeable ArchiveFormat
ArchiveFormat -> DataType
ArchiveFormat -> Constr
(forall b. Data b => b -> b) -> ArchiveFormat -> ArchiveFormat
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) -> ArchiveFormat -> u
forall u. (forall d. Data d => d -> u) -> ArchiveFormat -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArchiveFormat -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArchiveFormat -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArchiveFormat
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArchiveFormat -> c ArchiveFormat
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArchiveFormat)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ArchiveFormat)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ArchiveFormat -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ArchiveFormat -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ArchiveFormat -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ArchiveFormat -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArchiveFormat -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArchiveFormat -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArchiveFormat -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArchiveFormat -> r
gmapT :: (forall b. Data b => b -> b) -> ArchiveFormat -> ArchiveFormat
$cgmapT :: (forall b. Data b => b -> b) -> ArchiveFormat -> ArchiveFormat
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ArchiveFormat)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ArchiveFormat)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArchiveFormat)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArchiveFormat)
dataTypeOf :: ArchiveFormat -> DataType
$cdataTypeOf :: ArchiveFormat -> DataType
toConstr :: ArchiveFormat -> Constr
$ctoConstr :: ArchiveFormat -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArchiveFormat
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArchiveFormat
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArchiveFormat -> c ArchiveFormat
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArchiveFormat -> c ArchiveFormat
Data, forall x. Rep ArchiveFormat x -> ArchiveFormat
forall x. ArchiveFormat -> Rep ArchiveFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ArchiveFormat x -> ArchiveFormat
$cfrom :: forall x. ArchiveFormat -> Rep ArchiveFormat x
Generic)
instance IsPathPart ArchiveFormat where
toPathPart :: ArchiveFormat -> Text
toPathPart ArchiveFormat
af = case ArchiveFormat
af of
ArchiveFormat
ArchiveFormatTarball -> Text
"tarball"
ArchiveFormat
ArchiveFormatZipball -> Text
"zipball"
instance FromJSON CollaboratorPermission where
parseJSON :: Value -> Parser CollaboratorPermission
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"CollaboratorPermission" forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text -> Text
T.toLower Text
t of
Text
"admin" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure CollaboratorPermission
CollaboratorPermissionAdmin
Text
"write" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure CollaboratorPermission
CollaboratorPermissionWrite
Text
"read" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure CollaboratorPermission
CollaboratorPermissionRead
Text
"none" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure CollaboratorPermission
CollaboratorPermissionNone
Text
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Unknown CollaboratorPermission: " forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
t
instance ToJSON CollaboratorPermission where
toJSON :: CollaboratorPermission -> Value
toJSON CollaboratorPermission
CollaboratorPermissionAdmin = Value
"admin"
toJSON CollaboratorPermission
CollaboratorPermissionWrite = Value
"write"
toJSON CollaboratorPermission
CollaboratorPermissionRead = Value
"read"
toJSON CollaboratorPermission
CollaboratorPermissionNone = Value
"none"
instance FromJSON CollaboratorWithPermission where
parseJSON :: Value -> Parser CollaboratorWithPermission
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CollaboratorWithPermission" forall a b. (a -> b) -> a -> b
$ \Object
o -> SimpleUser -> CollaboratorPermission -> CollaboratorWithPermission
CollaboratorWithPermission
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"permission"