Safe Haskell | None |
---|---|
Language | Haskell2010 |
GitHub.Data.Invitation
Documentation
data Invitation Source #
Constructors
Invitation | |
Fields
|
Instances
data InvitationRole Source #
Constructors
InvitationRoleDirectMember | |
InvitationRoleAdmin | |
InvitationRoleBillingManager | |
InvitationRoleHiringManager | |
InvitationRoleReinstate |
Instances
FromJSON InvitationRole Source # | |||||
Defined in GitHub.Data.Invitation Methods parseJSON :: Value -> Parser InvitationRole # parseJSONList :: Value -> Parser [InvitationRole] # | |||||
Data InvitationRole Source # | |||||
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 :: forall r r'. (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 # | |||||
Bounded InvitationRole Source # | |||||
Defined in GitHub.Data.Invitation | |||||
Enum InvitationRole Source # | |||||
Defined in GitHub.Data.Invitation Methods succ :: InvitationRole -> InvitationRole # pred :: InvitationRole -> InvitationRole # toEnum :: Int -> InvitationRole # fromEnum :: InvitationRole -> Int # enumFrom :: InvitationRole -> [InvitationRole] # enumFromThen :: InvitationRole -> InvitationRole -> [InvitationRole] # enumFromTo :: InvitationRole -> InvitationRole -> [InvitationRole] # enumFromThenTo :: InvitationRole -> InvitationRole -> InvitationRole -> [InvitationRole] # | |||||
Generic InvitationRole Source # | |||||
Defined in GitHub.Data.Invitation Associated Types
Methods from :: InvitationRole -> Rep InvitationRole x # to :: Rep InvitationRole x -> InvitationRole # | |||||
Show InvitationRole Source # | |||||
Defined in GitHub.Data.Invitation Methods showsPrec :: Int -> InvitationRole -> ShowS # show :: InvitationRole -> String # showList :: [InvitationRole] -> ShowS # | |||||
Binary InvitationRole Source # | |||||
Defined in GitHub.Data.Invitation Methods put :: InvitationRole -> Put # get :: Get InvitationRole # putList :: [InvitationRole] -> Put # | |||||
NFData InvitationRole Source # | |||||
Defined in GitHub.Data.Invitation Methods rnf :: InvitationRole -> () # | |||||
Eq InvitationRole Source # | |||||
Defined in GitHub.Data.Invitation Methods (==) :: InvitationRole -> InvitationRole -> Bool # (/=) :: InvitationRole -> InvitationRole -> Bool # | |||||
Ord InvitationRole Source # | |||||
Defined in GitHub.Data.Invitation Methods compare :: InvitationRole -> InvitationRole -> Ordering # (<) :: InvitationRole -> InvitationRole -> Bool # (<=) :: InvitationRole -> InvitationRole -> Bool # (>) :: InvitationRole -> InvitationRole -> Bool # (>=) :: InvitationRole -> InvitationRole -> Bool # max :: InvitationRole -> InvitationRole -> InvitationRole # min :: InvitationRole -> InvitationRole -> InvitationRole # | |||||
type Rep InvitationRole Source # | |||||
Defined in GitHub.Data.Invitation type Rep InvitationRole = D1 ('MetaData "InvitationRole" "GitHub.Data.Invitation" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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 #
Constructors
RepoInvitation | |
Fields |
Instances
FromJSON RepoInvitation Source # | |||||
Defined in GitHub.Data.Invitation Methods parseJSON :: Value -> Parser RepoInvitation # parseJSONList :: Value -> Parser [RepoInvitation] # | |||||
Data RepoInvitation Source # | |||||
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 :: forall r r'. (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 # | |||||
Generic RepoInvitation Source # | |||||
Defined in GitHub.Data.Invitation Associated Types
Methods from :: RepoInvitation -> Rep RepoInvitation x # to :: Rep RepoInvitation x -> RepoInvitation # | |||||
Show RepoInvitation Source # | |||||
Defined in GitHub.Data.Invitation Methods showsPrec :: Int -> RepoInvitation -> ShowS # show :: RepoInvitation -> String # showList :: [RepoInvitation] -> ShowS # | |||||
Binary RepoInvitation Source # | |||||
Defined in GitHub.Data.Invitation Methods put :: RepoInvitation -> Put # get :: Get RepoInvitation # putList :: [RepoInvitation] -> Put # | |||||
NFData RepoInvitation Source # | |||||
Defined in GitHub.Data.Invitation Methods rnf :: RepoInvitation -> () # | |||||
Eq RepoInvitation Source # | |||||
Defined in GitHub.Data.Invitation Methods (==) :: RepoInvitation -> RepoInvitation -> Bool # (/=) :: RepoInvitation -> RepoInvitation -> Bool # | |||||
Ord RepoInvitation Source # | |||||
Defined in GitHub.Data.Invitation Methods compare :: RepoInvitation -> RepoInvitation -> Ordering # (<) :: RepoInvitation -> RepoInvitation -> Bool # (<=) :: RepoInvitation -> RepoInvitation -> Bool # (>) :: RepoInvitation -> RepoInvitation -> Bool # (>=) :: RepoInvitation -> RepoInvitation -> Bool # max :: RepoInvitation -> RepoInvitation -> RepoInvitation # min :: RepoInvitation -> RepoInvitation -> RepoInvitation # | |||||
type Rep RepoInvitation Source # | |||||
Defined in GitHub.Data.Invitation type Rep RepoInvitation = D1 ('MetaData "RepoInvitation" "GitHub.Data.Invitation" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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))))) |