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

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

GitHub.Data.Invitation

Description

 

Documentation

data Invitation Source #

Instances
Eq Invitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Data Invitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Methods

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

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

toConstr :: Invitation -> Constr #

dataTypeOf :: Invitation -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Invitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Show Invitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Generic Invitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Associated Types

type Rep Invitation :: Type -> Type #

FromJSON Invitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Binary Invitation Source # 
Instance details

Defined in GitHub.Data.Invitation

NFData Invitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Methods

rnf :: Invitation -> () #

type Rep Invitation Source # 
Instance details

Defined in GitHub.Data.Invitation

data InvitationRole Source #

Instances
Bounded InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

Enum InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

Eq InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

Data InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

Methods

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

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

toConstr :: InvitationRole -> Constr #

dataTypeOf :: InvitationRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

Show InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

Generic InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

Associated Types

type Rep InvitationRole :: Type -> Type #

FromJSON InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

Binary InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

NFData InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

Methods

rnf :: InvitationRole -> () #

type Rep InvitationRole Source # 
Instance details

Defined in GitHub.Data.Invitation

type Rep InvitationRole = D1 (MetaData "InvitationRole" "GitHub.Data.Invitation" "github-0.24-7U9W4aQUcK5ET8TasTAb5B" False) ((C1 (MetaCons "InvitationRoleDirectMember" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "InvitationRoleAdmin" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "InvitationRoleBillingManager" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "InvitationRoleHiringManager" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "InvitationRoleReinstate" PrefixI False) (U1 :: Type -> Type))))

data RepoInvitation Source #

Instances
Eq RepoInvitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Data RepoInvitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Methods

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

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

toConstr :: RepoInvitation -> Constr #

dataTypeOf :: RepoInvitation -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RepoInvitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Show RepoInvitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Generic RepoInvitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Associated Types

type Rep RepoInvitation :: Type -> Type #

FromJSON RepoInvitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Binary RepoInvitation Source # 
Instance details

Defined in GitHub.Data.Invitation

NFData RepoInvitation Source # 
Instance details

Defined in GitHub.Data.Invitation

Methods

rnf :: RepoInvitation -> () #

type Rep RepoInvitation Source # 
Instance details

Defined in GitHub.Data.Invitation

type Rep RepoInvitation = D1 (MetaData "RepoInvitation" "GitHub.Data.Invitation" "github-0.24-7U9W4aQUcK5ET8TasTAb5B" False) (C1 (MetaCons "RepoInvitation" PrefixI True) (((S1 (MetaSel (Just "repoInvitationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Id RepoInvitation)) :*: S1 (MetaSel (Just "repoInvitationInvitee") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SimpleUser)) :*: (S1 (MetaSel (Just "repoInvitationInviter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SimpleUser) :*: S1 (MetaSel (Just "repoInvitationRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Repo))) :*: ((S1 (MetaSel (Just "repoInvitationUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL) :*: S1 (MetaSel (Just "repoInvitationCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime)) :*: (S1 (MetaSel (Just "repoInvitationPermission") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "repoInvitationHtmlUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL)))))