| Copyright | (c) 2021 Rory Tyler Hayford |
|---|---|
| License | BSD-3-Clause |
| Maintainer | rory.hayford@protonmail.com |
| Stability | experimental |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
Network.Reddit.Types.Moderation
Description
Synopsis
- newtype ModItem = ModItem Item
- data ModItemOpts = ModItemOpts {}
- data RemovalMessage = RemovalMessage {
- itemID :: ItemID
- message :: Body
- title :: Title
- removalType :: RemovalType
- data RemovalType
- data RemovalReason = RemovalReason {}
- type RemovalReasonID = Text
- data NewRemovalReasonID
- data RemovalReasonList
- data ModPermission
- = Access
- | Flair
- | Configuration
- | ChatConfig
- | ChatOperator
- | Posts
- | Wiki
- data SubredditRelationship
- newtype RelID = RelID Text
- newtype MuteID = MuteID Text
- data ModInvitee = ModInvitee {}
- data ModInviteeList = ModInviteeList {}
- data ModList
- data ModAccount = ModAccount {}
- data RelInfo = RelInfo {}
- data MuteInfo = MuteInfo {}
- data RelInfoOpts = RelInfoOpts {}
- data Ban = Ban {}
- data BanNotes = BanNotes {}
- data SubredditSettings = SubredditSettings {
- subredditID :: SubredditID
- title :: Title
- description :: Body
- submitText :: Text
- submitTextLabel :: Text
- headerHoverText :: Text
- language :: LanguageCode
- subredditType :: SubredditType
- contentOptions :: ContentOptions
- keyColor :: RGBText
- wikimode :: Wikimode
- wikiEditKarma :: Integer
- wikiEditAge :: Integer
- commentScoreHideMins :: Integer
- spamComments :: SpamFilter
- spamSelfposts :: SpamFilter
- spamLinks :: SpamFilter
- crowdControlLevel :: CrowdControlLevel
- crowdControlChatLevel :: CrowdControlLevel
- crowdControlMode :: Bool
- suggestedCommentSort :: Maybe ItemSort
- welcomeMessageText :: Maybe Text
- welcomeMessageEnabled :: Bool
- allowImages :: Bool
- allowVideos :: Bool
- allowPolls :: Bool
- allowCrossposts :: Bool
- allowChatPostCreation :: Bool
- spoilersEnabled :: Bool
- showMedia :: Bool
- showMediaPreview :: Bool
- restrictPosting :: Bool
- restrictCommenting :: Bool
- over18 :: Bool
- collapseDeletedComments :: Bool
- defaultSet :: Bool
- disableContribRequests :: Bool
- freeFormReports :: Bool
- excludeBannedModqueue :: Bool
- ocTagEnabled :: Bool
- allOC :: Bool
- data CrowdControlLevel
- data SubredditType
- data SpamFilter
- data Wikimode
- data ContentOptions
- newtype Modmail = Modmail {}
- data ModmailConversation = ModmailConversation {
- modmailID :: ModmailID
- subject :: Subject
- messages :: Seq ModmailMessage
- numMessages :: Integer
- subreddit :: SubredditName
- participant :: Maybe ModmailAuthor
- objIDs :: Seq ModmailObjID
- lastUpdated :: UTCTime
- lastUserUpdate :: Maybe UTCTime
- lastModUpdate :: Maybe UTCTime
- isHighlighted :: Bool
- isInternal :: Bool
- data ModmailMessage = ModmailMessage {
- modmailMessageID :: Text
- author :: ModmailAuthor
- body :: Body
- bodyHTML :: Body
- date :: UTCTime
- isInternal :: Bool
- type ModmailID = Text
- data BulkReadIDs
- data ModmailAuthor = ModmailAuthor {}
- data ModmailObjID = ModmailObjID {}
- data ModmailState
- data ModmailSort
- data ModmailOpts = ModmailOpts {
- after :: Maybe ModmailID
- subreddits :: Maybe [SubredditName]
- limit :: Maybe Word
- itemSort :: Maybe ModmailSort
- state :: Maybe ModmailState
- defaultModmailOpts :: ModmailOpts
- data ConversationDetails
- data ModmailReply = ModmailReply {
- body :: Body
- isAuthorHidden :: Bool
- isInternal :: Bool
- mkModmailReply :: Body -> ModmailReply
- data NewConversation = NewConversation {
- body :: Body
- subject :: Subject
- dest :: Username
- subreddit :: SubredditName
- isAuthorHidden :: Bool
- data ModAction = ModAction {}
- data ModActionID
- data ModActionType
- = BanUser
- | UnbanUser
- | SpamLink
- | RemoveLink
- | ApproveLink
- | SpamComment
- | RemoveComment
- | ApproveComment
- | AddModerator
- | ShowComment
- | InviteModerator
- | UninviteModerator
- | AcceptModeratorInvite
- | RemoveModerator
- | AddContributor
- | RemoveContributor
- | EditSettings
- | EditFlair
- | Distinguish
- | MarkNSFW
- | WikiBanned
- | WikiContrib
- | WikiUnbanned
- | WikiPageListed
- | RemoveWikiContributor
- | WikiRevise
- | WikiPermLevel
- | IgnoreReports
- | UnignoreReports
- | SetPermissions
- | SetSuggestedSort
- | Sticky
- | Unsticky
- | SetContestMode
- | UnsetContestMode
- | Lock
- | Unlock
- | MuteUser
- | UnmuteUser
- | CreateRule
- | EditRule
- | ReorderRules
- | DeleteRule
- | Spoiler
- | Unspoiler
- | MarkOriginalContent
- | Collections
- | Events
- | DeleteOverriddenClassification
- | OverrideClassification
- | ReorderModerators
- | SnoozeReports
- | UnsnoozeReports
- | OtherModAction
- data ModActionOpts = ModActionOpts {}
- data Stylesheet = Stylesheet {}
- data SubredditImage = SubredditImage {}
- data S3ModerationLease = S3ModerationLease {}
- data StructuredStyleImage
- data StyleImageAlignment
- data TrafficStat = TrafficStat {}
- data Traffic = Traffic {
- hour :: Seq TrafficStat
- day :: Seq TrafficStat
- month :: Seq TrafficStat
- data LanguageCode where
- pattern AF :: LanguageCode
- pattern AR :: LanguageCode
- pattern BE :: LanguageCode
- pattern BG :: LanguageCode
- pattern BS :: LanguageCode
- pattern CA :: LanguageCode
- pattern CS :: LanguageCode
- pattern CY :: LanguageCode
- pattern DA :: LanguageCode
- pattern DE :: LanguageCode
- pattern EL :: LanguageCode
- pattern EN :: LanguageCode
- pattern EO :: LanguageCode
- pattern ES :: LanguageCode
- pattern ET :: LanguageCode
- pattern EU :: LanguageCode
- pattern FA :: LanguageCode
- pattern FI :: LanguageCode
- pattern FR :: LanguageCode
- pattern GD :: LanguageCode
- pattern GL :: LanguageCode
- pattern HE :: LanguageCode
- pattern HI :: LanguageCode
- pattern HR :: LanguageCode
- pattern HU :: LanguageCode
- pattern HY :: LanguageCode
- pattern ID :: LanguageCode
- pattern IS :: LanguageCode
- pattern IT :: LanguageCode
- pattern JA :: LanguageCode
- pattern KO :: LanguageCode
- pattern LA :: LanguageCode
- pattern LT :: LanguageCode
- pattern LV :: LanguageCode
- pattern MS :: LanguageCode
- pattern NL :: LanguageCode
- pattern NN :: LanguageCode
- pattern NO :: LanguageCode
- pattern PL :: LanguageCode
- pattern PT :: LanguageCode
- pattern RO :: LanguageCode
- pattern RU :: LanguageCode
- pattern SK :: LanguageCode
- pattern SL :: LanguageCode
- pattern SR :: LanguageCode
- pattern SV :: LanguageCode
- pattern TA :: LanguageCode
- pattern TH :: LanguageCode
- pattern TR :: LanguageCode
- pattern UK :: LanguageCode
- pattern VI :: LanguageCode
- pattern ZH :: LanguageCode
Item moderation
An Item of interest to moderators (spam, modqueue, etc...)
Instances
| Eq ModItem Source # | |
| Show ModItem Source # | |
| Generic ModItem Source # | |
| FromJSON ModItem Source # | |
| Paginable ModItem Source # | |
Defined in Network.Reddit.Types.Moderation Methods defaultOpts :: PaginateOptions ModItem Source # getFullname :: ModItem -> PaginateThing ModItem Source # optsToForm :: PaginateOptions ModItem -> Form Source # | |
| type Rep ModItem Source # | |
Defined in Network.Reddit.Types.Moderation | |
| type PaginateOptions ModItem Source # | |
Defined in Network.Reddit.Types.Moderation | |
| type PaginateThing ModItem Source # | |
Defined in Network.Reddit.Types.Moderation | |
data ModItemOpts Source #
Options for Listings of ModItems. Only contains one field, only to
constrain the request to a single type (i.e. comments or links)
Constructors
| ModItemOpts | |
Instances
| Eq ModItemOpts Source # | |
Defined in Network.Reddit.Types.Moderation | |
| Show ModItemOpts Source # | |
Defined in Network.Reddit.Types.Moderation Methods showsPrec :: Int -> ModItemOpts -> ShowS # show :: ModItemOpts -> String # showList :: [ModItemOpts] -> ShowS # | |
| Generic ModItemOpts Source # | |
Defined in Network.Reddit.Types.Moderation Associated Types type Rep ModItemOpts :: Type -> Type # | |
| ToForm ModItemOpts Source # | |
Defined in Network.Reddit.Types.Moderation Methods toForm :: ModItemOpts -> Form # | |
| type Rep ModItemOpts Source # | |
Defined in Network.Reddit.Types.Moderation type Rep ModItemOpts = D1 ('MetaData "ModItemOpts" "Network.Reddit.Types.Moderation" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "ModItemOpts" 'PrefixI 'True) (S1 ('MetaSel ('Just "only") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ItemType)))) | |
data RemovalMessage Source #
A message to explain/note the removal an Item
Constructors
| RemovalMessage | |
Fields
| |
Instances
data RemovalType Source #
Controls how the RemovalMessage will be disseminated
Constructors
| PublicComment | Leaves the message as a public comment |
| PrivateExposed | Leaves moderator note with exposed username |
| PrivateHidden | Leaves mod note with hidden username |
Instances
data RemovalReason Source #
A subreddit-specific reason for item removal
Constructors
| RemovalReason | |
Fields
| |
Instances
type RemovalReasonID = Text Source #
Identifier for a RemovalReason
data NewRemovalReasonID Source #
Instances
data RemovalReasonList Source #
Instances
Subreddit relationships
data ModPermission Source #
Various permissions that can be afforded to moderators and invitees
Constructors
| Access | |
| Flair | |
| Configuration | |
| ChatConfig | |
| ChatOperator | |
| Posts | |
| Wiki |
Instances
data SubredditRelationship Source #
The types of relationships that mods can manipulate
Constructors
| Mod | |
| ModInvitation | |
| Contributor | |
| BannedFromWiki | |
| WikiContributor | |
| Banned | |
| Muted |
Instances
Uniquely identifies a subreddit relationship, excluding mutes (see MuteID)
Identifies relationships representing muted users
data ModInvitee Source #
Information about a user who has been invited to moderate the subreddit
Constructors
| ModInvitee | |
Instances
data ModInviteeList Source #
A list containing users invited to moderate the subreddit. For some reason,
the endpoints listing moderator invites do not use the same Listing mechanism
that most other endpoints do
Constructors
| ModInviteeList | |
Instances
Wrapped for list of moderators, which resembles a Listing, but cannot be
paginated or filtered
Instances
| Show ModList Source # | |
| Generic ModList Source # | |
| FromJSON ModList Source # | |
| type Rep ModList Source # | |
Defined in Network.Reddit.Types.Moderation type Rep ModList = D1 ('MetaData "ModList" "Network.Reddit.Types.Moderation" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'True) (C1 ('MetaCons "ModList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq ModAccount)))) | |
data ModAccount Source #
Account information about a moderator, similar to a Account, but
with less information
Constructors
| ModAccount | |
Instances
Information about a contributor on the subreddit
Instances
Information about a muted user
Instances
data RelInfoOpts Source #
Options for Listings of RelInfo. Currently only takes a single
field, user, to limit the listing to a single user
Constructors
| RelInfoOpts | |
Instances
| Eq RelInfoOpts Source # | |
Defined in Network.Reddit.Types.Moderation | |
| Show RelInfoOpts Source # | |
Defined in Network.Reddit.Types.Moderation Methods showsPrec :: Int -> RelInfoOpts -> ShowS # show :: RelInfoOpts -> String # showList :: [RelInfoOpts] -> ShowS # | |
| Generic RelInfoOpts Source # | |
Defined in Network.Reddit.Types.Moderation Associated Types type Rep RelInfoOpts :: Type -> Type # | |
| ToForm RelInfoOpts Source # | |
Defined in Network.Reddit.Types.Moderation Methods toForm :: RelInfoOpts -> Form # | |
| type Rep RelInfoOpts Source # | |
Defined in Network.Reddit.Types.Moderation type Rep RelInfoOpts = D1 ('MetaData "RelInfoOpts" "Network.Reddit.Types.Moderation" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "RelInfoOpts" 'PrefixI 'True) (S1 ('MetaSel ('Just "username") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Username)))) | |
Represents an account that has been banned from a particular subreddit
Constructors
| Ban | |
Instances
Details of a new ban to apply to a user
Constructors
| BanNotes | |
Instances
| Eq BanNotes Source # | |
| Show BanNotes Source # | |
| Generic BanNotes Source # | |
| ToForm BanNotes Source # | |
Defined in Network.Reddit.Types.Moderation | |
| type Rep BanNotes Source # | |
Defined in Network.Reddit.Types.Moderation type Rep BanNotes = D1 ('MetaData "BanNotes" "Network.Reddit.Types.Moderation" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "BanNotes" 'PrefixI 'True) ((S1 ('MetaSel ('Just "banMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Body) :*: S1 ('MetaSel ('Just "banReason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Body)) :*: (S1 ('MetaSel ('Just "duration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Word)) :*: S1 ('MetaSel ('Just "note") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Body)))) | |
Subreddit settings
data SubredditSettings Source #
The settings that may be configured for a particular subreddit
Constructors
Instances
data CrowdControlLevel Source #
The setting for crowd controls, from lenient to strict
Instances
data SubredditType Source #
The privacy level for the subreddit
Instances
data SpamFilter Source #
The strength of the subreddit's spam filter
Constructors
| LowFilter | |
| HighFilter | |
| AllFilter |
Instances
The editing mode for a subreddit's wiki
Constructors
| EditDisabled | Only mods can edit |
| ApprovedEdit | Only mods and approved editors can edit |
| ContributorEdit | Any sub contributor can edit |
Instances
| Eq Wikimode Source # | |
| Ord Wikimode Source # | |
Defined in Network.Reddit.Types.Moderation | |
| Show Wikimode Source # | |
| Generic Wikimode Source # | |
| FromJSON Wikimode Source # | |
| ToHttpApiData Wikimode Source # | |
Defined in Network.Reddit.Types.Moderation Methods toUrlPiece :: Wikimode -> Text # toEncodedUrlPiece :: Wikimode -> Builder # toHeader :: Wikimode -> ByteString # toQueryParam :: Wikimode -> Text # | |
| type Rep Wikimode Source # | |
Defined in Network.Reddit.Types.Moderation type Rep Wikimode = D1 ('MetaData "Wikimode" "Network.Reddit.Types.Moderation" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "EditDisabled" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ApprovedEdit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ContributorEdit" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data ContentOptions Source #
Permissible submissions on the subreddit
Constructors
| AnyContent | |
| LinkOnly | |
| SelfOnly |
Instances
Modmail
Moderator mail. Reddit no longer supports the older, message-based interface for modmail
Constructors
| Modmail | |
Fields | |
Instances
| Eq Modmail Source # | |
| Show Modmail Source # | |
| Generic Modmail Source # | |
| FromJSON Modmail Source # | |
| type Rep Modmail Source # | |
Defined in Network.Reddit.Types.Moderation type Rep Modmail = D1 ('MetaData "Modmail" "Network.Reddit.Types.Moderation" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'True) (C1 ('MetaCons "Modmail" 'PrefixI 'True) (S1 ('MetaSel ('Just "conversations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq ModmailConversation)))) | |
data ModmailConversation Source #
A single modmail conversation
Constructors
| ModmailConversation | |
Fields
| |
Instances
data ModmailMessage Source #
A single message in a ModmailConversation
Constructors
| ModmailMessage | |
Fields
| |
Instances
data BulkReadIDs Source #
Instances
| Show BulkReadIDs Source # | |
Defined in Network.Reddit.Types.Moderation Methods showsPrec :: Int -> BulkReadIDs -> ShowS # show :: BulkReadIDs -> String # showList :: [BulkReadIDs] -> ShowS # | |
| Generic BulkReadIDs Source # | |
Defined in Network.Reddit.Types.Moderation Associated Types type Rep BulkReadIDs :: Type -> Type # | |
| FromJSON BulkReadIDs Source # | |
Defined in Network.Reddit.Types.Moderation | |
| type Rep BulkReadIDs Source # | |
Defined in Network.Reddit.Types.Moderation type Rep BulkReadIDs = D1 ('MetaData "BulkReadIDs" "Network.Reddit.Types.Moderation" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'True) (C1 ('MetaCons "BulkReadIDs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq ModmailID)))) | |
data ModmailAuthor Source #
An author in a ModmailConversation; can be either a mod or a non-mod user
Constructors
| ModmailAuthor | |
Instances
data ModmailObjID Source #
A mapping to a modmail action to its ID
Constructors
| ModmailObjID | |
Instances
| Eq ModmailObjID Source # | |
Defined in Network.Reddit.Types.Moderation | |
| Show ModmailObjID Source # | |
Defined in Network.Reddit.Types.Moderation Methods showsPrec :: Int -> ModmailObjID -> ShowS # show :: ModmailObjID -> String # showList :: [ModmailObjID] -> ShowS # | |
| Generic ModmailObjID Source # | |
Defined in Network.Reddit.Types.Moderation Associated Types type Rep ModmailObjID :: Type -> Type # | |
| FromJSON ModmailObjID Source # | |
Defined in Network.Reddit.Types.Moderation | |
| type Rep ModmailObjID Source # | |
Defined in Network.Reddit.Types.Moderation type Rep ModmailObjID = D1 ('MetaData "ModmailObjID" "Network.Reddit.Types.Moderation" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "ModmailObjID" 'PrefixI 'True) (S1 ('MetaSel ('Just "objID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "key") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))) | |
data ModmailState Source #
The state of the modmail, for use when filtering mail
Constructors
| AllModmail | |
| NewModmail | |
| Appeals | |
| Notifications | |
| Inbox | |
| InProgress | |
| ArchivedMail | |
| Highlighted | |
| JoinRequests | |
| ModModmail |
Instances
data ModmailSort Source #
Order to sort modmail in
Constructors
| FromUser | |
| FromMod | |
| RecentMail | |
| UnreadMail |
Instances
data ModmailOpts Source #
Options for filtering/paginating modmail endpoints. Notably, this is an
entirely different mechanism than the usual Listings elsewhere on Reddit
Constructors
| ModmailOpts | |
Fields
| |
Instances
defaultModmailOpts :: ModmailOpts Source #
Default options for filtering modmail
data ConversationDetails Source #
Wrapper for parsing the JSON returned from the conversation details API endpoint. This is formatted differently and has different fields than the modmail overview endpoint
Instances
data ModmailReply Source #
A new reply to a ModmailConversation
Constructors
| ModmailReply | |
Fields
| |
Instances
mkModmailReply :: Body -> ModmailReply Source #
ModmailReply with default values for boolean fields
data NewConversation Source #
A new, mod-created modmail conversation
Constructors
| NewConversation | |
Fields
| |
Instances
Modlog
An action issued by a moderator. The various fields prefixed target can
refer to comments or submissions, where applicable
Constructors
| ModAction | |
Fields
| |
Instances
data ModActionID Source #
Identifier for an issued ModAction
Instances
data ModActionType Source #
Classification for ModActions
Constructors
Instances
data ModActionOpts Source #
Constructors
| ModActionOpts | |
Instances
| Eq ModActionOpts Source # | |
Defined in Network.Reddit.Types.Moderation Methods (==) :: ModActionOpts -> ModActionOpts -> Bool # (/=) :: ModActionOpts -> ModActionOpts -> Bool # | |
| Show ModActionOpts Source # | |
Defined in Network.Reddit.Types.Moderation Methods showsPrec :: Int -> ModActionOpts -> ShowS # show :: ModActionOpts -> String # showList :: [ModActionOpts] -> ShowS # | |
| Generic ModActionOpts Source # | |
Defined in Network.Reddit.Types.Moderation Associated Types type Rep ModActionOpts :: Type -> Type # | |
| type Rep ModActionOpts Source # | |
Defined in Network.Reddit.Types.Moderation type Rep ModActionOpts = D1 ('MetaData "ModActionOpts" "Network.Reddit.Types.Moderation" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "ModActionOpts" 'PrefixI 'True) (S1 ('MetaSel ('Just "action") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe ModActionType)) :*: S1 ('MetaSel ('Just "moderator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Username)))) | |
Styles and images
data Stylesheet Source #
The CSS stylesheet and images for a subreddit
Constructors
| Stylesheet | |
Fields
| |
Instances
data SubredditImage Source #
An image belonging to a Stylesheet
Instances
data S3ModerationLease Source #
Used to upload style assets and images to Reddit's servers with moderator privileges
Constructors
| S3ModerationLease | |
Instances
data StructuredStyleImage Source #
Represents one of the style images that may be uploaded
Constructors
| BannerBackground | |
| BannerAdditional | |
| BannerHover |
Instances
data StyleImageAlignment Source #
Alignment for certain StructuredStyleImages
Constructors
| LeftAligned | |
| CenterAligned | |
| RightAligned |
Instances
Misc
data TrafficStat Source #
An individual statistic for a subreddit's traffic
Constructors
| TrafficStat | |
Fields
| |
Instances
Traffic statistics for a given subreddit
Constructors
| Traffic | |
Fields
| |
Instances
| Eq Traffic Source # | |
| Show Traffic Source # | |
| Generic Traffic Source # | |
| FromJSON Traffic Source # | |
| type Rep Traffic Source # | |
Defined in Network.Reddit.Types.Moderation type Rep Traffic = D1 ('MetaData "Traffic" "Network.Reddit.Types.Moderation" "heddit-0.0.1-76ROQ5tOAm3CpLSaFw8ccb" 'False) (C1 ('MetaCons "Traffic" 'PrefixI 'True) (S1 ('MetaSel ('Just "hour") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq TrafficStat)) :*: (S1 ('MetaSel ('Just "day") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq TrafficStat)) :*: S1 ('MetaSel ('Just "month") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq TrafficStat))))) | |
data LanguageCode where Source #
The language in which the subreddit is available, as configured in the
SubredditSettings
Bundled Patterns