module Reddit.Routes.User where
import Reddit.Types.Comment (CommentID)
import Reddit.Types.Options
import Reddit.Types.Post
import Reddit.Types.Subreddit
import Reddit.Types.User
import Data.Text (Text)
import Network.API.Builder.Routes
aboutUser :: Username -> Route
aboutUser :: Username -> Route
aboutUser (Username Text
user) = [Text] -> [URLParam] -> Method -> Route
Route [ Text
"user", Text
user, Text
"about.json" ]
[]
Method
"GET"
aboutMe :: Route
aboutMe :: Route
aboutMe = [Text] -> [URLParam] -> Method -> Route
Route [ Text
"api", Text
"me.json" ]
[]
Method
"GET"
userComments :: Options CommentID -> Username -> Route
Options CommentID
opts (Username Text
user) =
[Text] -> [URLParam] -> Method -> Route
Route [ Text
"user", Text
user, Text
"comments" ]
[ Text
"limit" Text -> Maybe Int -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Options CommentID -> Maybe Int
forall a. Options a -> Maybe Int
limit Options CommentID
opts
, Text
"before" Text -> Maybe CommentID -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Options CommentID -> Maybe CommentID
forall a. Options a -> Maybe a
before Options CommentID
opts
, Text
"after" Text -> Maybe CommentID -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Options CommentID -> Maybe CommentID
forall a. Options a -> Maybe a
after Options CommentID
opts ]
Method
"GET"
userPosts :: Options PostID -> Username -> Route
userPosts :: Options PostID -> Username -> Route
userPosts Options PostID
opts (Username Text
user) =
[Text] -> [URLParam] -> Method -> Route
Route [ Text
"user", Text
user, Text
"submitted" ]
[ Text
"limit" Text -> Maybe Int -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Options PostID -> Maybe Int
forall a. Options a -> Maybe Int
limit Options PostID
opts
, Text
"before" Text -> Maybe PostID -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Options PostID -> Maybe PostID
forall a. Options a -> Maybe a
before Options PostID
opts
, Text
"after" Text -> Maybe PostID -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Options PostID -> Maybe PostID
forall a. Options a -> Maybe a
after Options PostID
opts ]
Method
"GET"
usernameAvailable :: Username -> Route
usernameAvailable :: Username -> Route
usernameAvailable Username
user = [Text] -> [URLParam] -> Method -> Route
Route [ Text
"api", Text
"username_available.json" ]
[ Text
"user" Text -> Username -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Username
user]
Method
"GET"
blocked :: Route
blocked :: Route
blocked = [Text] -> [URLParam] -> Method -> Route
Route [ Text
"prefs", Text
"blocked" ]
[ ]
Method
"GET"
friends :: Route
friends :: Route
friends = [Text] -> [URLParam] -> Method -> Route
Route [ Text
"prefs", Text
"friends" ]
[ ]
Method
"GET"
lookupUserFlair :: SubredditName -> Username -> Route
lookupUserFlair :: SubredditName -> Username -> Route
lookupUserFlair (R Text
r) Username
u =
[Text] -> [URLParam] -> Method -> Route
Route [ Text
"r", Text
r, Text
"api", Text
"flairlist" ]
[ Text
"name" Text -> Username -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Username
u ]
Method
"GET"
setUserFlair :: SubredditName -> Username -> Text -> Text -> Route
setUserFlair :: SubredditName -> Username -> Text -> Text -> Route
setUserFlair (R Text
r) Username
u Text
txt Text
cls =
[Text] -> [URLParam] -> Method -> Route
Route [ Text
"r", Text
r, Text
"api", Text
"flair" ]
[ Text
"name" Text -> Username -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Username
u
, Text
"text" Text -> Text -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Text
txt
, Text
"css_class" Text -> Text -> URLParam
forall a. ToQuery a => Text -> a -> URLParam
=. Text
cls ]
Method
"POST"