github-0.28.0.1: Access to the GitHub API, v3.
LicenseBSD-3-Clause
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellNone
LanguageHaskell2010

GitHub.Data.Repos

Description

This module also exports FromJSON a => FromJSON (HashMap Language a) orphan-ish instance for aeson < 1

Synopsis

Documentation

data Repo Source #

Instances

Instances details
Eq Repo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

(==) :: Repo -> Repo -> Bool #

(/=) :: Repo -> Repo -> Bool #

Data Repo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Repo -> c Repo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Repo #

toConstr :: Repo -> Constr #

dataTypeOf :: Repo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Repo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Repo) #

gmapT :: (forall b. Data b => b -> b) -> Repo -> Repo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Repo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Repo -> r #

gmapQ :: (forall d. Data d => d -> u) -> Repo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Repo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Repo -> m Repo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Repo -> m Repo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Repo -> m Repo #

Ord Repo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

compare :: Repo -> Repo -> Ordering #

(<) :: Repo -> Repo -> Bool #

(<=) :: Repo -> Repo -> Bool #

(>) :: Repo -> Repo -> Bool #

(>=) :: Repo -> Repo -> Bool #

max :: Repo -> Repo -> Repo #

min :: Repo -> Repo -> Repo #

Show Repo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

showsPrec :: Int -> Repo -> ShowS #

show :: Repo -> String #

showList :: [Repo] -> ShowS #

Generic Repo Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep Repo :: Type -> Type #

Methods

from :: Repo -> Rep Repo x #

to :: Rep Repo x -> Repo #

FromJSON Repo Source # 
Instance details

Defined in GitHub.Data.Repos

Binary Repo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

put :: Repo -> Put #

get :: Get Repo #

putList :: [Repo] -> Put #

NFData Repo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

rnf :: Repo -> () #

type Rep Repo Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep Repo = D1 ('MetaData "Repo" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "Repo" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "repoId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id Repo)) :*: S1 ('MetaSel ('Just "repoName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name Repo))) :*: (S1 ('MetaSel ('Just "repoOwner") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SimpleOwner) :*: S1 ('MetaSel ('Just "repoPrivate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "repoHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "repoDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "repoFork") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "repoUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))) :*: (((S1 ('MetaSel ('Just "repoGitUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "repoSshUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL))) :*: (S1 ('MetaSel ('Just "repoCloneUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "repoHooksUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "repoSvnUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "repoHomepage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "repoLanguage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Language)) :*: S1 ('MetaSel ('Just "repoForksCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))))) :*: ((((S1 ('MetaSel ('Just "repoStargazersCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "repoWatchersCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "repoSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "repoDefaultBranch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "repoOpenIssuesCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "repoHasIssues") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "repoHasProjects") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "repoHasWiki") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))))) :*: (((S1 ('MetaSel ('Just "repoHasPages") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "repoHasDownloads") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "repoArchived") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "repoDisabled") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "repoPushedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)) :*: S1 ('MetaSel ('Just "repoCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime))) :*: (S1 ('MetaSel ('Just "repoUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)) :*: S1 ('MetaSel ('Just "repoPermissions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe RepoPermissions))))))))

data CodeSearchRepo Source #

Instances

Instances details
Eq CodeSearchRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Data CodeSearchRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CodeSearchRepo -> c CodeSearchRepo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CodeSearchRepo #

toConstr :: CodeSearchRepo -> Constr #

dataTypeOf :: CodeSearchRepo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CodeSearchRepo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CodeSearchRepo) #

gmapT :: (forall b. Data b => b -> b) -> CodeSearchRepo -> CodeSearchRepo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CodeSearchRepo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CodeSearchRepo -> r #

gmapQ :: (forall d. Data d => d -> u) -> CodeSearchRepo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CodeSearchRepo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CodeSearchRepo -> m CodeSearchRepo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CodeSearchRepo -> m CodeSearchRepo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CodeSearchRepo -> m CodeSearchRepo #

Ord CodeSearchRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Show CodeSearchRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Generic CodeSearchRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep CodeSearchRepo :: Type -> Type #

FromJSON CodeSearchRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Binary CodeSearchRepo Source # 
Instance details

Defined in GitHub.Data.Repos

NFData CodeSearchRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

rnf :: CodeSearchRepo -> () #

type Rep CodeSearchRepo Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep CodeSearchRepo = D1 ('MetaData "CodeSearchRepo" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "CodeSearchRepo" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "codeSearchRepoId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id Repo)) :*: (S1 ('MetaSel ('Just "codeSearchRepoName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name Repo)) :*: S1 ('MetaSel ('Just "codeSearchRepoOwner") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SimpleOwner))) :*: ((S1 ('MetaSel ('Just "codeSearchRepoPrivate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "codeSearchRepoHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "codeSearchRepoDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "codeSearchRepoFork") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))))) :*: ((S1 ('MetaSel ('Just "codeSearchRepoUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "codeSearchRepoGitUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "codeSearchRepoSshUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)))) :*: ((S1 ('MetaSel ('Just "codeSearchRepoCloneUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "codeSearchRepoHooksUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "codeSearchRepoSvnUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "codeSearchRepoHomepage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))))) :*: (((S1 ('MetaSel ('Just "codeSearchRepoLanguage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Language)) :*: (S1 ('MetaSel ('Just "codeSearchRepoSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "codeSearchRepoDefaultBranch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "codeSearchRepoHasIssues") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "codeSearchRepoHasProjects") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "codeSearchRepoHasWiki") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "codeSearchRepoHasPages") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))))) :*: ((S1 ('MetaSel ('Just "codeSearchRepoHasDownloads") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "codeSearchRepoArchived") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "codeSearchRepoDisabled") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "codeSearchRepoPushedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)) :*: S1 ('MetaSel ('Just "codeSearchRepoCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime))) :*: (S1 ('MetaSel ('Just "codeSearchRepoUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)) :*: S1 ('MetaSel ('Just "codeSearchRepoPermissions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe RepoPermissions))))))))

data RepoPermissions Source #

Repository permissions, as they relate to the authenticated user.

Returned by for example currentUserReposR

Instances

Instances details
Eq RepoPermissions Source # 
Instance details

Defined in GitHub.Data.Repos

Data RepoPermissions Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoPermissions -> c RepoPermissions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoPermissions #

toConstr :: RepoPermissions -> Constr #

dataTypeOf :: RepoPermissions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RepoPermissions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoPermissions) #

gmapT :: (forall b. Data b => b -> b) -> RepoPermissions -> RepoPermissions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoPermissions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoPermissions -> r #

gmapQ :: (forall d. Data d => d -> u) -> RepoPermissions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoPermissions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoPermissions -> m RepoPermissions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoPermissions -> m RepoPermissions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoPermissions -> m RepoPermissions #

Ord RepoPermissions Source # 
Instance details

Defined in GitHub.Data.Repos

Show RepoPermissions Source # 
Instance details

Defined in GitHub.Data.Repos

Generic RepoPermissions Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep RepoPermissions :: Type -> Type #

FromJSON RepoPermissions Source # 
Instance details

Defined in GitHub.Data.Repos

Binary RepoPermissions Source # 
Instance details

Defined in GitHub.Data.Repos

NFData RepoPermissions Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

rnf :: RepoPermissions -> () #

type Rep RepoPermissions Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep RepoPermissions = D1 ('MetaData "RepoPermissions" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "RepoPermissions" 'PrefixI 'True) (S1 ('MetaSel ('Just "repoPermissionAdmin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "repoPermissionPush") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "repoPermissionPull") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))))

data RepoRef Source #

Constructors

RepoRef 

Instances

Instances details
Eq RepoRef Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

(==) :: RepoRef -> RepoRef -> Bool #

(/=) :: RepoRef -> RepoRef -> Bool #

Data RepoRef Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoRef -> c RepoRef #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoRef #

toConstr :: RepoRef -> Constr #

dataTypeOf :: RepoRef -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RepoRef) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoRef) #

gmapT :: (forall b. Data b => b -> b) -> RepoRef -> RepoRef #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoRef -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoRef -> r #

gmapQ :: (forall d. Data d => d -> u) -> RepoRef -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoRef -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoRef -> m RepoRef #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoRef -> m RepoRef #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoRef -> m RepoRef #

Ord RepoRef Source # 
Instance details

Defined in GitHub.Data.Repos

Show RepoRef Source # 
Instance details

Defined in GitHub.Data.Repos

Generic RepoRef Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep RepoRef :: Type -> Type #

Methods

from :: RepoRef -> Rep RepoRef x #

to :: Rep RepoRef x -> RepoRef #

FromJSON RepoRef Source # 
Instance details

Defined in GitHub.Data.Repos

Binary RepoRef Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

put :: RepoRef -> Put #

get :: Get RepoRef #

putList :: [RepoRef] -> Put #

NFData RepoRef Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

rnf :: RepoRef -> () #

type Rep RepoRef Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep RepoRef = D1 ('MetaData "RepoRef" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "RepoRef" 'PrefixI 'True) (S1 ('MetaSel ('Just "repoRefOwner") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SimpleOwner) :*: S1 ('MetaSel ('Just "repoRefRepo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name Repo))))

data NewRepo Source #

Instances

Instances details
Eq NewRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

(==) :: NewRepo -> NewRepo -> Bool #

(/=) :: NewRepo -> NewRepo -> Bool #

Data NewRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewRepo -> c NewRepo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewRepo #

toConstr :: NewRepo -> Constr #

dataTypeOf :: NewRepo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NewRepo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewRepo) #

gmapT :: (forall b. Data b => b -> b) -> NewRepo -> NewRepo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewRepo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewRepo -> r #

gmapQ :: (forall d. Data d => d -> u) -> NewRepo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NewRepo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewRepo -> m NewRepo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewRepo -> m NewRepo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewRepo -> m NewRepo #

Ord NewRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Show NewRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Generic NewRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep NewRepo :: Type -> Type #

Methods

from :: NewRepo -> Rep NewRepo x #

to :: Rep NewRepo x -> NewRepo #

ToJSON NewRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Binary NewRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

put :: NewRepo -> Put #

get :: Get NewRepo #

putList :: [NewRepo] -> Put #

NFData NewRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

rnf :: NewRepo -> () #

type Rep NewRepo Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep NewRepo = D1 ('MetaData "NewRepo" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "NewRepo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "newRepoName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name Repo)) :*: (S1 ('MetaSel ('Just "newRepoDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "newRepoHomepage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 ('MetaSel ('Just "newRepoPrivate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "newRepoHasIssues") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "newRepoHasProjects") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))))) :*: ((S1 ('MetaSel ('Just "newRepoHasWiki") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "newRepoAutoInit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "newRepoGitignoreTemplate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "newRepoLicenseTemplate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "newRepoAllowSquashMerge") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "newRepoAllowMergeCommit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "newRepoAllowRebaseMerge") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)))))))

data EditRepo Source #

Instances

Instances details
Eq EditRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Data EditRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EditRepo -> c EditRepo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EditRepo #

toConstr :: EditRepo -> Constr #

dataTypeOf :: EditRepo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EditRepo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EditRepo) #

gmapT :: (forall b. Data b => b -> b) -> EditRepo -> EditRepo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EditRepo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EditRepo -> r #

gmapQ :: (forall d. Data d => d -> u) -> EditRepo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EditRepo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EditRepo -> m EditRepo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EditRepo -> m EditRepo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EditRepo -> m EditRepo #

Ord EditRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Show EditRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Generic EditRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep EditRepo :: Type -> Type #

Methods

from :: EditRepo -> Rep EditRepo x #

to :: Rep EditRepo x -> EditRepo #

ToJSON EditRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Binary EditRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

put :: EditRepo -> Put #

get :: Get EditRepo #

putList :: [EditRepo] -> Put #

NFData EditRepo Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

rnf :: EditRepo -> () #

type Rep EditRepo Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep EditRepo = D1 ('MetaData "EditRepo" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "EditRepo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "editName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Name Repo))) :*: (S1 ('MetaSel ('Just "editDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "editHomepage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 ('MetaSel ('Just "editPrivate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "editHasIssues") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "editHasProjects") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))))) :*: ((S1 ('MetaSel ('Just "editHasWiki") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "editDefaultBranch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "editAllowSquashMerge") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)))) :*: (S1 ('MetaSel ('Just "editAllowMergeCommit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "editAllowRebaseMerge") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "editArchived") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)))))))

data RepoPublicity Source #

Filter the list of the user's repos using any of these constructors.

Constructors

RepoPublicityAll

All repos accessible to the user.

RepoPublicityOwner

Only repos owned by the user.

RepoPublicityPublic

Only public repos.

RepoPublicityPrivate

Only private repos.

RepoPublicityMember

Only repos to which the user is a member but not an owner.

Instances

Instances details
Bounded RepoPublicity Source # 
Instance details

Defined in GitHub.Data.Repos

Enum RepoPublicity Source # 
Instance details

Defined in GitHub.Data.Repos

Eq RepoPublicity Source # 
Instance details

Defined in GitHub.Data.Repos

Data RepoPublicity Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoPublicity -> c RepoPublicity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoPublicity #

toConstr :: RepoPublicity -> Constr #

dataTypeOf :: RepoPublicity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RepoPublicity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoPublicity) #

gmapT :: (forall b. Data b => b -> b) -> RepoPublicity -> RepoPublicity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoPublicity -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoPublicity -> r #

gmapQ :: (forall d. Data d => d -> u) -> RepoPublicity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoPublicity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoPublicity -> m RepoPublicity #

Ord RepoPublicity Source # 
Instance details

Defined in GitHub.Data.Repos

Show RepoPublicity Source # 
Instance details

Defined in GitHub.Data.Repos

Generic RepoPublicity Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep RepoPublicity :: Type -> Type #

type Rep RepoPublicity Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep RepoPublicity = D1 ('MetaData "RepoPublicity" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) ((C1 ('MetaCons "RepoPublicityAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RepoPublicityOwner" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RepoPublicityPublic" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RepoPublicityPrivate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RepoPublicityMember" 'PrefixI 'False) (U1 :: Type -> Type))))

type Languages = HashMap Language Int Source #

The value is the number of bytes of code written in that language.

newtype Language Source #

A programming language.

Constructors

Language Text 

Instances

Instances details
Eq Language Source # 
Instance details

Defined in GitHub.Data.Repos

Data Language Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Language -> c Language #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Language #

toConstr :: Language -> Constr #

dataTypeOf :: Language -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Language) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Language) #

gmapT :: (forall b. Data b => b -> b) -> Language -> Language #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Language -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Language -> r #

gmapQ :: (forall d. Data d => d -> u) -> Language -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Language -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Language -> m Language #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Language -> m Language #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Language -> m Language #

Ord Language Source # 
Instance details

Defined in GitHub.Data.Repos

Show Language Source # 
Instance details

Defined in GitHub.Data.Repos

IsString Language Source # 
Instance details

Defined in GitHub.Data.Repos

Generic Language Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep Language :: Type -> Type #

Methods

from :: Language -> Rep Language x #

to :: Rep Language x -> Language #

Hashable Language Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

hashWithSalt :: Int -> Language -> Int #

hash :: Language -> Int #

ToJSON Language Source # 
Instance details

Defined in GitHub.Data.Repos

FromJSON Language Source # 
Instance details

Defined in GitHub.Data.Repos

FromJSONKey Language Source # 
Instance details

Defined in GitHub.Data.Repos

Binary Language Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

put :: Language -> Put #

get :: Get Language #

putList :: [Language] -> Put #

NFData Language Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

rnf :: Language -> () #

type Rep Language Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep Language = D1 ('MetaData "Language" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'True) (C1 ('MetaCons "Language" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Contributor Source #

Constructors

KnownContributor !Int !URL !(Name User) !URL !(Id User) !Text

An existing Github user, with their number of contributions, avatar URL, login, URL, ID, and Gravatar ID.

AnonymousContributor !Int !Text

An unknown Github user with their number of contributions and recorded name.

Instances

Instances details
Eq Contributor Source # 
Instance details

Defined in GitHub.Data.Repos

Data Contributor Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Contributor -> c Contributor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Contributor #

toConstr :: Contributor -> Constr #

dataTypeOf :: Contributor -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Contributor) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contributor) #

gmapT :: (forall b. Data b => b -> b) -> Contributor -> Contributor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Contributor -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Contributor -> r #

gmapQ :: (forall d. Data d => d -> u) -> Contributor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Contributor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Contributor -> m Contributor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Contributor -> m Contributor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Contributor -> m Contributor #

Ord Contributor Source # 
Instance details

Defined in GitHub.Data.Repos

Show Contributor Source # 
Instance details

Defined in GitHub.Data.Repos

Generic Contributor Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep Contributor :: Type -> Type #

FromJSON Contributor Source # 
Instance details

Defined in GitHub.Data.Repos

Binary Contributor Source # 
Instance details

Defined in GitHub.Data.Repos

NFData Contributor Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

rnf :: Contributor -> () #

type Rep Contributor Source # 
Instance details

Defined in GitHub.Data.Repos

data CollaboratorPermission Source #

Instances

Instances details
Bounded CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Enum CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Eq CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Data CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CollaboratorPermission -> c CollaboratorPermission #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CollaboratorPermission #

toConstr :: CollaboratorPermission -> Constr #

dataTypeOf :: CollaboratorPermission -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CollaboratorPermission) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CollaboratorPermission) #

gmapT :: (forall b. Data b => b -> b) -> CollaboratorPermission -> CollaboratorPermission #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CollaboratorPermission -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CollaboratorPermission -> r #

gmapQ :: (forall d. Data d => d -> u) -> CollaboratorPermission -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CollaboratorPermission -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CollaboratorPermission -> m CollaboratorPermission #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CollaboratorPermission -> m CollaboratorPermission #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CollaboratorPermission -> m CollaboratorPermission #

Ord CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Show CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Generic CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep CollaboratorPermission :: Type -> Type #

ToJSON CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

FromJSON CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Binary CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

NFData CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

rnf :: CollaboratorPermission -> () #

type Rep CollaboratorPermission Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep CollaboratorPermission = D1 ('MetaData "CollaboratorPermission" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) ((C1 ('MetaCons "CollaboratorPermissionAdmin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CollaboratorPermissionWrite" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CollaboratorPermissionRead" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CollaboratorPermissionNone" 'PrefixI 'False) (U1 :: Type -> Type)))

data CollaboratorWithPermission Source #

Instances

Instances details
Eq CollaboratorWithPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Data CollaboratorWithPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CollaboratorWithPermission -> c CollaboratorWithPermission #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CollaboratorWithPermission #

toConstr :: CollaboratorWithPermission -> Constr #

dataTypeOf :: CollaboratorWithPermission -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CollaboratorWithPermission) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CollaboratorWithPermission) #

gmapT :: (forall b. Data b => b -> b) -> CollaboratorWithPermission -> CollaboratorWithPermission #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CollaboratorWithPermission -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CollaboratorWithPermission -> r #

gmapQ :: (forall d. Data d => d -> u) -> CollaboratorWithPermission -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CollaboratorWithPermission -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CollaboratorWithPermission -> m CollaboratorWithPermission #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CollaboratorWithPermission -> m CollaboratorWithPermission #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CollaboratorWithPermission -> m CollaboratorWithPermission #

Ord CollaboratorWithPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Show CollaboratorWithPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Generic CollaboratorWithPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep CollaboratorWithPermission :: Type -> Type #

FromJSON CollaboratorWithPermission Source # 
Instance details

Defined in GitHub.Data.Repos

Binary CollaboratorWithPermission Source # 
Instance details

Defined in GitHub.Data.Repos

NFData CollaboratorWithPermission Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep CollaboratorWithPermission Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep CollaboratorWithPermission = D1 ('MetaData "CollaboratorWithPermission" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "CollaboratorWithPermission" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SimpleUser) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CollaboratorPermission)))

data ArchiveFormat Source #

Constructors

ArchiveFormatTarball

".tar.gz" format

ArchiveFormatZipball

".zip" format

Instances

Instances details
Bounded ArchiveFormat Source # 
Instance details

Defined in GitHub.Data.Repos

Enum ArchiveFormat Source # 
Instance details

Defined in GitHub.Data.Repos

Eq ArchiveFormat Source # 
Instance details

Defined in GitHub.Data.Repos

Data ArchiveFormat Source # 
Instance details

Defined in GitHub.Data.Repos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArchiveFormat -> c ArchiveFormat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArchiveFormat #

toConstr :: ArchiveFormat -> Constr #

dataTypeOf :: ArchiveFormat -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArchiveFormat) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArchiveFormat) #

gmapT :: (forall b. Data b => b -> b) -> ArchiveFormat -> ArchiveFormat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArchiveFormat -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArchiveFormat -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArchiveFormat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArchiveFormat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArchiveFormat -> m ArchiveFormat #

Ord ArchiveFormat Source # 
Instance details

Defined in GitHub.Data.Repos

Show ArchiveFormat Source # 
Instance details

Defined in GitHub.Data.Repos

Generic ArchiveFormat Source # 
Instance details

Defined in GitHub.Data.Repos

Associated Types

type Rep ArchiveFormat :: Type -> Type #

IsPathPart ArchiveFormat Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep ArchiveFormat Source # 
Instance details

Defined in GitHub.Data.Repos

type Rep ArchiveFormat = D1 ('MetaData "ArchiveFormat" "GitHub.Data.Repos" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "ArchiveFormatTarball" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArchiveFormatZipball" 'PrefixI 'False) (U1 :: Type -> Type))