{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
module Network.Reddit.Item
(
delete
, reply
, edit
, vote
, report
, save
, unsave
, setInboxReplies
, getGildedItems
, module M
) where
import Data.Generics.Wrapped ( wrappedTo )
import Lens.Micro
import Network.Reddit.Internal
import Network.Reddit.Types
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.HttpApiData
( ToHttpApiData(toQueryParam, toUrlPiece)
)
delete :: MonadReddit m => ItemID -> m ()
delete :: ItemID -> m ()
delete ItemID
iid =
APIAction () -> m ()
forall (m :: * -> *). MonadReddit m => APIAction () -> m ()
runAction_ APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"del" ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData = [(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"id", ItemID -> PathSegment
forall a. Thing a => a -> PathSegment
fullname ItemID
iid) ]
}
reply :: MonadReddit m => ItemID -> Body -> m Comment
reply :: ItemID -> PathSegment -> m Comment
reply ItemID
iid PathSegment
txt = APIAction (PostedItem Comment) -> m (PostedItem Comment)
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @(PostedItem Comment) APIAction (PostedItem Comment)
forall a. APIAction a
r m (PostedItem Comment)
-> (PostedItem Comment -> Comment) -> m Comment
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> PostedItem Comment -> Comment
forall s t a b. Wrapped s t a b => s -> a
wrappedTo
where
r :: APIAction a
r = APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"comment" ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData = [(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"thing_id", ItemID -> PathSegment
forall a. Thing a => a -> PathSegment
fullname ItemID
iid)
, (PathSegment
"text", PathSegment
txt)
, (PathSegment
"api_type", PathSegment
"json")
]
}
edit :: MonadReddit m => ItemID -> Body -> m Item
edit :: ItemID -> PathSegment -> m Item
edit ItemID
iid PathSegment
txt = APIAction (PostedItem Item) -> m (PostedItem Item)
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction @(PostedItem Item) APIAction (PostedItem Item)
forall a. APIAction a
r m (PostedItem Item) -> (PostedItem Item -> Item) -> m Item
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> PostedItem Item -> Item
forall s t a b. Wrapped s t a b => s -> a
wrappedTo
where
r :: APIAction a
r = APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"editusertext" ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData = [(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"thing_id", ItemID -> PathSegment
forall a. Thing a => a -> PathSegment
fullname ItemID
iid)
, (PathSegment
"text", PathSegment
txt)
, (PathSegment
"api_type", PathSegment
"json")
]
}
vote :: MonadReddit m => Vote -> ItemID -> m ()
vote :: Vote -> ItemID -> m ()
vote Vote
v ItemID
iid =
APIAction () -> m ()
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"vote" ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData =
[(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"id", ItemID -> PathSegment
forall a. Thing a => a -> PathSegment
fullname ItemID
iid), (PathSegment
"dir", PathSegment
voteDir) ]
}
where
voteDir :: PathSegment
voteDir = case Vote
v of
Vote
Downvote -> PathSegment
"-1"
Vote
Unvote -> PathSegment
"0"
Vote
Upvote -> PathSegment
"1"
report :: MonadReddit m => Report -> ItemID -> m ()
report :: Report -> ItemID -> m ()
report Report
r ItemID
iid =
APIAction () -> m ()
forall (m :: * -> *). MonadReddit m => APIAction () -> m ()
runAction_ APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"report" ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData = [(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"id", ItemID -> PathSegment
forall a. Thing a => a -> PathSegment
fullname ItemID
iid)
, (PathSegment
"reason", Report -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam Report
r)
]
}
save :: MonadReddit m => ItemID -> m ()
save :: ItemID -> m ()
save = PathSegment -> ItemID -> m ()
forall (m :: * -> *).
MonadReddit m =>
PathSegment -> ItemID -> m ()
saveOrUnsave PathSegment
"save"
unsave :: MonadReddit m => ItemID -> m ()
unsave :: ItemID -> m ()
unsave = PathSegment -> ItemID -> m ()
forall (m :: * -> *).
MonadReddit m =>
PathSegment -> ItemID -> m ()
saveOrUnsave PathSegment
"unsave"
saveOrUnsave :: MonadReddit m => PathSegment -> ItemID -> m ()
saveOrUnsave :: PathSegment -> ItemID -> m ()
saveOrUnsave PathSegment
path ItemID
iid =
APIAction () -> m ()
forall (m :: * -> *). MonadReddit m => APIAction () -> m ()
runAction_ APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
path ]
, $sel:method:APIAction :: Method
method = Method
POST
, $sel:requestData:APIAction :: WithData
requestData = [(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"id", ItemID -> PathSegment
forall a. Thing a => a -> PathSegment
fullname ItemID
iid) ]
}
setInboxReplies :: MonadReddit m => Bool -> ItemID -> m ()
setInboxReplies :: Bool -> ItemID -> m ()
setInboxReplies Bool
p ItemID
iid =
APIAction () -> m ()
forall (m :: * -> *). MonadReddit m => APIAction () -> m ()
runAction_ APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"api", PathSegment
"sendreplies" ]
, $sel:requestData:APIAction :: WithData
requestData = [(PathSegment, PathSegment)] -> WithData
mkTextFormData [ (PathSegment
"id", ItemID -> PathSegment
forall a. Thing a => a -> PathSegment
fullname ItemID
iid)
, (PathSegment
"state", Bool -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toQueryParam Bool
p)
]
}
getGildedItems :: MonadReddit m
=> SubredditName
-> Paginator ItemID Item
-> m (Listing ItemID Item)
getGildedItems :: SubredditName -> Paginator ItemID Item -> m (Listing ItemID Item)
getGildedItems SubredditName
sname Paginator ItemID Item
paginator =
APIAction (Listing ItemID Item) -> m (Listing ItemID Item)
forall a (m :: * -> *).
(MonadReddit m, FromJSON a) =>
APIAction a -> m a
runAction APIAction Any
forall a. APIAction a
defaultAPIAction
{ $sel:pathSegments:APIAction :: [PathSegment]
pathSegments = [ PathSegment
"r", SubredditName -> PathSegment
forall a. ToHttpApiData a => a -> PathSegment
toUrlPiece SubredditName
sname, PathSegment
"gilded" ]
, $sel:requestData:APIAction :: WithData
requestData = Paginator ItemID Item -> WithData
forall t a. (Thing t, Paginable a) => Paginator t a -> WithData
paginatorToFormData Paginator ItemID Item
paginator
}