github-0.17.0: Access to the GitHub API, v3.

LicenseBSD-3-Clause
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellNone
LanguageHaskell2010

GitHub.Data.Definitions

Description

 

Synopsis

Documentation

data Error Source #

Errors have been tagged according to their source, so you can more easily dispatch and handle them.

Constructors

HTTPError !HttpException

A HTTP error occurred. The actual caught error is included.

ParseError !Text

An error in the parser itself.

JsonError !Text

The JSON is malformed or unexpected.

UserError !Text

Incorrect input.

data OwnerType Source #

Type of the repository owners.

Instances

Bounded OwnerType Source # 
Enum OwnerType Source # 
Eq OwnerType Source # 
Data OwnerType Source # 

Methods

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

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

toConstr :: OwnerType -> Constr #

dataTypeOf :: OwnerType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OwnerType Source # 
Read OwnerType Source # 
Show OwnerType Source # 
Generic OwnerType Source # 

Associated Types

type Rep OwnerType :: * -> * #

FromJSON OwnerType Source # 
Binary OwnerType Source # 
NFData OwnerType Source # 

Methods

rnf :: OwnerType -> () #

type Rep OwnerType Source # 
type Rep OwnerType = D1 (MetaData "OwnerType" "GitHub.Data.Definitions" "github-0.17.0-fZe2tmQJtNGH9i4ZUoXPX" False) ((:+:) (C1 (MetaCons "OwnerUser" PrefixI False) U1) (C1 (MetaCons "OwnerOrganization" PrefixI False) U1))

data SimpleUser Source #

Instances

Eq SimpleUser Source # 
Data SimpleUser Source # 

Methods

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

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

toConstr :: SimpleUser -> Constr #

dataTypeOf :: SimpleUser -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SimpleUser Source # 
Show SimpleUser Source # 
Generic SimpleUser Source # 

Associated Types

type Rep SimpleUser :: * -> * #

FromJSON SimpleUser Source # 
Binary SimpleUser Source # 
NFData SimpleUser Source # 

Methods

rnf :: SimpleUser -> () #

type Rep SimpleUser Source # 
type Rep SimpleUser = D1 (MetaData "SimpleUser" "GitHub.Data.Definitions" "github-0.17.0-fZe2tmQJtNGH9i4ZUoXPX" False) (C1 (MetaCons "SimpleUser" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "simpleUserId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Id User))) (S1 (MetaSel (Just Symbol "simpleUserLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Name User)))) ((:*:) (S1 (MetaSel (Just Symbol "simpleUserAvatarUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)) (S1 (MetaSel (Just Symbol "simpleUserUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)))))

data SimpleOrganization Source #

Instances

Eq SimpleOrganization Source # 
Data SimpleOrganization Source # 

Methods

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

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

toConstr :: SimpleOrganization -> Constr #

dataTypeOf :: SimpleOrganization -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SimpleOrganization Source # 
Show SimpleOrganization Source # 
Generic SimpleOrganization Source # 
FromJSON SimpleOrganization Source # 
Binary SimpleOrganization Source # 
NFData SimpleOrganization Source # 

Methods

rnf :: SimpleOrganization -> () #

type Rep SimpleOrganization Source # 
type Rep SimpleOrganization = D1 (MetaData "SimpleOrganization" "GitHub.Data.Definitions" "github-0.17.0-fZe2tmQJtNGH9i4ZUoXPX" False) (C1 (MetaCons "SimpleOrganization" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "simpleOrganizationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Id Organization))) (S1 (MetaSel (Just Symbol "simpleOrganizationLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Name Organization)))) ((:*:) (S1 (MetaSel (Just Symbol "simpleOrganizationUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)) (S1 (MetaSel (Just Symbol "simpleOrganizationAvatarUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)))))

data SimpleOwner Source #

Sometimes we don't know the type of the owner, e.g. in Repo

Instances

Eq SimpleOwner Source # 
Data SimpleOwner Source # 

Methods

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

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

toConstr :: SimpleOwner -> Constr #

dataTypeOf :: SimpleOwner -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SimpleOwner Source # 
Show SimpleOwner Source # 
Generic SimpleOwner Source # 

Associated Types

type Rep SimpleOwner :: * -> * #

FromJSON SimpleOwner Source # 
Binary SimpleOwner Source # 
NFData SimpleOwner Source # 

Methods

rnf :: SimpleOwner -> () #

type Rep SimpleOwner Source # 
type Rep SimpleOwner = D1 (MetaData "SimpleOwner" "GitHub.Data.Definitions" "github-0.17.0-fZe2tmQJtNGH9i4ZUoXPX" False) (C1 (MetaCons "SimpleOwner" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "simpleOwnerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Id Owner))) (S1 (MetaSel (Just Symbol "simpleOwnerLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Name Owner)))) ((:*:) (S1 (MetaSel (Just Symbol "simpleOwnerUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)) ((:*:) (S1 (MetaSel (Just Symbol "simpleOwnerAvatarUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)) (S1 (MetaSel (Just Symbol "simpleOwnerType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OwnerType))))))

data User Source #

Instances

Eq User Source # 

Methods

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

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

Data User Source # 

Methods

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

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

toConstr :: User -> Constr #

dataTypeOf :: User -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord User Source # 

Methods

compare :: User -> User -> Ordering #

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

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

(>) :: User -> User -> Bool #

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

max :: User -> User -> User #

min :: User -> User -> User #

Show User Source # 

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Generic User Source # 

Associated Types

type Rep User :: * -> * #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

FromJSON User Source # 
Binary User Source # 

Methods

put :: User -> Put #

get :: Get User #

putList :: [User] -> Put #

NFData User Source # 

Methods

rnf :: User -> () #

type Rep User Source # 
type Rep User = D1 (MetaData "User" "GitHub.Data.Definitions" "github-0.17.0-fZe2tmQJtNGH9i4ZUoXPX" False) (C1 (MetaCons "User" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Id User))) (S1 (MetaSel (Just Symbol "userLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Name User)))) ((:*:) (S1 (MetaSel (Just Symbol "userName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "userType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OwnerType)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime)) (S1 (MetaSel (Just Symbol "userPublicGists") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "userAvatarUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)) ((:*:) (S1 (MetaSel (Just Symbol "userFollowers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Just Symbol "userFollowing") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userHireable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "userBlog") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "userBio") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "userPublicRepos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "userCompany") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "userEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "userUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)) (S1 (MetaSel (Just Symbol "userHtmlUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL))))))))

data Organization Source #

Instances

Eq Organization Source # 
Data Organization Source # 

Methods

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

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

toConstr :: Organization -> Constr #

dataTypeOf :: Organization -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Organization Source # 
Show Organization Source # 
Generic Organization Source # 

Associated Types

type Rep Organization :: * -> * #

FromJSON Organization Source # 
Binary Organization Source # 
NFData Organization Source # 

Methods

rnf :: Organization -> () #

type Rep Organization Source # 
type Rep Organization = D1 (MetaData "Organization" "GitHub.Data.Definitions" "github-0.17.0-fZe2tmQJtNGH9i4ZUoXPX" False) (C1 (MetaCons "Organization" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "organizationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Id Organization))) (S1 (MetaSel (Just Symbol "organizationLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Name Organization)))) ((:*:) (S1 (MetaSel (Just Symbol "organizationName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "organizationType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OwnerType)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "organizationBlog") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "organizationLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "organizationFollowers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Just Symbol "organizationCompany") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "organizationAvatarUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)) (S1 (MetaSel (Just Symbol "organizationPublicGists") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "organizationHtmlUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)) (S1 (MetaSel (Just Symbol "organizationEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "organizationFollowing") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Just Symbol "organizationPublicRepos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "organizationUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)) (S1 (MetaSel (Just Symbol "organizationCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime)))))))

newtype Owner Source #

In practic, you cam't have concrete values of Owner.

Constructors

Owner (Either User Organization) 

Instances

Eq Owner Source # 

Methods

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

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

Data Owner Source # 

Methods

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

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

toConstr :: Owner -> Constr #

dataTypeOf :: Owner -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Owner Source # 

Methods

compare :: Owner -> Owner -> Ordering #

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

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

(>) :: Owner -> Owner -> Bool #

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

max :: Owner -> Owner -> Owner #

min :: Owner -> Owner -> Owner #

Show Owner Source # 

Methods

showsPrec :: Int -> Owner -> ShowS #

show :: Owner -> String #

showList :: [Owner] -> ShowS #

Generic Owner Source # 

Associated Types

type Rep Owner :: * -> * #

Methods

from :: Owner -> Rep Owner x #

to :: Rep Owner x -> Owner #

FromJSON Owner Source # 
Binary Owner Source # 

Methods

put :: Owner -> Put #

get :: Get Owner #

putList :: [Owner] -> Put #

NFData Owner Source # 

Methods

rnf :: Owner -> () #

type Rep Owner Source # 
type Rep Owner = D1 (MetaData "Owner" "GitHub.Data.Definitions" "github-0.17.0-fZe2tmQJtNGH9i4ZUoXPX" True) (C1 (MetaCons "Owner" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either User Organization))))

data OrgMemberFilter Source #

Filter members returned in the list.

Constructors

OrgMemberFilter2faDisabled

Members without two-factor authentication enabled. Available for organization owners.

OrgMemberFilterAll

All members the authenticated user can see.

Instances

Bounded OrgMemberFilter Source # 
Enum OrgMemberFilter Source # 
Eq OrgMemberFilter Source # 
Data OrgMemberFilter Source # 

Methods

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

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

toConstr :: OrgMemberFilter -> Constr #

dataTypeOf :: OrgMemberFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OrgMemberFilter Source # 
Show OrgMemberFilter Source # 
Generic OrgMemberFilter Source # 
type Rep OrgMemberFilter Source # 
type Rep OrgMemberFilter = D1 (MetaData "OrgMemberFilter" "GitHub.Data.Definitions" "github-0.17.0-fZe2tmQJtNGH9i4ZUoXPX" False) ((:+:) (C1 (MetaCons "OrgMemberFilter2faDisabled" PrefixI False) U1) (C1 (MetaCons "OrgMemberFilterAll" PrefixI False) U1))

data OrgMemberRole Source #

Filter members returned by their role.

Constructors

OrgMemberRoleAll

All members of the organization, regardless of role.

OrgMemberRoleAdmin

Organization owners.

OrgMemberRoleMember

Non-owner organization members.

Instances

Bounded OrgMemberRole Source # 
Enum OrgMemberRole Source # 
Eq OrgMemberRole Source # 
Data OrgMemberRole Source # 

Methods

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

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

toConstr :: OrgMemberRole -> Constr #

dataTypeOf :: OrgMemberRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OrgMemberRole Source # 
Show OrgMemberRole Source # 
Generic OrgMemberRole Source # 

Associated Types

type Rep OrgMemberRole :: * -> * #

type Rep OrgMemberRole Source # 
type Rep OrgMemberRole = D1 (MetaData "OrgMemberRole" "GitHub.Data.Definitions" "github-0.17.0-fZe2tmQJtNGH9i4ZUoXPX" False) ((:+:) (C1 (MetaCons "OrgMemberRoleAll" PrefixI False) U1) ((:+:) (C1 (MetaCons "OrgMemberRoleAdmin" PrefixI False) U1) (C1 (MetaCons "OrgMemberRoleMember" PrefixI False) U1)))

type QueryString = [(ByteString, Maybe ByteString)] Source #

Request query string

type Count = Int Source #

Count of elements

data IssueLabel Source #

Constructors

IssueLabel 

Instances

Eq IssueLabel Source # 
Data IssueLabel Source # 

Methods

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

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

toConstr :: IssueLabel -> Constr #

dataTypeOf :: IssueLabel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IssueLabel Source # 
Show IssueLabel Source # 
Generic IssueLabel Source # 

Associated Types

type Rep IssueLabel :: * -> * #

FromJSON IssueLabel Source # 
Binary IssueLabel Source # 
NFData IssueLabel Source # 

Methods

rnf :: IssueLabel -> () #

type Rep IssueLabel Source # 
type Rep IssueLabel = D1 (MetaData "IssueLabel" "GitHub.Data.Definitions" "github-0.17.0-fZe2tmQJtNGH9i4ZUoXPX" False) (C1 (MetaCons "IssueLabel" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "labelColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "labelUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)) (S1 (MetaSel (Just Symbol "labelName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Name IssueLabel))))))