{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
module Web.Twitter.Conduit.Status (
StatusesMentionsTimeline,
mentionsTimeline,
StatusesUserTimeline,
userTimeline,
StatusesHomeTimeline,
homeTimeline,
StatusesRetweetsOfMe,
retweetsOfMe,
StatusesRetweetsId,
retweetsId,
StatusesShowId,
showId,
StatusesDestroyId,
destroyId,
StatusesUpdate,
update,
StatusesRetweetId,
retweetId,
MediaData (..),
StatusesUpdateWithMedia,
updateWithMedia,
StatusesLookup,
lookup,
) where
import Web.Twitter.Conduit.Base
import Web.Twitter.Conduit.Parameters
import Web.Twitter.Conduit.Request
import Web.Twitter.Conduit.Request.Internal
import Web.Twitter.Types
import Prelude hiding (lookup)
import Data.Default
import qualified Data.Text as T
import Network.HTTP.Client.MultipartFormData
mentionsTimeline :: APIRequest StatusesMentionsTimeline [Status]
mentionsTimeline :: APIRequest StatusesMentionsTimeline [Status]
mentionsTimeline = Method
-> String
-> APIQuery
-> APIRequest StatusesMentionsTimeline [Status]
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"GET" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/mentions_timeline.json") APIQuery
forall a. Default a => a
def
type StatusesMentionsTimeline =
'[ "count" ':= Integer
, "since_id" ':= Integer
, "max_id" ':= Integer
, "trim_user" ':= Bool
, "contributor_details" ':= Bool
, "include_entities" ':= Bool
, "tweet_mode" ':= TweetMode
]
userTimeline :: UserParam -> APIRequest StatusesUserTimeline [Status]
userTimeline :: UserParam -> APIRequest StatusesUserTimeline [Status]
userTimeline UserParam
q = Method
-> String -> APIQuery -> APIRequest StatusesUserTimeline [Status]
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"GET" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/user_timeline.json") (UserParam -> APIQuery
mkUserParam UserParam
q)
type StatusesUserTimeline =
'[ "count" ':= Integer
, "since_id" ':= Integer
, "max_id" ':= Integer
, "trim_user" ':= Bool
, "exclude_replies" ':= Bool
, "contributor_details" ':= Bool
, "include_rts" ':= Bool
, "tweet_mode" ':= TweetMode
]
homeTimeline :: APIRequest StatusesHomeTimeline [Status]
homeTimeline :: APIRequest StatusesHomeTimeline [Status]
homeTimeline = Method
-> String -> APIQuery -> APIRequest StatusesHomeTimeline [Status]
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"GET" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/home_timeline.json") APIQuery
forall a. Default a => a
def
type StatusesHomeTimeline =
'[ "count" ':= Integer
, "since_id" ':= Integer
, "max_id" ':= Integer
, "trim_user" ':= Bool
, "exclude_replies" ':= Bool
, "contributor_details" ':= Bool
, "include_entities" ':= Bool
, "tweet_mode" ':= TweetMode
]
retweetsOfMe :: APIRequest StatusesRetweetsOfMe [Status]
= Method
-> String -> APIQuery -> APIRequest StatusesRetweetsOfMe [Status]
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"GET" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/retweets_of_me.json") APIQuery
forall a. Default a => a
def
type =
'[ "count" ':= Integer
, "since_id" ':= Integer
, "max_id" ':= Integer
, "trim_user" ':= Bool
, "include_entities" ':= Bool
, "include_user_entities" ':= Bool
, "tweet_mode" ':= TweetMode
]
retweetsId :: StatusId -> APIRequest StatusesRetweetsId [RetweetedStatus]
StatusId
status_id = Method
-> String
-> APIQuery
-> APIRequest StatusesRetweetsId [RetweetedStatus]
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"GET" String
uri APIQuery
forall a. Default a => a
def
where
uri :: String
uri = String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/retweets/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ StatusId -> String
forall a. Show a => a -> String
show StatusId
status_id String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".json"
type =
'[ "count" ':= Integer
, "trim_user" ':= Bool
, "tweet_mode" ':= TweetMode
]
showId :: StatusId -> APIRequest StatusesShowId Status
showId :: StatusId -> APIRequest StatusesShowId Status
showId StatusId
status_id = Method -> String -> APIQuery -> APIRequest StatusesShowId Status
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"GET" String
uri APIQuery
forall a. Default a => a
def
where
uri :: String
uri = String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/show/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ StatusId -> String
forall a. Show a => a -> String
show StatusId
status_id String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".json"
type StatusesShowId =
'[ "trim_user" ':= Bool
, "include_my_retweet" ':= Bool
, "include_entities" ':= Bool
, "include_ext_alt_text" ':= Bool
, "tweet_mode" ':= TweetMode
]
destroyId :: StatusId -> APIRequest StatusesDestroyId Status
destroyId :: StatusId -> APIRequest StatusesDestroyId Status
destroyId StatusId
status_id = Method -> String -> APIQuery -> APIRequest StatusesDestroyId Status
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" String
uri APIQuery
forall a. Default a => a
def
where
uri :: String
uri = String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/destroy/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ StatusId -> String
forall a. Show a => a -> String
show StatusId
status_id String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".json"
type StatusesDestroyId =
'[ "trim_user" ':= Bool
, "tweet_mode" ':= TweetMode
]
update :: T.Text -> APIRequest StatusesUpdate Status
update :: Text -> APIRequest StatusesUpdate Status
update Text
status = Method -> String -> APIQuery -> APIRequest StatusesUpdate Status
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" String
uri [(Method
"status", Text -> PV
PVString Text
status)]
where
uri :: String
uri = String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/update.json"
type StatusesUpdate =
'[ "in_reply_to_status_id" ':= Integer
,
"display_coordinates" ':= Bool
, "trim_user" ':= Bool
, "media_ids" ':= [Integer]
, "tweet_mode" ':= TweetMode
]
retweetId :: StatusId -> APIRequest StatusesRetweetId RetweetedStatus
StatusId
status_id = Method
-> String
-> APIQuery
-> APIRequest StatusesDestroyId RetweetedStatus
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" String
uri APIQuery
forall a. Default a => a
def
where
uri :: String
uri = String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/retweet/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ StatusId -> String
forall a. Show a => a -> String
show StatusId
status_id String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".json"
type =
'[ "trim_user" ':= Bool
, "tweet_mode" ':= TweetMode
]
updateWithMedia ::
T.Text ->
MediaData ->
APIRequest StatusesUpdateWithMedia Status
updateWithMedia :: Text -> MediaData -> APIRequest StatusesUpdateWithMedia Status
updateWithMedia Text
tweet MediaData
mediaData =
Method
-> String
-> APIQuery
-> [Part]
-> APIRequest StatusesUpdateWithMedia Status
forall (supports :: [Param Symbol *]) responseType.
Method
-> String -> APIQuery -> [Part] -> APIRequest supports responseType
APIRequestMultipart Method
"POST" String
uri [(Method
"status", Text -> PV
PVString Text
tweet)] [MediaData -> Part
mediaBody MediaData
mediaData]
where
uri :: String
uri = String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/update_with_media.json"
mediaBody :: MediaData -> Part
mediaBody (MediaFromFile String
fp) = Text -> String -> Part
partFileSource Text
"media[]" String
fp
mediaBody (MediaRequestBody String
filename RequestBody
filebody) = Text -> String -> RequestBody -> Part
forall (m :: * -> *).
Applicative m =>
Text -> String -> RequestBody -> PartM m
partFileRequestBody Text
"media[]" String
filename RequestBody
filebody
type StatusesUpdateWithMedia =
'[ "possibly_sensitive" ':= Bool
, "in_reply_to_status_id" ':= Integer
,
"display_coordinates" ':= Bool
, "tweet_mode" ':= TweetMode
]
lookup :: [StatusId] -> APIRequest StatusesLookup [Status]
lookup :: [StatusId] -> APIRequest StatusesLookup [Status]
lookup [StatusId]
ids = Method -> String -> APIQuery -> APIRequest StatusesLookup [Status]
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"GET" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"statuses/lookup.json") [(Method
"id", [StatusId] -> PV
PVIntegerArray [StatusId]
ids)]
type StatusesLookup =
'[ "include_entities" ':= Bool
, "trim_user" ':= Bool
, "map" ':= Bool
, "tweet_mode" ':= TweetMode
]