{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeApplications #-} -- | -- Module : Network.Reddit.Item -- Copyright : (c) 2021 Rory Tyler Hayford -- License : BSD-3-Clause -- Maintainer : rory.hayford@protonmail.com -- Stability : experimental -- Portability : GHC -- -- Actions with operate on 'Item's, which can be either 'Comment's or -- 'Submission's -- module Network.Reddit.Item ( -- * Actions delete , reply , edit , vote , report , save , unsave , award , gild , setInboxReplies , getGildedItems -- * Types , module M ) where import Data.Generics.Wrapped ( wrappedTo ) import Lens.Micro import Network.Reddit.Internal import Network.Reddit.Types import Network.Reddit.Types.Award import Network.Reddit.Types.Award as M ( Award(Award) , AwardID(..) , AwardingsSummary(AwardingsSummary) , mkAward ) import Network.Reddit.Types.Comment import Network.Reddit.Types.Item ( PostedItem ) import Network.Reddit.Types.Item as M ( Item(..) , ItemID(..) , Report , Vote(..) , mkReport ) import Network.Reddit.Types.Subreddit import Network.Reddit.Utils import Web.FormUrlEncoded ( ToForm(toForm) ) import Web.HttpApiData ( ToHttpApiData(toQueryParam, toUrlPiece) ) -- | Delete an 'Item' delete :: MonadReddit m => ItemID -> m () delete iid = runAction_ defaultAPIAction { pathSegments = [ "api", "del" ] , method = POST , requestData = mkTextFormData [ ("id", fullname iid) ] } -- | Leave a comment in reply to an 'Item', which can be markdown-formatted. This -- will return the newly created 'Comment' upon success reply :: MonadReddit m => ItemID -> Body -> m Comment reply iid txt = runAction @(PostedItem Comment) r <&> wrappedTo where r = defaultAPIAction { pathSegments = [ "api", "comment" ] , method = POST , requestData = mkTextFormData [ ("thing_id", fullname iid) , ("text", txt) , ("api_type", "json") ] } -- | Edit some item, given its 'ItemID'. The return value will be wrapped in an -- 'Item' constructor, since it can be either a 'Comment' or 'Submission' edit :: MonadReddit m => ItemID -> Body -> m Item edit iid txt = runAction @(PostedItem Item) r <&> wrappedTo where r = defaultAPIAction { pathSegments = [ "api", "editusertext" ] , method = POST , requestData = mkTextFormData [ ("thing_id", fullname iid) , ("text", txt) , ("api_type", "json") ] } -- | Submit a vote. Be careful! Reddit views bot-based vote manipulation as a -- serious violation vote :: MonadReddit m => Vote -> ItemID -> m () vote v iid = runAction defaultAPIAction { pathSegments = [ "api", "vote" ] , method = POST , requestData = mkTextFormData [ ("id", fullname iid), ("dir", voteDir) ] } where voteDir = case v of Downvote -> "-1" Unvote -> "0" Upvote -> "1" -- | Report an item, which brings it to the attention of the subreddit moderators report :: MonadReddit m => Report -> ItemID -> m () report r iid = runAction_ defaultAPIAction { pathSegments = [ "api", "report" ] , method = POST , requestData = mkTextFormData [ ("id", fullname iid) , ("reason", toQueryParam r) ] } -- | Save an item save :: MonadReddit m => ItemID -> m () save = saveOrUnsave "save" -- | Unsave an item unsave :: MonadReddit m => ItemID -> m () unsave = saveOrUnsave "unsave" saveOrUnsave :: MonadReddit m => PathSegment -> ItemID -> m () saveOrUnsave path iid = runAction_ defaultAPIAction { pathSegments = [ "api", path ] , method = POST , requestData = mkTextFormData [ ("id", fullname iid) ] } -- | Grant an award to the author of an 'Item'. See the docs for 'Award' for -- information about the available options when awarding as well as 'mkAward' -- to use defaults. -- -- To grant a common award, such as gold, see the bundled pattern synonyms of -- 'AwardID'. If you wish to anonymously gild an item without a message, see the -- 'gild' action in this module, provided for convenience award :: MonadReddit m => Award -> ItemID -> m AwardingsSummary award aw iid = runAction defaultAPIAction { pathSegments = [ "api", "v2", "gold", "gild" ] , method = POST , requestData = WithForm $ mkTextForm [ ("thing_id", fullname iid) ] <> toForm aw } -- | Gild an item anonymously, without a message. To grant other types of -- awards to items, or to gild non-anonymously\/with a message, see 'award' gild :: MonadReddit m => ItemID -> m AwardingsSummary gild = award $ mkAward Gold -- | Enable or disable inbox replies for an item given its 'ItemID' setInboxReplies :: MonadReddit m => Bool -> ItemID -> m () setInboxReplies p iid = runAction_ defaultAPIAction { pathSegments = [ "api", "sendreplies" ] , requestData = mkTextFormData [ ("id", fullname iid) , ("state", toQueryParam p) ] } -- | Get a @Listing@ of 'Item's that have been gilded getGildedItems :: MonadReddit m => SubredditName -> Paginator ItemID Item -> m (Listing ItemID Item) getGildedItems sname paginator = runAction defaultAPIAction { pathSegments = [ "r", toUrlPiece sname, "gilded" ] , requestData = paginatorToFormData paginator }