heddit-0.2: Reddit API bindings
Copyright(c) 2021 Rory Tyler Hayford
LicenseBSD-3-Clause
Maintainerrory.hayford@protonmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Network.Reddit.Comment

Description

 
Synopsis

Reading comments

getComments :: (MonadReddit m, Foldable t) => ItemOpts -> t CommentID -> m (Seq Comment) Source #

Get the Comments corresponding to a container of CommentIDs

getComment :: MonadReddit m => CommentID -> m Comment Source #

Get information on a single CommentID. Throws an exception if no such Comment exists

getCommentByURL :: MonadReddit m => URL -> m Comment Source #

Get a comment based on its permalink URL, which must be of the form https://{www.}reddit.com/r/<SUB>/comments/<SID>/<NAME>/<ID>

withReplies :: MonadReddit m => ItemOpts -> Comment -> m Comment Source #

Update a Comment to include its ChildComments, returning the updated Comment. This will probably be necessary if the original Comment was obtained by getting a Username's or Subreddit's comments, etc...

loadMoreComments :: forall m. MonadReddit m => Maybe Word -> ItemOpts -> SubmissionID -> MoreComments -> m (Seq ChildComment) Source #

Transform MoreComments, loading the actual comments they refer to, up to the limit passed in (pass Nothing for no limit). If CommentIDs still remain from the original MoreComments, they will be returned in a new MoreComments inserted into the resulting sequence of ChildComments, along with an updated count

loadMoreCommentsDef :: MonadReddit m => SubmissionID -> MoreComments -> m (Seq ChildComment) Source #

A version of loadMoreComments with default parameters for the limit (Nothing) and options (defaultItemOpts)

unsaveComment :: MonadReddit m => CommentID -> m () Source #

Unsave a comment

saveComment :: MonadReddit m => CommentID -> m () Source #

Save a comment

Creating, editing, and deleting

deleteComment :: MonadReddit m => CommentID -> m () Source #

Delete a comment that the currently authenticated user has authored, given its CommentID

editComment :: MonadReddit m => CommentID -> Body -> m Comment Source #

Edit a comment given its CommentID, receving an updated Comment in response

replyToComment :: MonadReddit m => CommentID -> Body -> m Comment Source #

Reply to a comment given its CommentID, returning the newly created Comment

getNewComments :: MonadReddit m => Maybe SubredditName -> Paginator CommentID Comment -> m (Listing CommentID Comment) Source #

Get new Comments, either for the site as a whole or for a single subreddit, given its SubredditName

setCommentReplies :: MonadReddit m => Bool -> CommentID -> m () Source #

Enable/disable inbox replies for a comment

Voting

Note: According to Reddit's API rules:

votes must be cast by humans. That is, API clients proxying a human's action one-for-one are OK, but bots deciding how to vote on content or amplifying a human's vote are not. See the reddit rules for more details on what constitutes vote cheating.

upvoteComment :: MonadReddit m => CommentID -> m () Source #

Upvote a comment.

downvoteComment :: MonadReddit m => CommentID -> m () Source #

Downvote a comment.

unvoteComment :: MonadReddit m => CommentID -> m () Source #

Remove an existing vote on a comment.

Awarding

awardComment :: MonadReddit m => Award -> CommentID -> m AwardingsSummary Source #

Grant an Award to a comment. See mkAward for creating an award with default values, as well as the pattern synonyms for common awards

gildComment :: MonadReddit m => CommentID -> m AwardingsSummary Source #

Convenience action to anonymously give Gold to the author of a comment, without a message. See awardComment if you need more fine-grained control

Misc

reportComment :: MonadReddit m => Report -> CommentID -> m () Source #

Report a comment to the subreddit's mods

Types

data MoreComments Source #

A link to load more children Comments

Instances

Instances details
Eq MoreComments Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Show MoreComments Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Generic MoreComments Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Associated Types

type Rep MoreComments :: Type -> Type #

FromJSON MoreComments Source # 
Instance details

Defined in Network.Reddit.Types.Comment

type Rep MoreComments Source # 
Instance details

Defined in Network.Reddit.Types.Comment

type Rep MoreComments = D1 ('MetaData "MoreComments" "Network.Reddit.Types.Comment" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "MoreComments" 'PrefixI 'True) (S1 ('MetaSel ('Just "childIDs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq CommentID)) :*: S1 ('MetaSel ('Just "count") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Integer)))

data ChildComment Source #

Represents a comments on a submission or replies to a comment, which can be actual Comments, or a list of children corresponding to "load more" or "continue this thread" links on Reddit's UI

Instances

Instances details
Eq ChildComment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Show ChildComment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Generic ChildComment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Associated Types

type Rep ChildComment :: Type -> Type #

FromJSON ChildComment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

type Rep ChildComment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

type Rep ChildComment = D1 ('MetaData "ChildComment" "Network.Reddit.Types.Comment" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "TopLevel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Comment)) :+: C1 ('MetaCons "More" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MoreComments)))

data Comment Source #

A Reddit comment

Instances

Instances details
Eq Comment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Methods

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

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

Show Comment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Generic Comment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Associated Types

type Rep Comment :: Type -> Type #

Methods

from :: Comment -> Rep Comment x #

to :: Rep Comment x -> Comment #

FromJSON Comment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Paginable Comment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

FromJSON (PostedItem Comment) Source # 
Instance details

Defined in Network.Reddit.Types.Item

type Rep Comment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

type Rep Comment = D1 ('MetaData "Comment" "Network.Reddit.Types.Comment" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'False) (C1 ('MetaCons "Comment" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "commentID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommentID) :*: (S1 ('MetaSel ('Just "author") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Username) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Body))) :*: (S1 ('MetaSel ('Just "bodyHTML") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Body) :*: (S1 ('MetaSel ('Just "replies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq ChildComment)) :*: S1 ('MetaSel ('Just "score") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Integer))))) :*: ((S1 ('MetaSel ('Just "ups") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Integer)) :*: (S1 ('MetaSel ('Just "downs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Integer)) :*: S1 ('MetaSel ('Just "created") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UTCTime))) :*: (S1 ('MetaSel ('Just "edited") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe UTCTime)) :*: (S1 ('MetaSel ('Just "subreddit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SubredditName) :*: S1 ('MetaSel ('Just "subredditID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SubredditID))))) :*: (((S1 ('MetaSel ('Just "gilded") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "scoreHidden") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "linkID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SubmissionID))) :*: (S1 ('MetaSel ('Just "linkURL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe URL)) :*: (S1 ('MetaSel ('Just "linkAuthor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Username)) :*: S1 ('MetaSel ('Just "permaLink") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 URL)))) :*: ((S1 ('MetaSel ('Just "userReports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq ItemReport)) :*: (S1 ('MetaSel ('Just "modReports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq ItemReport)) :*: S1 ('MetaSel ('Just "numReports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Integer)))) :*: ((S1 ('MetaSel ('Just "distinguished") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Distinction)) :*: S1 ('MetaSel ('Just "isSubmitter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "stickied") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "allAwardings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq Awarding))))))))
type PaginateOptions Comment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

type PaginateThing Comment Source # 
Instance details

Defined in Network.Reddit.Types.Comment

newtype CommentID Source #

A Comment ID

Constructors

CommentID Text 

Instances

Instances details
Eq CommentID Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Ord CommentID Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Show CommentID Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Generic CommentID Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Associated Types

type Rep CommentID :: Type -> Type #

FromJSON CommentID Source # 
Instance details

Defined in Network.Reddit.Types.Comment

ToHttpApiData CommentID Source # 
Instance details

Defined in Network.Reddit.Types.Comment

Thing CommentID Source # 
Instance details

Defined in Network.Reddit.Types.Comment

type Rep CommentID Source # 
Instance details

Defined in Network.Reddit.Types.Comment

type Rep CommentID = D1 ('MetaData "CommentID" "Network.Reddit.Types.Comment" "heddit-0.2-6CPbqZeiNUj1PM6nX368ZU" 'True) (C1 ('MetaCons "CommentID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))