Copyright | (c) 2021 Rory Tyler Hayford |
---|---|
License | BSD-3-Clause |
Maintainer | rory.hayford@protonmail.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Actions related to moderation. Assume that each action in this module requires moderator privileges, unless stated otherwise
Synopsis
- distinguishItem :: MonadReddit m => Distinction -> ItemID -> m ()
- undistinguishItem :: MonadReddit m => ItemID -> m ()
- removeItem :: MonadReddit m => Maybe Body -> Bool -> ItemID -> m ()
- sendRemovalMessage :: MonadReddit m => RemovalMessage -> m ()
- approveItem :: MonadReddit m => ItemID -> m ()
- lockItem :: MonadReddit m => ItemID -> m ()
- unlockItem :: MonadReddit m => ItemID -> m ()
- ignoreItemReports :: MonadReddit m => ItemID -> m ()
- unignoreItemReports :: MonadReddit m => ItemID -> m ()
- getRemovalReasons :: MonadReddit m => SubredditName -> m (Seq RemovalReason)
- createRemovalReason :: MonadReddit m => SubredditName -> Title -> Body -> m RemovalReasonID
- updateRemovalReason :: MonadReddit m => SubredditName -> RemovalReason -> m ()
- deleteRemovalReason :: MonadReddit m => SubredditName -> RemovalReasonID -> m ()
- getReports :: MonadReddit m => SubredditName -> Paginator ItemID ModItem -> m (Listing ItemID ModItem)
- getModqueue :: MonadReddit m => SubredditName -> Paginator ItemID ModItem -> m (Listing ItemID ModItem)
- getSpam :: MonadReddit m => SubredditName -> Paginator ItemID ModItem -> m (Listing ItemID ModItem)
- getEdited :: MonadReddit m => SubredditName -> Paginator ItemID ModItem -> m (Listing ItemID ModItem)
- getUnmoderated :: MonadReddit m => SubredditName -> Paginator ItemID ModItem -> m (Listing ItemID ModItem)
- getModlog :: MonadReddit m => SubredditName -> Paginator ModActionID ModAction -> m (Listing ModActionID ModAction)
- distinguishSubmission :: MonadReddit m => Distinction -> SubmissionID -> m ()
- undistinguishSubmission :: MonadReddit m => SubmissionID -> m ()
- approveSubmission :: MonadReddit m => SubmissionID -> m ()
- lockSubmission :: MonadReddit m => SubmissionID -> m ()
- unlockSubmission :: MonadReddit m => SubmissionID -> m ()
- ignoreSubmissionReports :: MonadReddit m => SubmissionID -> m ()
- unignoreSubmissionReports :: MonadReddit m => SubmissionID -> m ()
- unmarkNSFW :: MonadReddit m => SubmissionID -> m ()
- markNSFW :: MonadReddit m => SubmissionID -> m ()
- setOC :: MonadReddit m => SubredditName -> SubmissionID -> m ()
- unsetOC :: MonadReddit m => SubredditName -> SubmissionID -> m ()
- setSpoiler :: MonadReddit m => SubmissionID -> m ()
- unsetSpoiler :: MonadReddit m => SubmissionID -> m ()
- stickySubmission :: MonadReddit m => Bool -> SubmissionID -> m ()
- unstickySubmission :: MonadReddit m => SubmissionID -> m ()
- setSuggestedSort :: MonadReddit m => Maybe ItemSort -> SubmissionID -> m ()
- showComment :: MonadReddit m => CommentID -> m ()
- distinguishComment :: MonadReddit m => Distinction -> Bool -> CommentID -> m ()
- undistinguishComment :: MonadReddit m => CommentID -> m ()
- approveComment :: MonadReddit m => CommentID -> m ()
- lockComment :: MonadReddit m => CommentID -> m ()
- unlockComment :: MonadReddit m => CommentID -> m ()
- ignoreCommentReports :: MonadReddit m => CommentID -> m ()
- unignoreCommentReports :: MonadReddit m => CommentID -> m ()
- createCollection :: MonadReddit m => NewCollection -> m Collection
- deleteCollection :: MonadReddit m => CollectionID -> m ()
- addSubmissionToCollection :: MonadReddit m => CollectionID -> SubmissionID -> m ()
- removeSubmissionFromCollection :: MonadReddit m => CollectionID -> SubmissionID -> m ()
- reorderCollection :: (MonadReddit m, Foldable t) => CollectionID -> t SubmissionID -> m ()
- updateCollectionDescription :: MonadReddit m => CollectionID -> Body -> m ()
- updateCollectionTitle :: MonadReddit m => CollectionID -> Title -> m ()
- getModerators :: MonadReddit m => SubredditName -> m (Seq ModAccount)
- getModerator :: MonadReddit m => SubredditName -> Username -> m (Maybe ModAccount)
- updateModerator :: (MonadReddit m, Foldable t) => Maybe (t ModPermission) -> SubredditName -> Username -> m ()
- removeModerator :: MonadReddit m => SubredditName -> Username -> m ()
- abdicateModerator :: MonadReddit m => SubredditName -> m ()
- inviteModerator :: MonadReddit m => SubredditName -> Username -> m ()
- inviteModeratorWithPerms :: (MonadReddit m, Foldable t) => t ModPermission -> SubredditName -> Username -> m ()
- getInvitees :: MonadReddit m => Maybe ModInviteeList -> SubredditName -> m ModInviteeList
- getInvitee :: MonadReddit m => SubredditName -> Username -> m (Maybe ModInvitee)
- updateInvitation :: (MonadReddit m, Foldable t) => Maybe (t ModPermission) -> SubredditName -> Username -> m ()
- revokeInvitation :: MonadReddit m => SubredditName -> Username -> m ()
- acceptInvitation :: MonadReddit m => SubredditName -> m ()
- getContributors :: MonadReddit m => SubredditName -> Paginator RelID RelInfo -> m (Listing RelID RelInfo)
- getContributor :: MonadReddit m => SubredditName -> Username -> m (Maybe RelInfo)
- addContributor :: MonadReddit m => SubredditName -> Username -> m ()
- removeContributor :: MonadReddit m => SubredditName -> Username -> m ()
- abdicateContributor :: MonadReddit m => SubredditID -> m ()
- getWikiContributors :: MonadReddit m => SubredditName -> Paginator RelID RelInfo -> m (Listing RelID RelInfo)
- getWikiContributor :: MonadReddit m => SubredditName -> Username -> m (Maybe RelInfo)
- addWikiContributor :: MonadReddit m => SubredditName -> Username -> m ()
- removeWikiContributor :: MonadReddit m => SubredditName -> Username -> m ()
- getBans :: MonadReddit m => SubredditName -> Paginator RelID Ban -> m (Listing RelID Ban)
- getBan :: MonadReddit m => SubredditName -> Username -> m (Maybe Ban)
- banUser :: MonadReddit m => BanNotes -> SubredditName -> Username -> m ()
- unbanUser :: MonadReddit m => SubredditName -> Username -> m ()
- getWikibans :: MonadReddit m => SubredditName -> Paginator RelID RelInfo -> m (Listing RelID RelInfo)
- getWikiban :: MonadReddit m => SubredditName -> Username -> m (Maybe RelInfo)
- wikibanUser :: MonadReddit m => BanNotes -> SubredditName -> Username -> m ()
- wikiUnbanUser :: MonadReddit m => SubredditName -> Username -> m ()
- getMuted :: MonadReddit m => SubredditName -> Paginator MuteID MuteInfo -> m (Listing MuteID MuteInfo)
- getMutedUser :: MonadReddit m => SubredditName -> Username -> m (Maybe MuteInfo)
- unmuteUser :: MonadReddit m => SubredditName -> Username -> m ()
- muteUser :: MonadReddit m => BanNotes -> SubredditName -> Username -> m ()
- getSubredditSettings :: MonadReddit m => SubredditName -> m SubredditSettings
- setSubredditSettings :: MonadReddit m => SubredditSettings -> m ()
- addSubredditRule :: MonadReddit m => SubredditName -> NewSubredditRule -> m SubredditRule
- deleteSubredditRule :: MonadReddit m => SubredditName -> Name -> m ()
- updateSubredditRule :: MonadReddit m => SubredditName -> Name -> SubredditRule -> m SubredditRule
- reorderSubredditRules :: (MonadReddit m, Foldable t) => SubredditName -> t Name -> m ()
- getFlairList :: MonadReddit m => SubredditName -> Paginator UserID AssignedFlair -> m (Listing UserID AssignedFlair)
- getUserFlair :: MonadReddit m => SubredditName -> Username -> m (Maybe UserFlair)
- setUserFlair :: MonadReddit m => FlairSelection -> Username -> m ()
- setUserFlairs :: (MonadReddit m, Foldable t) => SubredditName -> t AssignedFlair -> m (Seq FlairResult)
- deleteUserFlair :: MonadReddit m => SubredditName -> Username -> m ()
- createFlairTemplate :: MonadReddit m => FlairType -> SubredditName -> FlairTemplate -> m FlairTemplate
- updateFlairTemplate :: MonadReddit m => FlairType -> SubredditName -> FlairTemplate -> m ()
- createUserFlairTemplate :: MonadReddit m => SubredditName -> FlairTemplate -> m FlairTemplate
- createSubmissionFlairTemplate :: MonadReddit m => SubredditName -> FlairTemplate -> m FlairTemplate
- updateSubmissionFlairTemplate :: MonadReddit m => SubredditName -> FlairTemplate -> m ()
- updateUserFlairTemplate :: MonadReddit m => SubredditName -> FlairTemplate -> m ()
- deleteFlairTemplate :: MonadReddit m => SubredditName -> FlairID -> m ()
- clearUserFlairTemplates :: MonadReddit m => SubredditName -> m ()
- clearSubmissionFlairTemplates :: MonadReddit m => SubredditName -> m ()
- clearFlairTemplates :: MonadReddit m => FlairType -> SubredditName -> m ()
- getStylesheet :: MonadReddit m => SubredditName -> m Stylesheet
- updateStylesheet :: MonadReddit m => SubredditName -> Maybe Text -> Text -> m ()
- uploadImage :: MonadReddit m => Text -> FilePath -> SubredditName -> m ()
- uploadHeader :: MonadReddit m => Text -> FilePath -> SubredditName -> m ()
- uploadMobileIcon :: MonadReddit m => Text -> FilePath -> SubredditName -> m ()
- uploadMobileHeader :: MonadReddit m => Text -> FilePath -> SubredditName -> m ()
- deleteImage :: MonadReddit m => Text -> SubredditName -> m ()
- deleteHeader :: MonadReddit m => SubredditName -> m ()
- deleteMobileIcon :: MonadReddit m => Text -> SubredditName -> m ()
- uploadBanner :: MonadReddit m => SubredditName -> FilePath -> m ()
- deleteBanner :: MonadReddit m => SubredditName -> m ()
- uploadBannerAdditional :: MonadReddit m => Maybe StyleImageAlignment -> SubredditName -> FilePath -> m ()
- deleteBannerAdditional :: MonadReddit m => SubredditName -> m ()
- uploadBannerHover :: MonadReddit m => SubredditName -> FilePath -> m ()
- deleteBannerHover :: MonadReddit m => SubredditName -> m ()
- addWikiEditor :: MonadReddit m => SubredditName -> WikiPageName -> Username -> m ()
- removeWikiEditor :: MonadReddit m => SubredditName -> WikiPageName -> Username -> m ()
- getWikiPageSettings :: MonadReddit m => SubredditName -> WikiPageName -> m WikiPageSettings
- revertWikiPage :: MonadReddit m => SubredditName -> WikiPageName -> WikiRevisionID -> m ()
- getModmail :: MonadReddit m => m Modmail
- getModmailWithOpts :: MonadReddit m => ModmailOpts -> m Modmail
- getModmailConversation :: MonadReddit m => ModmailID -> m ModmailConversation
- getUnreadModmailCount :: MonadReddit m => m (HashMap ModmailState Word)
- replyToConversation :: MonadReddit m => ModmailReply -> ModmailID -> m ModmailConversation
- archiveConversation :: MonadReddit m => ModmailID -> m ()
- unarchiveConversation :: MonadReddit m => ModmailID -> m ()
- highlightConversation :: MonadReddit m => ModmailID -> m ()
- unhighlightConversation :: MonadReddit m => ModmailID -> m ()
- markConversationsRead :: (Foldable t, MonadReddit m) => t ModmailID -> m ()
- markConversationRead :: MonadReddit m => ModmailID -> m ()
- markConversationsUnread :: (Foldable t, MonadReddit m) => t ModmailID -> m ()
- markConversationUnread :: MonadReddit m => ModmailID -> m ()
- bulkReadConversations :: (MonadReddit m, Foldable t) => Maybe ModmailState -> t SubredditName -> m (Seq ModmailID)
- muteModmailUser :: MonadReddit m => Word -> ModmailID -> m ()
- unmuteModmailUser :: MonadReddit m => ModmailID -> m ()
- createConversation :: MonadReddit m => NewConversation -> m ModmailConversation
- deleteWidget :: MonadReddit m => SubredditName -> WidgetID -> m ()
- updateWidget :: MonadReddit m => SubredditName -> WidgetID -> Widget -> m Widget
- reorderWidgets :: (MonadReddit m, Foldable t) => Maybe WidgetSection -> SubredditName -> t WidgetID -> m ()
- addButtonWidget :: MonadReddit m => SubredditName -> ButtonWidget -> m ButtonWidget
- addCalendarWidget :: MonadReddit m => Maybe Body -> SubredditName -> CalendarWidget -> m CalendarWidget
- addCommunityListWidget :: MonadReddit m => Maybe Body -> SubredditName -> CommunityListWidget -> m CommunityListWidget
- addCustomWidget :: MonadReddit m => SubredditName -> CustomWidget -> m CustomWidget
- addImageWidget :: MonadReddit m => SubredditName -> ImageWidget -> m ImageWidget
- addMenuWidget :: MonadReddit m => SubredditName -> MenuWidget -> m MenuWidget
- addPostFlairWidget :: MonadReddit m => SubredditName -> PostFlairWidget -> m PostFlairWidget
- addTextAreaWidget :: MonadReddit m => SubredditName -> TextAreaWidget -> m TextAreaWidget
- uploadWidgetImage :: MonadReddit m => SubredditName -> FilePath -> m UploadURL
- addEmoji :: MonadReddit m => SubredditName -> FilePath -> Emoji -> m ()
- deleteEmoji :: MonadReddit m => SubredditName -> EmojiName -> m ()
- updateEmoji :: MonadReddit m => SubredditName -> Emoji -> m ()
- setCustomEmojiSize :: MonadReddit m => SubredditName -> Maybe (Int, Int) -> m ()
- getTraffic :: MonadReddit m => SubredditName -> m Traffic
- data LanguageCode where
- pattern ZH :: LanguageCode
- pattern VI :: LanguageCode
- pattern UK :: LanguageCode
- pattern TR :: LanguageCode
- pattern TH :: LanguageCode
- pattern TA :: LanguageCode
- pattern SV :: LanguageCode
- pattern SR :: LanguageCode
- pattern SL :: LanguageCode
- pattern SK :: LanguageCode
- pattern RU :: LanguageCode
- pattern RO :: LanguageCode
- pattern PT :: LanguageCode
- pattern PL :: LanguageCode
- pattern NO :: LanguageCode
- pattern NN :: LanguageCode
- pattern NL :: LanguageCode
- pattern MS :: LanguageCode
- pattern LV :: LanguageCode
- pattern LA :: LanguageCode
- pattern KO :: LanguageCode
- pattern JA :: LanguageCode
- pattern IT :: LanguageCode
- pattern IS :: LanguageCode
- pattern ID :: LanguageCode
- pattern HY :: LanguageCode
- pattern HU :: LanguageCode
- pattern HR :: LanguageCode
- pattern HI :: LanguageCode
- pattern HE :: LanguageCode
- pattern GD :: LanguageCode
- pattern FR :: LanguageCode
- pattern FI :: LanguageCode
- pattern FA :: LanguageCode
- pattern EU :: LanguageCode
- pattern ES :: LanguageCode
- pattern EO :: LanguageCode
- pattern EN :: LanguageCode
- pattern EL :: LanguageCode
- pattern DE :: LanguageCode
- pattern DA :: LanguageCode
- pattern CY :: LanguageCode
- pattern CS :: LanguageCode
- pattern CA :: LanguageCode
- pattern BS :: LanguageCode
- pattern BG :: LanguageCode
- pattern AR :: LanguageCode
- pattern AF :: LanguageCode
- pattern GL :: LanguageCode
- pattern ET :: LanguageCode
- pattern LT :: LanguageCode
- pattern BE :: LanguageCode
- data Traffic = Traffic (Seq TrafficStat) (Seq TrafficStat) (Seq TrafficStat)
- data TrafficStat = TrafficStat UTCTime Integer Integer (Maybe Integer)
- data StyleImageAlignment
- data StructuredStyleImage
- data S3ModerationLease = S3ModerationLease URL (HashMap Text Text) Text URL
- data SubredditImage = SubredditImage Name Text URL
- data Stylesheet = Stylesheet Text (Seq SubredditImage) SubredditID
- 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 ModActionID
- data ModActionOpts = ModActionOpts (Maybe ModActionType) (Maybe Username)
- data ModAction = ModAction ModActionID Username ModActionType UTCTime (Maybe Body) (Maybe Text) (Maybe ItemID) (Maybe Username) (Maybe Title) (Maybe URL)
- data NewConversation = NewConversation Body Subject Username SubredditName Bool
- data ModmailReply = ModmailReply Body Bool Bool
- data ModmailState
- data ModmailSort
- data ModmailOpts = ModmailOpts (Maybe ModmailID) (Maybe [SubredditName]) (Maybe Word) (Maybe ModmailSort) (Maybe ModmailState)
- data ModmailAuthor = ModmailAuthor Username Bool Bool Bool Bool Bool Bool
- data ModmailMessage = ModmailMessage Text ModmailAuthor Body Body UTCTime Bool
- data ModmailObjID = ModmailObjID Text Text
- type ModmailID = Text
- data ModmailConversation = ModmailConversation ModmailID Subject (Seq ModmailMessage) Integer SubredditName (Maybe ModmailAuthor) (Seq ModmailObjID) UTCTime (Maybe UTCTime) (Maybe UTCTime) Bool Bool
- newtype Modmail = Modmail (Seq ModmailConversation)
- data BanNotes = BanNotes Body Body (Maybe Word) Body
- newtype MuteID = MuteID Text
- newtype RelID = RelID Text
- data Ban = Ban RelID Username UserID (Maybe Text) UTCTime (Maybe Word)
- data Wikimode
- data SpamFilter
- data ContentOptions
- data SubredditType
- data CrowdControlLevel
- data SubredditSettings = SubredditSettings SubredditID Title Body Text Text Text LanguageCode SubredditType ContentOptions RGBText Wikimode Integer Integer Integer SpamFilter SpamFilter SpamFilter CrowdControlLevel CrowdControlLevel Bool (Maybe ItemSort) (Maybe Text) Bool Bool Bool Bool Bool Bool Bool Bool Bool Bool Bool Bool Bool Bool Bool Bool Bool Bool Bool
- data RelInfoOpts = RelInfoOpts (Maybe Username)
- data MuteInfo = MuteInfo UserID MuteID Username UTCTime
- data RelInfo = RelInfo UserID RelID Username UTCTime
- data ModAccount = ModAccount Username UserID RelID (Maybe FlairText) (Maybe CSSClass) UTCTime (Maybe (Seq ModPermission))
- data ModInviteeList = ModInviteeList (Seq ModInvitee) Bool (Maybe UserID) (Maybe UserID)
- data ModInvitee = ModInvitee UserID Username (Maybe FlairText) (HashMap ModPermission Bool) UTCTime Integer
- data SubredditRelationship
- data ModPermission
- = Access
- | Flair
- | Configuration
- | ChatConfig
- | ChatOperator
- | Posts
- | Wiki
- data NewRemovalReasonID
- type RemovalReasonID = Text
- data RemovalReason = RemovalReason RemovalReasonID Body Title
- data RemovalType
- data RemovalMessage = RemovalMessage ItemID Body Title RemovalType
- data ModItemOpts = ModItemOpts (Maybe ItemType)
- newtype ModItem = ModItem Item
- defaultModmailOpts :: ModmailOpts
- mkModmailReply :: Body -> ModmailReply
Item moderation
These actions work on Item
s, i.e either Comment
s or Submission
s.
This module also exports variants that take unwrapped SubmissionID
s
and CommentID
s to work with just one type of item (see below)
distinguishItem :: MonadReddit m => Distinction -> ItemID -> m () Source #
Distinguish an item. See distinguishComment
for further comment-specific
options
undistinguishItem :: MonadReddit m => ItemID -> m () Source #
Remove the distinction from an item, also removing the sticky flag for top-level comments
:: MonadReddit m | |
=> Maybe Body | A note for other mods. This is sent in second request
if |
-> Bool | Spam flag. Will remove the item from all listings if |
-> ItemID | |
-> m () |
Remove an item from the subreddit with an optional note to other mods.
Setting the isSpam
parameter to True
will entirely remove the item
from subreddit listings
sendRemovalMessage :: MonadReddit m => RemovalMessage -> m () Source #
Send a removal message for an item. The precise action depends on the form
of RemovalType
approveItem :: MonadReddit m => ItemID -> m () Source #
Approve an item, reverting a removal and resetting its report counter
lockItem :: MonadReddit m => ItemID -> m () Source #
Lock an item. See also unlockItem
unlockItem :: MonadReddit m => ItemID -> m () Source #
Unlock an item
ignoreItemReports :: MonadReddit m => ItemID -> m () Source #
Prevent all future reports on this item from sending notifications or appearing
in moderation listings. See also unignoreItemReports
, which reverses this action
unignoreItemReports :: MonadReddit m => ItemID -> m () Source #
Re-allow the item to trigger notifications and appear in moderation listings
Removal reasons
getRemovalReasons :: MonadReddit m => SubredditName -> m (Seq RemovalReason) Source #
Get a list of RemovalReason
s for the given subreddit
createRemovalReason :: MonadReddit m => SubredditName -> Title -> Body -> m RemovalReasonID Source #
Create a new RemovalReason
, returning the RemovalReasonID
of the newly
created reason
updateRemovalReason :: MonadReddit m => SubredditName -> RemovalReason -> m () Source #
Update a single RemovalReason
deleteRemovalReason :: MonadReddit m => SubredditName -> RemovalReasonID -> m () Source #
Delete the given removal reason
Moderation listings
Each of these retrieves a Listing ItemID ModItem
. You can constrain
the type of reports by passing the appropriate ItemType
to the
paginator options
getReports :: MonadReddit m => SubredditName -> Paginator ItemID ModItem -> m (Listing ItemID ModItem) Source #
Get the given subreddit's reported items
getModqueue :: MonadReddit m => SubredditName -> Paginator ItemID ModItem -> m (Listing ItemID ModItem) Source #
Get the given subreddit's moderation queue
getSpam :: MonadReddit m => SubredditName -> Paginator ItemID ModItem -> m (Listing ItemID ModItem) Source #
Get the given subreddit's items marked as spam
getEdited :: MonadReddit m => SubredditName -> Paginator ItemID ModItem -> m (Listing ItemID ModItem) Source #
Get the given subreddit's recently edited items
getUnmoderated :: MonadReddit m => SubredditName -> Paginator ItemID ModItem -> m (Listing ItemID ModItem) Source #
Get the given subreddit's unmoderated items
getModlog :: MonadReddit m => SubredditName -> Paginator ModActionID ModAction -> m (Listing ModActionID ModAction) Source #
Get a log of moderator actions for the given subreddit
Submission moderation
Includes re-exports from Network.Reddit.Submission
distinguishSubmission :: MonadReddit m => Distinction -> SubmissionID -> m () Source #
Distinguish a submission
undistinguishSubmission :: MonadReddit m => SubmissionID -> m () Source #
Remove the distinction from a submission
approveSubmission :: MonadReddit m => SubmissionID -> m () Source #
Approve a submission. See approveItem
lockSubmission :: MonadReddit m => SubmissionID -> m () Source #
Lock a submission. See lockItem
unlockSubmission :: MonadReddit m => SubmissionID -> m () Source #
Unlock a submission. See unlockItem
ignoreSubmissionReports :: MonadReddit m => SubmissionID -> m () Source #
Ignore reports for a submission. See ignoreItemReports
unignoreSubmissionReports :: MonadReddit m => SubmissionID -> m () Source #
Resume reports for a submission. See unignoreItemReports
unmarkNSFW :: MonadReddit m => SubmissionID -> m () Source #
Unmark a submission NSFW. The submission author can use this as well as the subreddit moderators
markNSFW :: MonadReddit m => SubmissionID -> m () Source #
Mark a submission NSFW. The submission author can use this as well as the subreddit moderators
setOC :: MonadReddit m => SubredditName -> SubmissionID -> m () Source #
Mark a submission as original content. In order for normal users to use this feature in addition to mods, the beta "Original Content" feature must be enabled in the subreddit settings
unsetOC :: MonadReddit m => SubredditName -> SubmissionID -> m () Source #
Unmark a submission as original content. In order for normal users to use this feature in addition to mods, the beta "Original Content" feature must be enabled in the subreddit settings
setSpoiler :: MonadReddit m => SubmissionID -> m () Source #
Mark the submission as containing spoilers
unsetSpoiler :: MonadReddit m => SubmissionID -> m () Source #
Unmark the submission as containing spoilers
:: MonadReddit m | |
=> Bool | When |
-> SubmissionID | |
-> m () |
Sticky the submission in the subreddit
unstickySubmission :: MonadReddit m => SubmissionID -> m () Source #
Unsticky the submission in the subreddit
:: MonadReddit m | |
=> Maybe ItemSort | If |
-> SubmissionID | |
-> m () |
Set the suggested sort order for a submission
Comment moderation
showComment :: MonadReddit m => CommentID -> m () Source #
Show a comment that has been "collapsed" by crowd-control
:: MonadReddit m | |
=> Distinction | |
-> Bool | Sticky flag |
-> CommentID | |
-> m () |
Distinguish aa comment. If True
, the sticky
param will set the comment
at the top of the page. This only applies to top-level comments; the flg is
otherwise ignored
undistinguishComment :: MonadReddit m => CommentID -> m () Source #
Undistinguish a comment, also removing its sticky flag if applicable
approveComment :: MonadReddit m => CommentID -> m () Source #
Approve a comment. See approveItem
lockComment :: MonadReddit m => CommentID -> m () Source #
Lock a comment. See lockItem
unlockComment :: MonadReddit m => CommentID -> m () Source #
Unlock a comment. See unlockItem
ignoreCommentReports :: MonadReddit m => CommentID -> m () Source #
Ignore reports for a comment. See ignoreItemReports
unignoreCommentReports :: MonadReddit m => CommentID -> m () Source #
Resume reports for a comment. See unignoreItemReports
Collections moderation
createCollection :: MonadReddit m => NewCollection -> m Collection Source #
Create a new collection, returning the new Collection
upon success
deleteCollection :: MonadReddit m => CollectionID -> m () Source #
Delete the entire collection from the subreddit
addSubmissionToCollection :: MonadReddit m => CollectionID -> SubmissionID -> m () Source #
Add a submission to a collection
removeSubmissionFromCollection :: MonadReddit m => CollectionID -> SubmissionID -> m () Source #
Remove a submission from a collection
reorderCollection :: (MonadReddit m, Foldable t) => CollectionID -> t SubmissionID -> m () Source #
Reorder the submissions that comprise the collection by providing a
container of SubmissionID
s in the new intended order
updateCollectionDescription :: MonadReddit m => CollectionID -> Body -> m () Source #
Update the description of the collection
updateCollectionTitle :: MonadReddit m => CollectionID -> Title -> m () Source #
Update the title of the collection
Subreddit relationships
Moderators
getModerators :: MonadReddit m => SubredditName -> m (Seq ModAccount) Source #
Get a list of information on all moderators for the given subreddit
getModerator :: MonadReddit m => SubredditName -> Username -> m (Maybe ModAccount) Source #
Get information about a single moderator, if such a moderator exists
:: (MonadReddit m, Foldable t) | |
=> Maybe (t ModPermission) | If |
-> SubredditName | |
-> Username | |
-> m () |
Update the permissions granted to a current moderator
removeModerator :: MonadReddit m => SubredditName -> Username -> m () Source #
Revoke the given user's mod status
abdicateModerator :: MonadReddit m => SubredditName -> m () Source #
Revoke the authenticated user's mod status in the given subreddit. Caution!
Mod invitations
inviteModerator :: MonadReddit m => SubredditName -> Username -> m () Source #
Invite a user to moderate the subreddit. This action will implicitly grant
the invitee all moderator permissions on the subreddit. To control which
specific set of permissions the invitee shall be allowed instead, see
inviteModeratorWithPerms
inviteModeratorWithPerms Source #
:: (MonadReddit m, Foldable t) | |
=> t ModPermission | If empty, no permissions are granted |
-> SubredditName | |
-> Username | |
-> m () |
Invite a user to moderate the subreddit with a specific set of permissions
:: MonadReddit m | |
=> Maybe ModInviteeList | A previously obtained |
-> SubredditName | |
-> m ModInviteeList |
Get a listing of users invited to moderate the subreddit. This endpoint only
returns 25 results at a time, and does not use the Listing
mechanism that
prevails elsewhere. You can paginate through all invitees by passing previous
ModInviteeList
results to subsequent invocations
getInvitee :: MonadReddit m => SubredditName -> Username -> m (Maybe ModInvitee) Source #
Get information about a single invited user
:: (MonadReddit m, Foldable t) | |
=> Maybe (t ModPermission) | If |
-> SubredditName | |
-> Username | |
-> m () |
Update the permissions granted to the mod invitee
revokeInvitation :: MonadReddit m => SubredditName -> Username -> m () Source #
Revoke an existing moderator invitation for the given user
acceptInvitation :: MonadReddit m => SubredditName -> m () Source #
Accept the invitation issued to the authenticated user to moderate the given subreddit
Contributors
getContributors :: MonadReddit m => SubredditName -> Paginator RelID RelInfo -> m (Listing RelID RelInfo) Source #
Get a list of contributors on the subreddit
getContributor :: MonadReddit m => SubredditName -> Username -> m (Maybe RelInfo) Source #
Get a single contributor, if such a user exists
addContributor :: MonadReddit m => SubredditName -> Username -> m () Source #
Give a user contributor status on the subreddit
removeContributor :: MonadReddit m => SubredditName -> Username -> m () Source #
Remove a contributor from the subreddit
abdicateContributor :: MonadReddit m => SubredditID -> m () Source #
AbdicateModerator your contributor status on the given subreddit
getWikiContributors :: MonadReddit m => SubredditName -> Paginator RelID RelInfo -> m (Listing RelID RelInfo) Source #
Get a list of wiki contributors on the subreddit
getWikiContributor :: MonadReddit m => SubredditName -> Username -> m (Maybe RelInfo) Source #
Get a single wiki contributor, if such a user exists
addWikiContributor :: MonadReddit m => SubredditName -> Username -> m () Source #
Give a user wiki contributor privileges on the subreddit
removeWikiContributor :: MonadReddit m => SubredditName -> Username -> m () Source #
Revoke wiki contributor privileges on the subreddit
Bans
getBans :: MonadReddit m => SubredditName -> Paginator RelID Ban -> m (Listing RelID Ban) Source #
Get the banned users for a given subreddit
getBan :: MonadReddit m => SubredditName -> Username -> m (Maybe Ban) Source #
Check to see if a given user is banned on a particular subreddit,
returning the details of the Ban
if so
banUser :: MonadReddit m => BanNotes -> SubredditName -> Username -> m () Source #
Issue a ban against a user on the given subreddit, with the provided notes and (optional) duration
unbanUser :: MonadReddit m => SubredditName -> Username -> m () Source #
Remove an existing ban on a user
getWikibans :: MonadReddit m => SubredditName -> Paginator RelID RelInfo -> m (Listing RelID RelInfo) Source #
Get a list of users banned on the subreddit wiki
getWikiban :: MonadReddit m => SubredditName -> Username -> m (Maybe RelInfo) Source #
Get information on a single user banned on the subreddit wiki, if such a ban exists
wikibanUser :: MonadReddit m => BanNotes -> SubredditName -> Username -> m () Source #
Ban a user from participating in the wiki
wikiUnbanUser :: MonadReddit m => SubredditName -> Username -> m () Source #
Reverse an existing wiki ban for a user
getMuted :: MonadReddit m => SubredditName -> Paginator MuteID MuteInfo -> m (Listing MuteID MuteInfo) Source #
Get a list of users muted on the subreddit wiki
getMutedUser :: MonadReddit m => SubredditName -> Username -> m (Maybe MuteInfo) Source #
Get information on a single user muted on the subreddit wiki, if such a ban exists
unmuteUser :: MonadReddit m => SubredditName -> Username -> m () Source #
Unmute a single user on the subreddit
muteUser :: MonadReddit m => BanNotes -> SubredditName -> Username -> m () Source #
Mute a single user on the subreddit
Subreddit settings
getSubredditSettings :: MonadReddit m => SubredditName -> m SubredditSettings Source #
Get the configured SubredditSettings
for a given subreddit
setSubredditSettings :: MonadReddit m => SubredditSettings -> m () Source #
Configure a subreddit with the provided SubredditSettings
Subreddit rules
To get a list of the current rules for a Subreddit,
an action which does not require moderator privileges,
see getSubredditRules
.
Also note that a subreddit may only configure up to 15
individual rules at a time, and that trying to add more may
raise an exception
addSubredditRule :: MonadReddit m => SubredditName -> NewSubredditRule -> m SubredditRule Source #
Add a rule to the subreddit. The newly created SubredditRule
is returned
upon success
deleteSubredditRule :: MonadReddit m => SubredditName -> Name -> m () Source #
Delete the rule identified by the given name from the subreddit
:: MonadReddit m | |
=> SubredditName | |
-> Name | The old name for the rule. This is required even if you are not changing the name of the rule, as Reddit has no other data to uniquely identify the rule |
-> SubredditRule | |
-> m SubredditRule |
Update an existing subreddit rule. You must provide the shortName
of the
existing rule as a parameter in order for Reddit to identify the rule. The
shortName
can be changed by updating the SubredditRule
record, however
reorderSubredditRules Source #
:: (MonadReddit m, Foldable t) | |
=> SubredditName | |
-> t Name | The desired order of the rules. Must contain all of the |
-> m () |
Reorder the subreddit rules
Flair
getFlairList :: MonadReddit m => SubredditName -> Paginator UserID AssignedFlair -> m (Listing UserID AssignedFlair) Source #
Get a list of usernames and the flair currently assigned to them
getUserFlair :: MonadReddit m => SubredditName -> Username -> m (Maybe UserFlair) Source #
setUserFlair :: MonadReddit m => FlairSelection -> Username -> m () Source #
Set a user's flair. If the CSSClass
is provided in the FlairChoice
, it
takes precedence over the FlairID
contained in that record
setUserFlairs :: (MonadReddit m, Foldable t) => SubredditName -> t AssignedFlair -> m (Seq FlairResult) Source #
Set, update, or deleteSRImage the flair of multiple users at once, given a
container of AssignedFlair
s
deleteUserFlair :: MonadReddit m => SubredditName -> Username -> m () Source #
Delete a user's flair on the given subreddit
createFlairTemplate :: MonadReddit m => FlairType -> SubredditName -> FlairTemplate -> m FlairTemplate Source #
Create a new FlairTemplate
for either users or submissions, returning the
newly created template
updateFlairTemplate :: MonadReddit m => FlairType -> SubredditName -> FlairTemplate -> m () Source #
Update an existing FlairTemplate
for either users or submissions
createUserFlairTemplate :: MonadReddit m => SubredditName -> FlairTemplate -> m FlairTemplate Source #
Create a new FlairTemplate
for users, returning the newly created template
createSubmissionFlairTemplate :: MonadReddit m => SubredditName -> FlairTemplate -> m FlairTemplate Source #
Create a new FlairTemplate
for submissions, returning the newly created
template
updateSubmissionFlairTemplate :: MonadReddit m => SubredditName -> FlairTemplate -> m () Source #
Update an existing FlairTemplate
for submissions
updateUserFlairTemplate :: MonadReddit m => SubredditName -> FlairTemplate -> m () Source #
Update an existing FlairTemplate
for users
deleteFlairTemplate :: MonadReddit m => SubredditName -> FlairID -> m () Source #
Delete a user or submission flair template given its FlairID
clearUserFlairTemplates :: MonadReddit m => SubredditName -> m () Source #
Clear all of the user flair templates on the subreddit
clearSubmissionFlairTemplates :: MonadReddit m => SubredditName -> m () Source #
Clear all of the user flair templates on the subreddit
clearFlairTemplates :: MonadReddit m => FlairType -> SubredditName -> m () Source #
Clear all of the user or submission flair templates on the subreddit
Stylesheets, images and widgets
getStylesheet :: MonadReddit m => SubredditName -> m Stylesheet Source #
Get the Stylesheet
that has been configured for the given subreddit
:: MonadReddit m | |
=> SubredditName | |
-> Maybe Text | The reason for the change, if any |
-> Text | The new contents of the stylesheet |
-> m () |
Update a given subreddit's stylesheet with new contents, which must be valid CSS
Images
Reddit only allows JPEG or PNG images in stylsheets, and further requires
that all -- uploaded images be less than 500Kb in size. Each action that
uploads an image file to stylesheets validates both of these constraints,
throwing a ClientException
in the event that they are not satisfied.
Note that most of the actions that delete images will appear to succeed even if the named image does not exists
uploadImage :: MonadReddit m => Text -> FilePath -> SubredditName -> m () Source #
Upload an image file to add to the given subreddit's stylesheet
uploadHeader :: MonadReddit m => Text -> FilePath -> SubredditName -> m () Source #
Upload the image header for the given subreddit's stylesheet
uploadMobileIcon :: MonadReddit m => Text -> FilePath -> SubredditName -> m () Source #
Upload a mobile icon for the given subreddit
uploadMobileHeader :: MonadReddit m => Text -> FilePath -> SubredditName -> m () Source #
Upload the mobile header for the given subreddit
deleteImage :: MonadReddit m => Text -> SubredditName -> m () Source #
Delete the named image from the given subreddit's stylesheet
deleteHeader :: MonadReddit m => SubredditName -> m () Source #
Delete header image from the given subreddit
deleteMobileIcon :: MonadReddit m => Text -> SubredditName -> m () Source #
Delete the named image from the given subreddit's stylesheet
uploadBanner :: MonadReddit m => SubredditName -> FilePath -> m () Source #
Upload a banner for the subreddit (redesign only)
deleteBanner :: MonadReddit m => SubredditName -> m () Source #
Delete the subreddit banner, even if it does not exist (redesign only)
uploadBannerAdditional :: MonadReddit m => Maybe StyleImageAlignment -> SubredditName -> FilePath -> m () Source #
Upload the additional image banner for the subreddit (redesign only)
deleteBannerAdditional :: MonadReddit m => SubredditName -> m () Source #
Delete all additional banners, including the hover banner (redesign only)
uploadBannerHover :: MonadReddit m => SubredditName -> FilePath -> m () Source #
Upload the banner hover image for the subreddit (redesign only)
deleteBannerHover :: MonadReddit m => SubredditName -> m () Source #
Delete the subreddit banner hover image (redesign only)
Wiki
addWikiEditor :: MonadReddit m => SubredditName -> WikiPageName -> Username -> m () Source #
Grant editing privileges to the given Username
on the subreddit's wikipage
removeWikiEditor :: MonadReddit m => SubredditName -> WikiPageName -> Username -> m () Source #
Revoke the given Username
's editing privileges on the subreddit's wikipage
getWikiPageSettings :: MonadReddit m => SubredditName -> WikiPageName -> m WikiPageSettings Source #
Get the WikiPageSettings
for the subreddit's given wikipage
revertWikiPage :: MonadReddit m => SubredditName -> WikiPageName -> WikiRevisionID -> m () Source #
Revert the wikipage to the given revision
Modmail
getModmail :: MonadReddit m => m Modmail Source #
Get all of the authenticated user's modmail. See getModmailWithOpts
in
order to control how modmail is sorted or filtered
getModmailWithOpts :: MonadReddit m => ModmailOpts -> m Modmail Source #
Get the authenticated user's modmail with the provided ModmailOpts
getModmailConversation :: MonadReddit m => ModmailID -> m ModmailConversation Source #
Get a single ModmailConversation
given its ID
getUnreadModmailCount :: MonadReddit m => m (HashMap ModmailState Word) Source #
Get the number of unread modmail conversations according to conversation state
replyToConversation :: MonadReddit m => ModmailReply -> ModmailID -> m ModmailConversation Source #
Reply to the modmail conversation
archiveConversation :: MonadReddit m => ModmailID -> m () Source #
Archive a modmail conversation
unarchiveConversation :: MonadReddit m => ModmailID -> m () Source #
Archive a modmail conversation
highlightConversation :: MonadReddit m => ModmailID -> m () Source #
Highlight a given conversation
unhighlightConversation :: MonadReddit m => ModmailID -> m () Source #
Unhighlight a given conversation
markConversationsRead :: (Foldable t, MonadReddit m) => t ModmailID -> m () Source #
Mark the conversations corresponding to a container of ModmailID
s as read
markConversationRead :: MonadReddit m => ModmailID -> m () Source #
Mark the conversation corresponding to a single ModmailID
as read
markConversationsUnread :: (Foldable t, MonadReddit m) => t ModmailID -> m () Source #
Mark the conversations corresponding to a container of ModmailID
s as unread
markConversationUnread :: MonadReddit m => ModmailID -> m () Source #
Mark the conversation corresponding to a single ModmailID
as unread
bulkReadConversations :: (MonadReddit m, Foldable t) => Maybe ModmailState -> t SubredditName -> m (Seq ModmailID) Source #
Mark all mail belonging to the subreddits as read, returning the ModmailID
s
of the newly read conversations
muteModmailUser :: MonadReddit m => Word -> ModmailID -> m () Source #
Mute the non-moderator user associated with the modmail conversation. Valid
durations for the days
parameter are 3, 7, and 28
unmuteModmailUser :: MonadReddit m => ModmailID -> m () Source #
Unmute the non-moderator user associated with the modmail conversation
createConversation :: MonadReddit m => NewConversation -> m ModmailConversation Source #
Create a new ModmailConversation
Widgets
deleteWidget :: MonadReddit m => SubredditName -> WidgetID -> m () Source #
Delete a widget, given its ID
updateWidget :: MonadReddit m => SubredditName -> WidgetID -> Widget -> m Widget Source #
Update an existing widget, given its ID. You must wrap the widget type in
the appropriate Widget
constructors, as this action may be performed on
heterogeneous widget types. The update widget is returned upon success
reorderWidgets :: (MonadReddit m, Foldable t) => Maybe WidgetSection -> SubredditName -> t WidgetID -> m () Source #
Reorder the widgets corresponding to a container of widget IDs in the given
section. At the moment, reddit does not allow for the Topbar
to be reordered.
If you attempt to reorder this section, you might receive an InvalidJSON
exception
addButtonWidget :: MonadReddit m => SubredditName -> ButtonWidget -> m ButtonWidget Source #
Add a button widget. Returns the created widget upon success. See the docs for
ButtonWidget
for the available options
:: MonadReddit m | |
=> Maybe Body | A short description of the widget, in markdown |
-> SubredditName | |
-> CalendarWidget | |
-> m CalendarWidget |
Add a calendar widget, which requires an active Google account and public
calendar. Returns the created widget upon success. See the docs for
CalendarWidget
for the available options
addCommunityListWidget Source #
:: MonadReddit m | |
=> Maybe Body | A short description of the widget, in markdown |
-> SubredditName | |
-> CommunityListWidget | |
-> m CommunityListWidget |
Add a community list widget. Returns the created widget upon success. See
the docs for CommunityListWidget
for the available options
addCustomWidget :: MonadReddit m => SubredditName -> CustomWidget -> m CustomWidget Source #
Add a custom widget. Returns the created widget upon success. See
the docs for CustomWidget
for the available options
addImageWidget :: MonadReddit m => SubredditName -> ImageWidget -> m ImageWidget Source #
Add an image widget. Returns the created widget upon success. See
the docs for ImageWidget
for the available options
addMenuWidget :: MonadReddit m => SubredditName -> MenuWidget -> m MenuWidget Source #
Add a menu widget. Returns the created widget upon success. See
the docs for MenuWidget
for the available options
addPostFlairWidget :: MonadReddit m => SubredditName -> PostFlairWidget -> m PostFlairWidget Source #
Add a post flair widget. Returns the created widget upon success. See
the docs for PostFlairWidget
for the available options along with
mkPostFlairWidget
addTextAreaWidget :: MonadReddit m => SubredditName -> TextAreaWidget -> m TextAreaWidget Source #
Add a text area widget. Returns the created widget upon success. See
the docs for TextAreaWidget
for the available options as well as
mkTextAreaWidget
uploadWidgetImage :: MonadReddit m => SubredditName -> FilePath -> m UploadURL Source #
Upload a widget image from a filepath. This returns the URL of the new image, which is required for creating certain widgets
Emoji
:: MonadReddit m | |
=> SubredditName | |
-> FilePath | Must be an image in jpeg/png format, with maximum dimensions of 128 x 128px and size of 64KB |
-> Emoji | |
-> m () |
Add a new emoji by uploading an image. See mkEmoji
to conveniently create
new Emoji
s to add. Also note the restrictions on the filepath argument below,
which are not currently validated by this action. This action can also be used
to update the image for an existing emoji (see
getSubredditEmoji
) to get a list of emojis
for a subreddit
deleteEmoji :: MonadReddit m => SubredditName -> EmojiName -> m () Source #
Delete a single emoji and associated s3 image
updateEmoji :: MonadReddit m => SubredditName -> Emoji -> m () Source #
Update an emoji. Only the boolean permissions fields will be sent. If you
would like to change the image associated with the emoji name, use addEmoji
with an updated filepath
setCustomEmojiSize :: MonadReddit m => SubredditName -> Maybe (Int, Int) -> m () Source #
Set the (h, w) dimensions for all custom emojis on the subreddit. Both
dimensions must be between 16px and 40px. A Nothing
argument will disable
custom sizes
Misc
getTraffic :: MonadReddit m => SubredditName -> m Traffic Source #
Get traffic statistics for the given subreddit
Types
data LanguageCode where Source #
The language in which the subreddit is available, as configured in the
SubredditSettings
Instances
Traffic statistics for a given subreddit
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 TrafficStat Source #
An individual statistic for a subreddit's traffic
Instances
data StyleImageAlignment Source #
Alignment for certain StructuredStyleImage
s
Instances
data StructuredStyleImage Source #
Represents one of the style images that may be uploaded
Instances
data S3ModerationLease Source #
Used to upload style assets and images to Reddit's servers with moderator privileges
Instances
data SubredditImage Source #
An image belonging to a Stylesheet
Instances
data Stylesheet Source #
The CSS stylesheet and images for a subreddit
Instances
data ModActionType Source #
Classification for ModAction
s
Instances
data ModActionID Source #
Identifier for an issued ModAction
Instances
data ModActionOpts Source #
Instances
An action issued by a moderator. The various fields prefixed target
can
refer to comments or submissions, where applicable
ModAction ModActionID Username ModActionType UTCTime (Maybe Body) (Maybe Text) (Maybe ItemID) (Maybe Username) (Maybe Title) (Maybe URL) |
Instances
data NewConversation Source #
A new, mod-created modmail conversation
Instances
data ModmailReply Source #
A new reply to a ModmailConversation
Instances
data ModmailState Source #
The state of the modmail, for use when filtering mail
AllModmail | |
NewModmail | |
Appeals | |
Notifications | |
Inbox | |
InProgress | |
ArchivedMail | |
Highlighted | |
JoinRequests | |
ModModmail |
Instances
data ModmailSort Source #
Order to sort modmail in
Instances
data ModmailOpts Source #
Options for filtering/paginating modmail endpoints. Notably, this is an
entirely different mechanism than the usual Listing
s elsewhere on Reddit
ModmailOpts (Maybe ModmailID) (Maybe [SubredditName]) (Maybe Word) (Maybe ModmailSort) (Maybe ModmailState) |
Instances
data ModmailAuthor Source #
An author in a ModmailConversation
; can be either a mod or a non-mod user
Instances
data ModmailMessage Source #
A single message in a ModmailConversation
Instances
data ModmailObjID Source #
A mapping to a modmail action to its ID
Instances
data ModmailConversation Source #
A single modmail conversation
ModmailConversation ModmailID Subject (Seq ModmailMessage) Integer SubredditName (Maybe ModmailAuthor) (Seq ModmailObjID) UTCTime (Maybe UTCTime) (Maybe UTCTime) Bool Bool |
Instances
Moderator mail. Reddit no longer supports the older, message-based interface for modmail
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)))) |
Details of a new ban to apply to a user
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)))) |
Identifies relationships representing muted users
Uniquely identifies a subreddit relationship, excluding mutes (see MuteID
)
Represents an account that has been banned from a particular subreddit
Instances
The editing mode for a subreddit's wiki
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 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 SpamFilter Source #
The strength of the subreddit's spam filter
Instances
data ContentOptions Source #
Permissible submissions on the subreddit
Instances
data SubredditType Source #
The privacy level for the subreddit
Instances
data CrowdControlLevel Source #
The setting for crowd controls, from lenient to strict
Instances
data SubredditSettings Source #
The settings that may be configured for a particular subreddit
Instances
data RelInfoOpts Source #
Options for Listing
s of RelInfo
. Currently only takes a single
field, user
, to limit the listing to a single user
Instances
Eq RelInfoOpts Source # | |
Defined in Network.Reddit.Types.Moderation (==) :: RelInfoOpts -> RelInfoOpts -> Bool # (/=) :: RelInfoOpts -> RelInfoOpts -> Bool # | |
Show RelInfoOpts Source # | |
Defined in Network.Reddit.Types.Moderation showsPrec :: Int -> RelInfoOpts -> ShowS # show :: RelInfoOpts -> String # showList :: [RelInfoOpts] -> ShowS # | |
Generic RelInfoOpts Source # | |
Defined in Network.Reddit.Types.Moderation type Rep RelInfoOpts :: Type -> Type # from :: RelInfoOpts -> Rep RelInfoOpts x # to :: Rep RelInfoOpts x -> RelInfoOpts # | |
ToForm RelInfoOpts Source # | |
Defined in Network.Reddit.Types.Moderation 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)))) |
Information about a muted user
Instances
Information about a contributor on the subreddit
Instances
data ModAccount Source #
Account information about a moderator, similar to a Account
, but
with less information
ModAccount Username UserID RelID (Maybe FlairText) (Maybe CSSClass) UTCTime (Maybe (Seq ModPermission)) |
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
Instances
data ModInvitee Source #
Information about a user who has been invited to moderate the subreddit
Instances
data SubredditRelationship Source #
The types of relationships that mods can manipulate
Instances
data ModPermission Source #
Various permissions that can be afforded to moderators and invitees
Instances
data NewRemovalReasonID Source #
Instances
type RemovalReasonID = Text Source #
Identifier for a RemovalReason
data RemovalReason Source #
A subreddit-specific reason for item removal
Instances
data RemovalType Source #
Controls how the RemovalMessage
will be disseminated
PublicComment | Leaves the message as a public comment |
PrivateExposed | Leaves moderator note with exposed username |
PrivateHidden | Leaves mod note with hidden username |
Instances
data RemovalMessage Source #
A message to explain/note the removal an Item
Instances
data ModItemOpts Source #
Options for Listing
s of ModItem
s. Only contains one field, only
to
constrain the request to a single type (i.e. comments or links)
Instances
Eq ModItemOpts Source # | |
Defined in Network.Reddit.Types.Moderation (==) :: ModItemOpts -> ModItemOpts -> Bool # (/=) :: ModItemOpts -> ModItemOpts -> Bool # | |
Show ModItemOpts Source # | |
Defined in Network.Reddit.Types.Moderation showsPrec :: Int -> ModItemOpts -> ShowS # show :: ModItemOpts -> String # showList :: [ModItemOpts] -> ShowS # | |
Generic ModItemOpts Source # | |
Defined in Network.Reddit.Types.Moderation type Rep ModItemOpts :: Type -> Type # from :: ModItemOpts -> Rep ModItemOpts x # to :: Rep ModItemOpts x -> ModItemOpts # | |
ToForm ModItemOpts Source # | |
Defined in Network.Reddit.Types.Moderation 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)))) |
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 type PaginateOptions ModItem Source # type PaginateThing ModItem 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 |
defaultModmailOpts :: ModmailOpts Source #
Default options for filtering modmail
mkModmailReply :: Body -> ModmailReply Source #
ModmailReply
with default values for boolean fields