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.Activities

Description

 

Documentation

data RepoStarred Source #

Instances

Instances details
Eq RepoStarred Source # 
Instance details

Defined in GitHub.Data.Activities

Data RepoStarred Source # 
Instance details

Defined in GitHub.Data.Activities

Methods

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

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

toConstr :: RepoStarred -> Constr #

dataTypeOf :: RepoStarred -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RepoStarred Source # 
Instance details

Defined in GitHub.Data.Activities

Show RepoStarred Source # 
Instance details

Defined in GitHub.Data.Activities

Generic RepoStarred Source # 
Instance details

Defined in GitHub.Data.Activities

Associated Types

type Rep RepoStarred :: Type -> Type #

FromJSON RepoStarred Source # 
Instance details

Defined in GitHub.Data.Activities

Binary RepoStarred Source # 
Instance details

Defined in GitHub.Data.Activities

NFData RepoStarred Source # 
Instance details

Defined in GitHub.Data.Activities

Methods

rnf :: RepoStarred -> () #

type Rep RepoStarred Source # 
Instance details

Defined in GitHub.Data.Activities

type Rep RepoStarred = D1 ('MetaData "RepoStarred" "GitHub.Data.Activities" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "RepoStarred" 'PrefixI 'True) (S1 ('MetaSel ('Just "repoStarredStarredAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "repoStarredRepo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Repo)))

data Subject Source #

Instances

Instances details
Eq Subject Source # 
Instance details

Defined in GitHub.Data.Activities

Methods

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

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

Data Subject Source # 
Instance details

Defined in GitHub.Data.Activities

Methods

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

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

toConstr :: Subject -> Constr #

dataTypeOf :: Subject -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Subject Source # 
Instance details

Defined in GitHub.Data.Activities

Show Subject Source # 
Instance details

Defined in GitHub.Data.Activities

Generic Subject Source # 
Instance details

Defined in GitHub.Data.Activities

Associated Types

type Rep Subject :: Type -> Type #

Methods

from :: Subject -> Rep Subject x #

to :: Rep Subject x -> Subject #

FromJSON Subject Source # 
Instance details

Defined in GitHub.Data.Activities

Binary Subject Source # 
Instance details

Defined in GitHub.Data.Activities

Methods

put :: Subject -> Put #

get :: Get Subject #

putList :: [Subject] -> Put #

NFData Subject Source # 
Instance details

Defined in GitHub.Data.Activities

Methods

rnf :: Subject -> () #

type Rep Subject Source # 
Instance details

Defined in GitHub.Data.Activities

type Rep Subject = D1 ('MetaData "Subject" "GitHub.Data.Activities" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "Subject" 'PrefixI 'True) ((S1 ('MetaSel ('Just "subjectTitle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "subjectURL") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "subjectLatestCommentURL") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "subjectType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

data NotificationReason Source #

Instances

Instances details
Bounded NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

Enum NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

Eq NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

Data NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

Methods

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

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

toConstr :: NotificationReason -> Constr #

dataTypeOf :: NotificationReason -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

Show NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

Generic NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

Associated Types

type Rep NotificationReason :: Type -> Type #

FromJSON NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

Binary NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

NFData NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

Methods

rnf :: NotificationReason -> () #

type Rep NotificationReason Source # 
Instance details

Defined in GitHub.Data.Activities

type Rep NotificationReason = D1 ('MetaData "NotificationReason" "GitHub.Data.Activities" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (((C1 ('MetaCons "AssignReason" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AuthorReason" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CommentReason" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InvitationReason" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ManualReason" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MentionReason" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ReviewRequestedReason" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StateChangeReason" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SubscribedReason" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TeamMentionReason" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Notification Source #

Instances

Instances details
Eq Notification Source # 
Instance details

Defined in GitHub.Data.Activities

Data Notification Source # 
Instance details

Defined in GitHub.Data.Activities

Methods

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

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

toConstr :: Notification -> Constr #

dataTypeOf :: Notification -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Notification Source # 
Instance details

Defined in GitHub.Data.Activities

Show Notification Source # 
Instance details

Defined in GitHub.Data.Activities

Generic Notification Source # 
Instance details

Defined in GitHub.Data.Activities

Associated Types

type Rep Notification :: Type -> Type #

FromJSON Notification Source # 
Instance details

Defined in GitHub.Data.Activities

Binary Notification Source # 
Instance details

Defined in GitHub.Data.Activities

NFData Notification Source # 
Instance details

Defined in GitHub.Data.Activities

Methods

rnf :: Notification -> () #

type Rep Notification Source # 
Instance details

Defined in GitHub.Data.Activities

type Rep Notification = D1 ('MetaData "Notification" "GitHub.Data.Activities" "github-0.28.0.1-Ane44df1Z4EB2fvYeVzY0Q" 'False) (C1 ('MetaCons "Notification" 'PrefixI 'True) (((S1 ('MetaSel ('Just "notificationId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id Notification)) :*: S1 ('MetaSel ('Just "notificationRepo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RepoRef)) :*: (S1 ('MetaSel ('Just "notificationSubject") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Subject) :*: S1 ('MetaSel ('Just "notificationReason") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NotificationReason))) :*: ((S1 ('MetaSel ('Just "notificationUnread") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "notificationUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime))) :*: (S1 ('MetaSel ('Just "notificationLastReadAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)) :*: S1 ('MetaSel ('Just "notificationUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))))