{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeApplications #-} -- | -- Module : Network.Reddit.Message -- Copyright : (c) 2021 Rory Tyler Hayford -- License : BSD-3-Clause -- Maintainer : rory.hayford@protonmail.com -- Stability : experimental -- Portability : GHC -- -- Actions for messaging. These can be both comment replies as well as private -- messages -- module Network.Reddit.Message ( -- * Actions getInbox , getUnread , getSent , markRead , sendMessage , replyToMessage , reportMessage -- * Types , module M ) where import Data.Generics.Wrapped ( wrappedTo ) import Data.Text ( Text ) import Lens.Micro import Network.Reddit.Internal import Network.Reddit.Types import Network.Reddit.Types.Item import Network.Reddit.Types.Message import Network.Reddit.Types.Message as M ( Message(Message) , MessageID , MessageOpts(MessageOpts) , NewMessage(NewMessage) , PrivateMessageID(PrivateMessageID) ) import Network.Reddit.Utils import Web.FormUrlEncoded ( ToForm(toForm) ) import Web.HttpApiData ( ToHttpApiData(toQueryParam) ) -- | Get the 'Message' inbox for the currently authenticated user getInbox :: MonadReddit m => Paginator MessageID Message -> m (Listing MessageID Message) getInbox = msgs "inbox" -- | Get the unread 'Message's of the currently authenticated user getUnread :: MonadReddit m => Paginator MessageID Message -> m (Listing MessageID Message) getUnread = msgs "unread" -- | Get the 'Message's sent by the currently authenticated user getSent :: MonadReddit m => Paginator MessageID Message -> m (Listing MessageID Message) getSent = msgs "sent" -- | Mark a 'Message' as read markRead :: MonadReddit m => MessageID -> m () markRead mid = runAction_ defaultAPIAction { pathSegments = [ "api", "read_message" ] , method = POST , requestData = mkTextFormData [ ("id", fullname mid) ] } -- | Send a 'NewMessage' to another user sendMessage :: MonadReddit m => NewMessage -> m () sendMessage newMsg = runAction_ defaultAPIAction { pathSegments = [ "api", "compose" ] , method = POST , requestData = WithForm $ toForm newMsg } -- | Reply to a 'Message', returning the newly created 'Message' replyToMessage :: MonadReddit m => MessageID -> Body -> m Message replyToMessage mid txt = runAction @PostedMessage r <&> wrappedTo where r = defaultAPIAction { pathSegments = [ "api", "comment" ] , method = POST , requestData = WithForm $ toForm @[(Text, Text)] [ ("thing_id", fullname mid) , ("text", txt) , ("api_type", "json") ] } msgs :: MonadReddit m => Text -> Paginator MessageID Message -> m (Listing MessageID Message) msgs path paginator = runAction defaultAPIAction { pathSegments = [ "message", path ] , requestData = paginatorToFormData paginator } -- | Report a message, bringing it to the attention of the Reddit admins reportMessage :: MonadReddit m => Report -> MessageID -> m () reportMessage r mid = runAction_ defaultAPIAction { pathSegments = [ "api", "report" ] , method = POST , requestData = mkTextFormData [ ("id", toQueryParam mid) , ("reason", toQueryParam r) ] }