Safe Haskell | None |
---|---|
Language | Haskell2010 |
GitHub.Data.Repos
Description
Synopsis
- data Repo = Repo {
- repoId :: !(Id Repo)
- repoName :: !(Name Repo)
- repoOwner :: !SimpleOwner
- repoPrivate :: !Bool
- repoHtmlUrl :: !URL
- repoDescription :: !(Maybe Text)
- repoFork :: !(Maybe Bool)
- repoUrl :: !URL
- repoGitUrl :: !(Maybe URL)
- repoSshUrl :: !(Maybe URL)
- repoCloneUrl :: !(Maybe URL)
- repoHooksUrl :: !URL
- repoSvnUrl :: !(Maybe URL)
- repoHomepage :: !(Maybe Text)
- repoLanguage :: !(Maybe Language)
- repoForksCount :: !Int
- repoStargazersCount :: !Int
- repoWatchersCount :: !Int
- repoSize :: !(Maybe Int)
- repoDefaultBranch :: !(Maybe Text)
- repoOpenIssuesCount :: !Int
- repoHasIssues :: !(Maybe Bool)
- repoHasProjects :: !(Maybe Bool)
- repoHasWiki :: !(Maybe Bool)
- repoHasPages :: !(Maybe Bool)
- repoHasDownloads :: !(Maybe Bool)
- repoArchived :: !Bool
- repoDisabled :: !Bool
- repoPushedAt :: !(Maybe UTCTime)
- repoCreatedAt :: !(Maybe UTCTime)
- repoUpdatedAt :: !(Maybe UTCTime)
- repoPermissions :: !(Maybe RepoPermissions)
- data CodeSearchRepo = CodeSearchRepo {
- codeSearchRepoId :: !(Id Repo)
- codeSearchRepoName :: !(Name Repo)
- codeSearchRepoOwner :: !SimpleOwner
- codeSearchRepoPrivate :: !Bool
- codeSearchRepoHtmlUrl :: !URL
- codeSearchRepoDescription :: !(Maybe Text)
- codeSearchRepoFork :: !(Maybe Bool)
- codeSearchRepoUrl :: !URL
- codeSearchRepoGitUrl :: !(Maybe URL)
- codeSearchRepoSshUrl :: !(Maybe URL)
- codeSearchRepoCloneUrl :: !(Maybe URL)
- codeSearchRepoHooksUrl :: !URL
- codeSearchRepoSvnUrl :: !(Maybe URL)
- codeSearchRepoHomepage :: !(Maybe Text)
- codeSearchRepoLanguage :: !(Maybe Language)
- codeSearchRepoSize :: !(Maybe Int)
- codeSearchRepoDefaultBranch :: !(Maybe Text)
- codeSearchRepoHasIssues :: !(Maybe Bool)
- codeSearchRepoHasProjects :: !(Maybe Bool)
- codeSearchRepoHasWiki :: !(Maybe Bool)
- codeSearchRepoHasPages :: !(Maybe Bool)
- codeSearchRepoHasDownloads :: !(Maybe Bool)
- codeSearchRepoArchived :: !Bool
- codeSearchRepoDisabled :: !Bool
- codeSearchRepoPushedAt :: !(Maybe UTCTime)
- codeSearchRepoCreatedAt :: !(Maybe UTCTime)
- codeSearchRepoUpdatedAt :: !(Maybe UTCTime)
- codeSearchRepoPermissions :: !(Maybe RepoPermissions)
- data RepoPermissions = RepoPermissions {}
- data RepoRef = RepoRef {
- repoRefOwner :: !SimpleOwner
- repoRefRepo :: !(Name Repo)
- data NewRepo = NewRepo {
- newRepoName :: !(Name Repo)
- newRepoDescription :: !(Maybe Text)
- newRepoHomepage :: !(Maybe Text)
- newRepoPrivate :: !(Maybe Bool)
- newRepoHasIssues :: !(Maybe Bool)
- newRepoHasProjects :: !(Maybe Bool)
- newRepoHasWiki :: !(Maybe Bool)
- newRepoAutoInit :: !(Maybe Bool)
- newRepoGitignoreTemplate :: !(Maybe Text)
- newRepoLicenseTemplate :: !(Maybe Text)
- newRepoAllowSquashMerge :: !(Maybe Bool)
- newRepoAllowMergeCommit :: !(Maybe Bool)
- newRepoAllowRebaseMerge :: !(Maybe Bool)
- newRepo :: Name Repo -> NewRepo
- data EditRepo = EditRepo {
- editName :: !(Maybe (Name Repo))
- editDescription :: !(Maybe Text)
- editHomepage :: !(Maybe Text)
- editPrivate :: !(Maybe Bool)
- editHasIssues :: !(Maybe Bool)
- editHasProjects :: !(Maybe Bool)
- editHasWiki :: !(Maybe Bool)
- editDefaultBranch :: !(Maybe Text)
- editAllowSquashMerge :: !(Maybe Bool)
- editAllowMergeCommit :: !(Maybe Bool)
- editAllowRebaseMerge :: !(Maybe Bool)
- editArchived :: !(Maybe Bool)
- data RepoPublicity
- type Languages = HashMap Language Int
- newtype Language = Language Text
- getLanguage :: Language -> Text
- data Contributor
- contributorToSimpleUser :: Contributor -> Maybe SimpleUser
- data CollaboratorPermission
- data CollaboratorWithPermission = CollaboratorWithPermission SimpleUser CollaboratorPermission
- data ArchiveFormat
Documentation
Constructors
Instances
data CodeSearchRepo Source #
Constructors
CodeSearchRepo | |
Fields
|
Instances
FromJSON CodeSearchRepo Source # | |||||
Defined in GitHub.Data.Repos Methods parseJSON :: Value -> Parser CodeSearchRepo # parseJSONList :: Value -> Parser [CodeSearchRepo] # | |||||
Data CodeSearchRepo Source # | |||||
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 # | |||||
Generic CodeSearchRepo Source # | |||||
Defined in GitHub.Data.Repos Associated Types
Methods from :: CodeSearchRepo -> Rep CodeSearchRepo x # to :: Rep CodeSearchRepo x -> CodeSearchRepo # | |||||
Show CodeSearchRepo Source # | |||||
Defined in GitHub.Data.Repos Methods showsPrec :: Int -> CodeSearchRepo -> ShowS # show :: CodeSearchRepo -> String # showList :: [CodeSearchRepo] -> ShowS # | |||||
Binary CodeSearchRepo Source # | |||||
Defined in GitHub.Data.Repos Methods put :: CodeSearchRepo -> Put # get :: Get CodeSearchRepo # putList :: [CodeSearchRepo] -> Put # | |||||
NFData CodeSearchRepo Source # | |||||
Defined in GitHub.Data.Repos Methods rnf :: CodeSearchRepo -> () # | |||||
Eq CodeSearchRepo Source # | |||||
Defined in GitHub.Data.Repos Methods (==) :: CodeSearchRepo -> CodeSearchRepo -> Bool # (/=) :: CodeSearchRepo -> CodeSearchRepo -> Bool # | |||||
Ord CodeSearchRepo Source # | |||||
Defined in GitHub.Data.Repos Methods compare :: CodeSearchRepo -> CodeSearchRepo -> Ordering # (<) :: CodeSearchRepo -> CodeSearchRepo -> Bool # (<=) :: CodeSearchRepo -> CodeSearchRepo -> Bool # (>) :: CodeSearchRepo -> CodeSearchRepo -> Bool # (>=) :: CodeSearchRepo -> CodeSearchRepo -> Bool # max :: CodeSearchRepo -> CodeSearchRepo -> CodeSearchRepo # min :: CodeSearchRepo -> CodeSearchRepo -> CodeSearchRepo # | |||||
type Rep CodeSearchRepo Source # | |||||
Defined in GitHub.Data.Repos type Rep CodeSearchRepo = D1 ('MetaData "CodeSearchRepo" "GitHub.Data.Repos" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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
Constructors
RepoPermissions | |
Fields
|
Instances
FromJSON RepoPermissions Source # | |||||
Defined in GitHub.Data.Repos Methods parseJSON :: Value -> Parser RepoPermissions # parseJSONList :: Value -> Parser [RepoPermissions] # | |||||
Data RepoPermissions Source # | |||||
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 # | |||||
Generic RepoPermissions Source # | |||||
Defined in GitHub.Data.Repos Associated Types
Methods from :: RepoPermissions -> Rep RepoPermissions x # to :: Rep RepoPermissions x -> RepoPermissions # | |||||
Show RepoPermissions Source # | |||||
Defined in GitHub.Data.Repos Methods showsPrec :: Int -> RepoPermissions -> ShowS # show :: RepoPermissions -> String # showList :: [RepoPermissions] -> ShowS # | |||||
Binary RepoPermissions Source # | |||||
Defined in GitHub.Data.Repos Methods put :: RepoPermissions -> Put # get :: Get RepoPermissions # putList :: [RepoPermissions] -> Put # | |||||
NFData RepoPermissions Source # | |||||
Defined in GitHub.Data.Repos Methods rnf :: RepoPermissions -> () # | |||||
Eq RepoPermissions Source # | |||||
Defined in GitHub.Data.Repos Methods (==) :: RepoPermissions -> RepoPermissions -> Bool # (/=) :: RepoPermissions -> RepoPermissions -> Bool # | |||||
Ord RepoPermissions Source # | |||||
Defined in GitHub.Data.Repos Methods compare :: RepoPermissions -> RepoPermissions -> Ordering # (<) :: RepoPermissions -> RepoPermissions -> Bool # (<=) :: RepoPermissions -> RepoPermissions -> Bool # (>) :: RepoPermissions -> RepoPermissions -> Bool # (>=) :: RepoPermissions -> RepoPermissions -> Bool # max :: RepoPermissions -> RepoPermissions -> RepoPermissions # min :: RepoPermissions -> RepoPermissions -> RepoPermissions # | |||||
type Rep RepoPermissions Source # | |||||
Defined in GitHub.Data.Repos type Rep RepoPermissions = D1 ('MetaData "RepoPermissions" "GitHub.Data.Repos" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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)))) |
Constructors
RepoRef | |
Fields
|
Instances
FromJSON RepoRef Source # | |||||
Defined in GitHub.Data.Repos | |||||
Data RepoRef Source # | |||||
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 # | |||||
Generic RepoRef Source # | |||||
Defined in GitHub.Data.Repos Associated Types
| |||||
Show RepoRef Source # | |||||
Binary RepoRef Source # | |||||
NFData RepoRef Source # | |||||
Defined in GitHub.Data.Repos | |||||
Eq RepoRef Source # | |||||
Ord RepoRef Source # | |||||
type Rep RepoRef Source # | |||||
Defined in GitHub.Data.Repos type Rep RepoRef = D1 ('MetaData "RepoRef" "GitHub.Data.Repos" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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)))) |
Constructors
NewRepo | |
Fields
|
Instances
ToJSON NewRepo Source # | |||||
Data NewRepo Source # | |||||
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 # | |||||
Generic NewRepo Source # | |||||
Defined in GitHub.Data.Repos Associated Types
| |||||
Show NewRepo Source # | |||||
Binary NewRepo Source # | |||||
NFData NewRepo Source # | |||||
Defined in GitHub.Data.Repos | |||||
Eq NewRepo Source # | |||||
Ord NewRepo Source # | |||||
type Rep NewRepo Source # | |||||
Defined in GitHub.Data.Repos type Rep NewRepo = D1 ('MetaData "NewRepo" "GitHub.Data.Repos" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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))))))) |
Constructors
EditRepo | |
Fields
|
Instances
ToJSON EditRepo Source # | |||||
Data EditRepo Source # | |||||
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 # | |||||
Generic EditRepo Source # | |||||
Defined in GitHub.Data.Repos Associated Types
| |||||
Show EditRepo Source # | |||||
Binary EditRepo Source # | |||||
NFData EditRepo Source # | |||||
Defined in GitHub.Data.Repos | |||||
Eq EditRepo Source # | |||||
Ord EditRepo Source # | |||||
Defined in GitHub.Data.Repos | |||||
type Rep EditRepo Source # | |||||
Defined in GitHub.Data.Repos type Rep EditRepo = D1 ('MetaData "EditRepo" "GitHub.Data.Repos" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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
Data RepoPublicity Source # | |||||
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 # | |||||
Bounded RepoPublicity Source # | |||||
Defined in GitHub.Data.Repos | |||||
Enum RepoPublicity Source # | |||||
Defined in GitHub.Data.Repos Methods succ :: RepoPublicity -> RepoPublicity # pred :: RepoPublicity -> RepoPublicity # toEnum :: Int -> RepoPublicity # fromEnum :: RepoPublicity -> Int # enumFrom :: RepoPublicity -> [RepoPublicity] # enumFromThen :: RepoPublicity -> RepoPublicity -> [RepoPublicity] # enumFromTo :: RepoPublicity -> RepoPublicity -> [RepoPublicity] # enumFromThenTo :: RepoPublicity -> RepoPublicity -> RepoPublicity -> [RepoPublicity] # | |||||
Generic RepoPublicity Source # | |||||
Defined in GitHub.Data.Repos Associated Types
| |||||
Show RepoPublicity Source # | |||||
Defined in GitHub.Data.Repos Methods showsPrec :: Int -> RepoPublicity -> ShowS # show :: RepoPublicity -> String # showList :: [RepoPublicity] -> ShowS # | |||||
Eq RepoPublicity Source # | |||||
Defined in GitHub.Data.Repos Methods (==) :: RepoPublicity -> RepoPublicity -> Bool # (/=) :: RepoPublicity -> RepoPublicity -> Bool # | |||||
Ord RepoPublicity Source # | |||||
Defined in GitHub.Data.Repos Methods compare :: RepoPublicity -> RepoPublicity -> Ordering # (<) :: RepoPublicity -> RepoPublicity -> Bool # (<=) :: RepoPublicity -> RepoPublicity -> Bool # (>) :: RepoPublicity -> RepoPublicity -> Bool # (>=) :: RepoPublicity -> RepoPublicity -> Bool # max :: RepoPublicity -> RepoPublicity -> RepoPublicity # min :: RepoPublicity -> RepoPublicity -> RepoPublicity # | |||||
type Rep RepoPublicity Source # | |||||
Defined in GitHub.Data.Repos type Rep RepoPublicity = D1 ('MetaData "RepoPublicity" "GitHub.Data.Repos" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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.
A programming language.
Instances
FromJSON Language Source # | |||||
Defined in GitHub.Data.Repos | |||||
FromJSONKey Language Source # | |||||
Defined in GitHub.Data.Repos Methods | |||||
ToJSON Language Source # | |||||
Data Language Source # | |||||
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 # | |||||
IsString Language Source # | |||||
Defined in GitHub.Data.Repos Methods fromString :: String -> Language # | |||||
Generic Language Source # | |||||
Defined in GitHub.Data.Repos Associated Types
| |||||
Show Language Source # | |||||
Binary Language Source # | |||||
NFData Language Source # | |||||
Defined in GitHub.Data.Repos | |||||
Eq Language Source # | |||||
Ord Language Source # | |||||
Defined in GitHub.Data.Repos | |||||
Hashable Language Source # | |||||
Defined in GitHub.Data.Repos | |||||
type Rep Language Source # | |||||
Defined in GitHub.Data.Repos |
getLanguage :: Language -> Text Source #
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
FromJSON Contributor Source # | |||||
Defined in GitHub.Data.Repos | |||||
Data Contributor Source # | |||||
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 # | |||||
Generic Contributor Source # | |||||
Defined in GitHub.Data.Repos Associated Types
| |||||
Show Contributor Source # | |||||
Defined in GitHub.Data.Repos Methods showsPrec :: Int -> Contributor -> ShowS # show :: Contributor -> String # showList :: [Contributor] -> ShowS # | |||||
Binary Contributor Source # | |||||
Defined in GitHub.Data.Repos | |||||
NFData Contributor Source # | |||||
Defined in GitHub.Data.Repos Methods rnf :: Contributor -> () # | |||||
Eq Contributor Source # | |||||
Defined in GitHub.Data.Repos | |||||
Ord Contributor Source # | |||||
Defined in GitHub.Data.Repos Methods compare :: Contributor -> Contributor -> Ordering # (<) :: Contributor -> Contributor -> Bool # (<=) :: Contributor -> Contributor -> Bool # (>) :: Contributor -> Contributor -> Bool # (>=) :: Contributor -> Contributor -> Bool # max :: Contributor -> Contributor -> Contributor # min :: Contributor -> Contributor -> Contributor # | |||||
type Rep Contributor Source # | |||||
Defined in GitHub.Data.Repos type Rep Contributor = D1 ('MetaData "Contributor" "GitHub.Data.Repos" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "KnownContributor" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Name User)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id User)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :+: C1 ('MetaCons "AnonymousContributor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |
data CollaboratorPermission Source #
The permission of a collaborator on a repository. See https://developer.github.com/v3/repos/collaborators/#review-a-users-permission-level
Constructors
CollaboratorPermissionAdmin | |
CollaboratorPermissionWrite | |
CollaboratorPermissionRead | |
CollaboratorPermissionNone |
Instances
FromJSON CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos Methods parseJSON :: Value -> Parser CollaboratorPermission # parseJSONList :: Value -> Parser [CollaboratorPermission] # | |||||
ToJSON CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos Methods toJSON :: CollaboratorPermission -> Value # toEncoding :: CollaboratorPermission -> Encoding # toJSONList :: [CollaboratorPermission] -> Value # toEncodingList :: [CollaboratorPermission] -> Encoding # omitField :: CollaboratorPermission -> Bool # | |||||
Data CollaboratorPermission Source # | |||||
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 # | |||||
Bounded CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos | |||||
Enum CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos Methods succ :: CollaboratorPermission -> CollaboratorPermission # pred :: CollaboratorPermission -> CollaboratorPermission # toEnum :: Int -> CollaboratorPermission # fromEnum :: CollaboratorPermission -> Int # enumFrom :: CollaboratorPermission -> [CollaboratorPermission] # enumFromThen :: CollaboratorPermission -> CollaboratorPermission -> [CollaboratorPermission] # enumFromTo :: CollaboratorPermission -> CollaboratorPermission -> [CollaboratorPermission] # enumFromThenTo :: CollaboratorPermission -> CollaboratorPermission -> CollaboratorPermission -> [CollaboratorPermission] # | |||||
Generic CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos Associated Types
Methods from :: CollaboratorPermission -> Rep CollaboratorPermission x # to :: Rep CollaboratorPermission x -> CollaboratorPermission # | |||||
Show CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos Methods showsPrec :: Int -> CollaboratorPermission -> ShowS # show :: CollaboratorPermission -> String # showList :: [CollaboratorPermission] -> ShowS # | |||||
Binary CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos Methods put :: CollaboratorPermission -> Put # get :: Get CollaboratorPermission # putList :: [CollaboratorPermission] -> Put # | |||||
NFData CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos Methods rnf :: CollaboratorPermission -> () # | |||||
Eq CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos Methods (==) :: CollaboratorPermission -> CollaboratorPermission -> Bool # (/=) :: CollaboratorPermission -> CollaboratorPermission -> Bool # | |||||
Ord CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos Methods compare :: CollaboratorPermission -> CollaboratorPermission -> Ordering # (<) :: CollaboratorPermission -> CollaboratorPermission -> Bool # (<=) :: CollaboratorPermission -> CollaboratorPermission -> Bool # (>) :: CollaboratorPermission -> CollaboratorPermission -> Bool # (>=) :: CollaboratorPermission -> CollaboratorPermission -> Bool # max :: CollaboratorPermission -> CollaboratorPermission -> CollaboratorPermission # min :: CollaboratorPermission -> CollaboratorPermission -> CollaboratorPermission # | |||||
type Rep CollaboratorPermission Source # | |||||
Defined in GitHub.Data.Repos type Rep CollaboratorPermission = D1 ('MetaData "CollaboratorPermission" "GitHub.Data.Repos" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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 #
A collaborator and its permission on a repository. See https://developer.github.com/v3/repos/collaborators/#review-a-users-permission-level
Instances
FromJSON CollaboratorWithPermission Source # | |||||
Defined in GitHub.Data.Repos | |||||
Data CollaboratorWithPermission Source # | |||||
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 # | |||||
Generic CollaboratorWithPermission Source # | |||||
Defined in GitHub.Data.Repos Associated Types
Methods from :: CollaboratorWithPermission -> Rep CollaboratorWithPermission x # to :: Rep CollaboratorWithPermission x -> CollaboratorWithPermission # | |||||
Show CollaboratorWithPermission Source # | |||||
Defined in GitHub.Data.Repos Methods showsPrec :: Int -> CollaboratorWithPermission -> ShowS # show :: CollaboratorWithPermission -> String # showList :: [CollaboratorWithPermission] -> ShowS # | |||||
Binary CollaboratorWithPermission Source # | |||||
Defined in GitHub.Data.Repos Methods put :: CollaboratorWithPermission -> Put # get :: Get CollaboratorWithPermission # putList :: [CollaboratorWithPermission] -> Put # | |||||
NFData CollaboratorWithPermission Source # | |||||
Defined in GitHub.Data.Repos Methods rnf :: CollaboratorWithPermission -> () # | |||||
Eq CollaboratorWithPermission Source # | |||||
Defined in GitHub.Data.Repos Methods (==) :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool # (/=) :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool # | |||||
Ord CollaboratorWithPermission Source # | |||||
Defined in GitHub.Data.Repos Methods compare :: CollaboratorWithPermission -> CollaboratorWithPermission -> Ordering # (<) :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool # (<=) :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool # (>) :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool # (>=) :: CollaboratorWithPermission -> CollaboratorWithPermission -> Bool # max :: CollaboratorWithPermission -> CollaboratorWithPermission -> CollaboratorWithPermission # min :: CollaboratorWithPermission -> CollaboratorWithPermission -> CollaboratorWithPermission # | |||||
type Rep CollaboratorWithPermission Source # | |||||
Defined in GitHub.Data.Repos type Rep CollaboratorWithPermission = D1 ('MetaData "CollaboratorWithPermission" "GitHub.Data.Repos" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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
Data ArchiveFormat Source # | |||||
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 # | |||||
Bounded ArchiveFormat Source # | |||||
Defined in GitHub.Data.Repos | |||||
Enum ArchiveFormat Source # | |||||
Defined in GitHub.Data.Repos Methods succ :: ArchiveFormat -> ArchiveFormat # pred :: ArchiveFormat -> ArchiveFormat # toEnum :: Int -> ArchiveFormat # fromEnum :: ArchiveFormat -> Int # enumFrom :: ArchiveFormat -> [ArchiveFormat] # enumFromThen :: ArchiveFormat -> ArchiveFormat -> [ArchiveFormat] # enumFromTo :: ArchiveFormat -> ArchiveFormat -> [ArchiveFormat] # enumFromThenTo :: ArchiveFormat -> ArchiveFormat -> ArchiveFormat -> [ArchiveFormat] # | |||||
Generic ArchiveFormat Source # | |||||
Defined in GitHub.Data.Repos Associated Types
| |||||
Show ArchiveFormat Source # | |||||
Defined in GitHub.Data.Repos Methods showsPrec :: Int -> ArchiveFormat -> ShowS # show :: ArchiveFormat -> String # showList :: [ArchiveFormat] -> ShowS # | |||||
Eq ArchiveFormat Source # | |||||
Defined in GitHub.Data.Repos Methods (==) :: ArchiveFormat -> ArchiveFormat -> Bool # (/=) :: ArchiveFormat -> ArchiveFormat -> Bool # | |||||
Ord ArchiveFormat Source # | |||||
Defined in GitHub.Data.Repos Methods compare :: ArchiveFormat -> ArchiveFormat -> Ordering # (<) :: ArchiveFormat -> ArchiveFormat -> Bool # (<=) :: ArchiveFormat -> ArchiveFormat -> Bool # (>) :: ArchiveFormat -> ArchiveFormat -> Bool # (>=) :: ArchiveFormat -> ArchiveFormat -> Bool # max :: ArchiveFormat -> ArchiveFormat -> ArchiveFormat # min :: ArchiveFormat -> ArchiveFormat -> ArchiveFormat # | |||||
IsPathPart ArchiveFormat Source # | |||||
Defined in GitHub.Data.Repos Methods toPathPart :: ArchiveFormat -> Text Source # | |||||
type Rep ArchiveFormat Source # | |||||
Defined in GitHub.Data.Repos |