Safe Haskell | None |
---|---|
Language | Haskell2010 |
GitHub.Data.Activities
Documentation
data RepoStarred Source #
Constructors
RepoStarred | |
Fields |
Instances
Constructors
Subject | |
Fields
|
Instances
FromJSON Subject Source # | |||||
Defined in GitHub.Data.Activities | |||||
Data Subject Source # | |||||
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 # | |||||
Generic Subject Source # | |||||
Defined in GitHub.Data.Activities Associated Types
| |||||
Show Subject Source # | |||||
Binary Subject Source # | |||||
NFData Subject Source # | |||||
Defined in GitHub.Data.Activities | |||||
Eq Subject Source # | |||||
Ord Subject Source # | |||||
Defined in GitHub.Data.Activities | |||||
type Rep Subject Source # | |||||
Defined in GitHub.Data.Activities type Rep Subject = D1 ('MetaData "Subject" "GitHub.Data.Activities" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (C1 ('MetaCons "Subject" 'PrefixI 'True) ((S1 ('MetaSel ('Just "subjectTitle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "subjectURL") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL))) :*: (S1 ('MetaSel ('Just "subjectLatestCommentURL") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "subjectType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) |
data NotificationReason Source #
Constructors
ApprovalRequestedReason | |
AssignReason | |
AuthorReason | |
CommentReason | |
CiActivityReason | |
InvitationReason | |
ManualReason | |
MemberFeatureRequestedReason | |
MentionReason | |
ReviewRequestedReason | |
SecurityAlertReason | |
SecurityAdvisoryCreditReason | |
StateChangeReason | |
SubscribedReason | |
TeamMentionReason |
Instances
FromJSON NotificationReason Source # | |||||
Defined in GitHub.Data.Activities Methods parseJSON :: Value -> Parser NotificationReason # parseJSONList :: Value -> Parser [NotificationReason] # | |||||
Data NotificationReason Source # | |||||
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 # | |||||
Bounded NotificationReason Source # | |||||
Defined in GitHub.Data.Activities | |||||
Enum NotificationReason Source # | |||||
Defined in GitHub.Data.Activities Methods succ :: NotificationReason -> NotificationReason # pred :: NotificationReason -> NotificationReason # toEnum :: Int -> NotificationReason # fromEnum :: NotificationReason -> Int # enumFrom :: NotificationReason -> [NotificationReason] # enumFromThen :: NotificationReason -> NotificationReason -> [NotificationReason] # enumFromTo :: NotificationReason -> NotificationReason -> [NotificationReason] # enumFromThenTo :: NotificationReason -> NotificationReason -> NotificationReason -> [NotificationReason] # | |||||
Generic NotificationReason Source # | |||||
Defined in GitHub.Data.Activities Associated Types
Methods from :: NotificationReason -> Rep NotificationReason x # to :: Rep NotificationReason x -> NotificationReason # | |||||
Show NotificationReason Source # | |||||
Defined in GitHub.Data.Activities Methods showsPrec :: Int -> NotificationReason -> ShowS # show :: NotificationReason -> String # showList :: [NotificationReason] -> ShowS # | |||||
Binary NotificationReason Source # | |||||
Defined in GitHub.Data.Activities Methods put :: NotificationReason -> Put # get :: Get NotificationReason # putList :: [NotificationReason] -> Put # | |||||
NFData NotificationReason Source # | |||||
Defined in GitHub.Data.Activities Methods rnf :: NotificationReason -> () # | |||||
Eq NotificationReason Source # | |||||
Defined in GitHub.Data.Activities Methods (==) :: NotificationReason -> NotificationReason -> Bool # (/=) :: NotificationReason -> NotificationReason -> Bool # | |||||
Ord NotificationReason Source # | |||||
Defined in GitHub.Data.Activities Methods compare :: NotificationReason -> NotificationReason -> Ordering # (<) :: NotificationReason -> NotificationReason -> Bool # (<=) :: NotificationReason -> NotificationReason -> Bool # (>) :: NotificationReason -> NotificationReason -> Bool # (>=) :: NotificationReason -> NotificationReason -> Bool # max :: NotificationReason -> NotificationReason -> NotificationReason # min :: NotificationReason -> NotificationReason -> NotificationReason # | |||||
type Rep NotificationReason Source # | |||||
Defined in GitHub.Data.Activities type Rep NotificationReason = D1 ('MetaData "NotificationReason" "GitHub.Data.Activities" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) (((C1 ('MetaCons "ApprovalRequestedReason" 'PrefixI 'False) (U1 :: Type -> Type) :+: (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 "CiActivityReason" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InvitationReason" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ManualReason" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MemberFeatureRequestedReason" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MentionReason" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ReviewRequestedReason" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SecurityAlertReason" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SecurityAdvisoryCreditReason" '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 #
Constructors
Notification | |
Fields
|
Instances
FromJSON Notification Source # | |||||
Defined in GitHub.Data.Activities | |||||
Data Notification Source # | |||||
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 # | |||||
Generic Notification Source # | |||||
Defined in GitHub.Data.Activities Associated Types
| |||||
Show Notification Source # | |||||
Defined in GitHub.Data.Activities Methods showsPrec :: Int -> Notification -> ShowS # show :: Notification -> String # showList :: [Notification] -> ShowS # | |||||
Binary Notification Source # | |||||
Defined in GitHub.Data.Activities | |||||
NFData Notification Source # | |||||
Defined in GitHub.Data.Activities Methods rnf :: Notification -> () # | |||||
Eq Notification Source # | |||||
Defined in GitHub.Data.Activities | |||||
Ord Notification Source # | |||||
Defined in GitHub.Data.Activities Methods compare :: Notification -> Notification -> Ordering # (<) :: Notification -> Notification -> Bool # (<=) :: Notification -> Notification -> Bool # (>) :: Notification -> Notification -> Bool # (>=) :: Notification -> Notification -> Bool # max :: Notification -> Notification -> Notification # min :: Notification -> Notification -> Notification # | |||||
type Rep Notification Source # | |||||
Defined in GitHub.Data.Activities type Rep Notification = D1 ('MetaData "Notification" "GitHub.Data.Activities" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" '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))))) |