{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}

module Web.Twitter.Conduit.Api
       (
       -- * Status
         statusesMentionsTimeline
       , statusesUserTimeline
       , statusesHomeTimeline
       , statusesRetweetsOfMe
       , statusesRetweetsId
       , statusesShowId
       , statusesDestroyId
       , statusesUpdate
       , statusesRetweetId
       , statusesUpdateWithMedia
       , statusesLookup

       -- * Search
       , SearchTweets
       , searchTweets
       , search

       -- * Direct Messages
       , DirectMessages
       , directMessages
       , DirectMessagesSent
       , directMessagesSent
       , DirectMessagesShow
       , directMessagesShow
       , DirectMessagesDestroy
       , directMessagesDestroy
       , DirectMessagesNew
       , directMessagesNew

       -- * Friends & Followers
       , FriendshipsNoRetweetsIds
       , friendshipsNoRetweetsIds
       , FriendsIds
       , friendsIds
       , FollowersIds
       , followersIds
       , FriendshipsIncoming
       , friendshipsIncoming
       , FriendshipsOutgoing
       , friendshipsOutgoing
       , FriendshipsCreate
       , friendshipsCreate
       , FriendshipsDestroy
       , friendshipsDestroy
       -- , friendshipsUpdate
       -- , friendshipsShow
       , FriendsList
       , friendsList
       , FollowersList
       , followersList
       -- , friendshipsLookup

       -- * Users
       -- , accountSettings
       , AccountVerifyCredentials
       , accountVerifyCredentials
       -- , accountSettingsUpdate
       -- , accountUpdateDeliveryDevice
       , AccountUpdateProfile
       , accountUpdateProfile
       -- , accountUpdateProfileBackgroundImage
       -- , accountUpdateProfileColors
       -- , accoutUpdateProfileImage
       -- , blocksList
       -- , blocksIds
       -- , blocksCreate
       -- , blocksDestroy

       , UsersLookup
       , usersLookup
       , UsersShow
       , usersShow
       -- , usersSearch
       -- , usersContributees
       -- , usersContributors
       -- , accuntRemoveProfileBanner
       -- , accuntUpdateProfileBanner
       -- , usersProfileBanner
       -- , mutesUsersCreate
       -- , mutesUsersDestroy
       -- , mutesUsersIds
       -- , mutesUsersList

       -- * Suggested Users
       -- , usersSuggestionsSlug
       -- , usersSuggestions
       -- , usersSuggestionsSlugMembers

       -- * Favorites
       , FavoritesList
       , favoritesList
       , FavoritesDestroy
       , favoritesDestroy
       , FavoritesCreate
       , favoritesCreate

       -- * Lists
       -- , listsList
       , ListsStatuses
       , listsStatuses
       , ListsMembersDestroy
       , listsMembersDestroy
       , ListsMemberships
       , listsMemberships
       , ListsSubscribers
       , listsSubscribers
       -- , listsSubscribersCreate
       -- , listsSubscribersShow
       -- , listsSubscribersDestroy
       , ListsMembersCreateAll
       , listsMembersCreateAll
       -- , listsMembersShow
       , ListsMembers
       , listsMembers
       , ListsMembersCreate
       , listsMembersCreate
       , ListsDestroy
       , listsDestroy
       , ListsUpdate
       , listsUpdate
       , ListsCreate
       , listsCreate
       , ListsShow
       , listsShow
       , ListsSubscriptions
       , listsSubscriptions
       , ListsMembersDestroyAll
       , listsMembersDestroyAll
       , ListsOwnerships
       , listsOwnerships

       -- * Saved Searches
       -- savedSearchesList
       -- savedSearchesShowId
       -- savedSearchesCreate
       -- savedSearchesDestroyId

       -- * Places & Geo
       -- geoIdPlaceId
       -- geoReverseGeocode
       -- geoSearch
       -- geoSimilarPlaces
       -- geoPlace

       -- * media
       , MediaUpload
       , mediaUpload
       ) where

import Web.Twitter.Conduit.Base
import Web.Twitter.Conduit.Cursor
import Web.Twitter.Conduit.Parameters
import Web.Twitter.Conduit.Request
import Web.Twitter.Conduit.Request.Internal
import qualified Web.Twitter.Conduit.Status as Status
import Web.Twitter.Types

import Network.HTTP.Client.MultipartFormData
import qualified Data.Text as T
import Data.Default
import Data.Time.Calendar (Day)
import Data.Aeson

-- $setup
-- >>> :set -XOverloadedStrings -XOverloadedLabels
-- >>> import Control.Lens

-- | Returns search query.
--
-- You can perform a search query using 'call':
--
-- @
-- res <- 'call' ('searchTweets' \"search text\")
-- 'print' $ res ^. 'searchResultStatuses'
-- @
--
-- >>> searchTweets "search text"
-- APIRequest "GET" "https://api.twitter.com/1.1/search/tweets.json" [("q","search text")]
-- >>> searchTweets "search text" & #lang ?~ "ja" & #count ?~ 100
-- APIRequest "GET" "https://api.twitter.com/1.1/search/tweets.json" [("count","100"),("lang","ja"),("q","search text")]
searchTweets :: T.Text -- ^ search string
             -> APIRequest SearchTweets (SearchResult [Status])
searchTweets :: Text -> APIRequest SearchTweets (SearchResult [Status])
searchTweets Text
q = Method
-> String
-> APIQuery
-> APIRequest SearchTweets (SearchResult [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
"search/tweets.json") [(Method
"q", Text -> PV
PVString Text
q)]
type SearchTweets = '[
      "lang" ':= T.Text
    , "locale" ':= T.Text
    , "result_type" ':= T.Text
    , "count" ':= Integer
    , "until" ':= Day
    , "since_id" ':= Integer
    , "max_id" ':= Integer
    , "include_entities" ':= Bool
    ]

-- | Alias of 'searchTweets', for backward compatibility
search :: T.Text -- ^ search string
       -> APIRequest SearchTweets (SearchResult [Status])
search :: Text -> APIRequest SearchTweets (SearchResult [Status])
search = Text -> APIRequest SearchTweets (SearchResult [Status])
searchTweets
{-# DEPRECATED search "Please use Web.Twitter.Conduit.searchTweets" #-}

-- | Returns query data which asks recent direct messages sent to the authenticating user.
--
-- You can perform a query using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'directMessages' '&' #count '?~' 50
-- @
--
-- >>> directMessages
-- APIRequest "GET" "https://api.twitter.com/1.1/direct_messages/events/list.json" []
-- >>> directMessages & #count ?~ 50
-- APIRequest "GET" "https://api.twitter.com/1.1/direct_messages/events/list.json" [("count","50")]
directMessages :: APIRequest DirectMessages (WithCursor T.Text EventsCursorKey DirectMessage)
directMessages :: APIRequest
  DirectMessages (WithCursor Text EventsCursorKey DirectMessage)
directMessages = Method
-> String
-> APIQuery
-> APIRequest
     DirectMessages (WithCursor Text EventsCursorKey DirectMessage)
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
"direct_messages/events/list.json") APIQuery
forall a. Default a => a
def
type DirectMessages = '[
      "count" ':= Integer
    , "include_entities" ':= Bool
    , "skip_status" ':= Bool
    , "full_text" ':= Bool
    , "cursor" ':= T.Text
    ]

-- | Returns query data which asks recent direct messages sent by the authenticating user.
--
-- You can perform a query using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'directMessagesSent' '&' #count '?~' 100
-- @
--
-- >>> directMessagesSent
-- APIRequest "GET" "https://api.twitter.com/1.1/direct_messages/sent.json" []
-- >>> directMessagesSent & #count ?~ 100
-- APIRequest "GET" "https://api.twitter.com/1.1/direct_messages/sent.json" [("count","100")]
directMessagesSent :: APIRequest DirectMessagesSent [DirectMessage]
directMessagesSent :: APIRequest DirectMessagesSent [DirectMessage]
directMessagesSent = Method
-> String
-> APIQuery
-> APIRequest DirectMessagesSent [DirectMessage]
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
"direct_messages/sent.json") APIQuery
forall a. Default a => a
def
type DirectMessagesSent = '[
      "since_id" ':= Integer
    , "max_id" ':= Integer
    , "count" ':= Integer
    , "include_entities" ':= Bool
    , "page" ':= Integer
    , "skip_status" ':= Bool
    , "full_text" ':= Bool
    ]

-- | Returns query data which asks a single direct message, specified by an id parameter.
--
-- You can perform a query using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'directMessagesShow' 1234567890
-- @
--
-- >>> directMessagesShow 1234567890
-- APIRequest "GET" "https://api.twitter.com/1.1/direct_messages/show.json" [("id","1234567890")]
directMessagesShow :: StatusId -> APIRequest DirectMessagesShow DirectMessage
directMessagesShow :: StatusId -> APIRequest DirectMessagesShow DirectMessage
directMessagesShow StatusId
sId = Method
-> String
-> APIQuery
-> APIRequest DirectMessagesShow DirectMessage
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
"direct_messages/show.json") [(Method
"id", StatusId -> PV
PVInteger StatusId
sId)]
type DirectMessagesShow = '[
      "full_text" ':= Bool
    ]

-- | Returns post data which destroys the direct message specified in the required ID parameter.
--
-- You can perform a query using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'directMessagesDestroy' 1234567890
-- @
--
-- >>> directMessagesDestroy 1234567890
-- APIRequest "DELETE" "https://api.twitter.com/1.1/direct_messages/events/destroy.json" [("id","1234567890")]
directMessagesDestroy :: StatusId -> APIRequest DirectMessagesDestroy NoContent
directMessagesDestroy :: StatusId -> APIRequest DirectMessagesDestroy NoContent
directMessagesDestroy StatusId
sId = Method
-> String -> APIQuery -> APIRequest DirectMessagesDestroy NoContent
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"DELETE" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"direct_messages/events/destroy.json") [(Method
"id", StatusId -> PV
PVInteger StatusId
sId)]
type DirectMessagesDestroy = EmptyParams

newtype DirectMessagesNewResponse = DirectMessagesNewResponse
    { DirectMessagesNewResponse -> DirectMessage
directMessageBody :: DirectMessage
    } deriving (Int -> DirectMessagesNewResponse -> String -> String
[DirectMessagesNewResponse] -> String -> String
DirectMessagesNewResponse -> String
(Int -> DirectMessagesNewResponse -> String -> String)
-> (DirectMessagesNewResponse -> String)
-> ([DirectMessagesNewResponse] -> String -> String)
-> Show DirectMessagesNewResponse
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DirectMessagesNewResponse] -> String -> String
$cshowList :: [DirectMessagesNewResponse] -> String -> String
show :: DirectMessagesNewResponse -> String
$cshow :: DirectMessagesNewResponse -> String
showsPrec :: Int -> DirectMessagesNewResponse -> String -> String
$cshowsPrec :: Int -> DirectMessagesNewResponse -> String -> String
Show, DirectMessagesNewResponse -> DirectMessagesNewResponse -> Bool
(DirectMessagesNewResponse -> DirectMessagesNewResponse -> Bool)
-> (DirectMessagesNewResponse -> DirectMessagesNewResponse -> Bool)
-> Eq DirectMessagesNewResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DirectMessagesNewResponse -> DirectMessagesNewResponse -> Bool
$c/= :: DirectMessagesNewResponse -> DirectMessagesNewResponse -> Bool
== :: DirectMessagesNewResponse -> DirectMessagesNewResponse -> Bool
$c== :: DirectMessagesNewResponse -> DirectMessagesNewResponse -> Bool
Eq)

instance FromJSON DirectMessagesNewResponse where
    parseJSON :: Value -> Parser DirectMessagesNewResponse
parseJSON = String
-> (Object -> Parser DirectMessagesNewResponse)
-> Value
-> Parser DirectMessagesNewResponse
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"DirectMessagesNewResponse" ((Object -> Parser DirectMessagesNewResponse)
 -> Value -> Parser DirectMessagesNewResponse)
-> (Object -> Parser DirectMessagesNewResponse)
-> Value
-> Parser DirectMessagesNewResponse
forall a b. (a -> b) -> a -> b
$ \Object
o -> DirectMessage -> DirectMessagesNewResponse
DirectMessagesNewResponse (DirectMessage -> DirectMessagesNewResponse)
-> Parser DirectMessage -> Parser DirectMessagesNewResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser DirectMessage
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"event"

-- | Returns post data which sends a new direct message to the specified user from the authenticating user.
--
-- You can perform a post using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'directMessagesNew' (ScreenNameParam \"thimura\") \"Hello DM\"
-- @
--
-- >>> directMessagesNew 69179963 "Hello thimura! by UserId"
-- APIRequestJSON "POST" "https://api.twitter.com/1.1/direct_messages/events/new.json" []
directMessagesNew :: RecipientId -> T.Text -> APIRequest DirectMessagesNew DirectMessagesNewResponse
directMessagesNew :: StatusId
-> Text
-> APIRequest DirectMessagesDestroy DirectMessagesNewResponse
directMessagesNew StatusId
up Text
msg =
    Method
-> String
-> APIQuery
-> Value
-> APIRequest DirectMessagesDestroy DirectMessagesNewResponse
forall (supports :: [Param Symbol *]) responseType.
Method
-> String -> APIQuery -> Value -> APIRequest supports responseType
APIRequestJSON Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"direct_messages/events/new.json") [] Value
body
  where
    body :: Value
body =
        [Pair] -> Value
object
            [ Text
"event" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=
              [Pair] -> Value
object
                  [ Text
"type" Text -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= (String
"message_create" :: String)
                  , Text
"message_create" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.=
                    [Pair] -> Value
object
                        [ Text
"target" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Pair] -> Value
object [Text
"recipient_id" Text -> StatusId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= StatusId
up]
                        , Text
"message_data" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Pair] -> Value
object [Text
"text" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
msg]
                        ]
                  ]
            ]
type DirectMessagesNew = EmptyParams

type RecipientId = Integer

-- | Returns a collection of user_ids that the currently authenticated user does not want to receive retweets from.
--
-- You can perform a request using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'friendshipsNoRetweetsIds'
-- @
--
-- >>> friendshipsNoRetweetsIds
-- APIRequest "GET" "https://api.twitter.com/1.1/friendships/no_retweets/ids.json" []
friendshipsNoRetweetsIds :: APIRequest FriendshipsNoRetweetsIds [UserId]
friendshipsNoRetweetsIds :: APIRequest DirectMessagesDestroy [StatusId]
friendshipsNoRetweetsIds = Method
-> String
-> APIQuery
-> APIRequest DirectMessagesDestroy [StatusId]
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
"friendships/no_retweets/ids.json") []
type FriendshipsNoRetweetsIds = EmptyParams

-- | Returns query data which asks a collection of user IDs for every user the specified user is following.
--
-- You can perform a query using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'friendsIds' ('ScreenNameParam' \"thimura\")
-- @
--
-- Or, you can iterate with 'sourceWithCursor':
--
-- @
-- 'sourceWithCursor' ('friendsIds' ('ScreenNameParam' \"thimura\")) $$ CL.consume
-- @
--
-- >>> friendsIds (ScreenNameParam "thimura")
-- APIRequest "GET" "https://api.twitter.com/1.1/friends/ids.json" [("screen_name","thimura")]
-- >>> friendsIds (ScreenNameParam "thimura") & #count ?~ 5000
-- APIRequest "GET" "https://api.twitter.com/1.1/friends/ids.json" [("count","5000"),("screen_name","thimura")]
friendsIds :: UserParam -> APIRequest FriendsIds (WithCursor Integer IdsCursorKey UserId)
friendsIds :: UserParam
-> APIRequest
     FriendsIds (WithCursor StatusId IdsCursorKey StatusId)
friendsIds UserParam
q = Method
-> String
-> APIQuery
-> APIRequest
     FriendsIds (WithCursor StatusId IdsCursorKey StatusId)
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
"friends/ids.json") (UserParam -> APIQuery
mkUserParam UserParam
q)
type FriendsIds = '[
      "count" ':= Integer
    , "cursor" ':= Integer
    ]

-- | Returns query data which asks a collection of user IDs for every user following the specified user.
--
-- You can perform a query using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'followersIds' ('ScreenNameParam' \"thimura\")
-- @
--
-- Or, you can iterate with 'sourceWithCursor':
--
-- @
-- 'sourceWithCursor' ('followersIds' ('ScreenNameParam' \"thimura\")) $$ CL.consume
-- @
--
-- >>> followersIds (ScreenNameParam "thimura")
-- APIRequest "GET" "https://api.twitter.com/1.1/followers/ids.json" [("screen_name","thimura")]
-- >>> followersIds (ScreenNameParam "thimura") & #count ?~ 5000
-- APIRequest "GET" "https://api.twitter.com/1.1/followers/ids.json" [("count","5000"),("screen_name","thimura")]
followersIds :: UserParam -> APIRequest FollowersIds (WithCursor Integer IdsCursorKey UserId)
followersIds :: UserParam
-> APIRequest
     FriendsIds (WithCursor StatusId IdsCursorKey StatusId)
followersIds UserParam
q = Method
-> String
-> APIQuery
-> APIRequest
     FriendsIds (WithCursor StatusId IdsCursorKey StatusId)
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
"followers/ids.json") (UserParam -> APIQuery
mkUserParam UserParam
q)
type FollowersIds = '[
      "count" ':= Integer
    , "cursor" ':= Integer
    ]

-- | Returns a collection of numeric IDs for every user who has a pending request to follow the authenticating user.
--
-- You can perform a request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'friendshipsIncoming'
-- @
--
-- Or, you can iterate with 'sourceWithCursor':
--
-- @
-- 'sourceWithCursor' 'friendshipsIncoming' $$ CL.consume
-- @
--
-- >>> friendshipsIncoming
-- APIRequest "GET" "https://api.twitter.com/1.1/friendships/incoming.json" []
friendshipsIncoming :: APIRequest FriendshipsIncoming (WithCursor Integer IdsCursorKey UserId)
friendshipsIncoming :: APIRequest
  FriendshipsIncoming (WithCursor StatusId IdsCursorKey StatusId)
friendshipsIncoming = Method
-> String
-> APIQuery
-> APIRequest
     FriendshipsIncoming (WithCursor StatusId IdsCursorKey StatusId)
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
"friendships/incoming.json") APIQuery
forall a. Default a => a
def
type FriendshipsIncoming = '[
      "cursor" ':= Integer
    ]

-- | Returns a collection of numeric IDs for every protected user for whom the authenticating user has a pending follow request.
--
-- You can perform a request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'friendshipsOutgoing'
-- @
--
-- Or, you can iterate with 'sourceWithCursor':
--
-- @
-- 'sourceWithCursor' 'friendshipsOutgoing' $$ CL.consume
-- @
--
-- >>> friendshipsOutgoing
-- APIRequest "GET" "https://api.twitter.com/1.1/friendships/outgoing.json" []
friendshipsOutgoing :: APIRequest FriendshipsOutgoing (WithCursor Integer IdsCursorKey UserId)
friendshipsOutgoing :: APIRequest
  FriendshipsIncoming (WithCursor StatusId IdsCursorKey StatusId)
friendshipsOutgoing = Method
-> String
-> APIQuery
-> APIRequest
     FriendshipsIncoming (WithCursor StatusId IdsCursorKey StatusId)
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
"friendships/outgoing.json") APIQuery
forall a. Default a => a
def
type FriendshipsOutgoing = '[
      "cursor" ':= Integer
    ]

-- | Returns post data which follows the user specified in the ID parameter.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'friendshipsCreate' ('ScreenNameParam' \"thimura\")
-- @
--
-- >>> friendshipsCreate (ScreenNameParam "thimura")
-- APIRequest "POST" "https://api.twitter.com/1.1/friendships/create.json" [("screen_name","thimura")]
-- >>> friendshipsCreate (UserIdParam 69179963)
-- APIRequest "POST" "https://api.twitter.com/1.1/friendships/create.json" [("user_id","69179963")]
friendshipsCreate :: UserParam -> APIRequest FriendshipsCreate User
friendshipsCreate :: UserParam -> APIRequest FriendshipsCreate User
friendshipsCreate UserParam
user = Method -> String -> APIQuery -> APIRequest FriendshipsCreate User
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"friendships/create.json") (UserParam -> APIQuery
mkUserParam UserParam
user)
type FriendshipsCreate = '[
      "follow" ':= Bool
    ]

-- | Returns post data which unfollows the user specified in the ID parameter.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'friendshipsDestroy' ('ScreenNameParam' \"thimura\")
-- @
--
-- >>> friendshipsDestroy (ScreenNameParam "thimura")
-- APIRequest "POST" "https://api.twitter.com/1.1/friendships/destroy.json" [("screen_name","thimura")]
-- >>> friendshipsDestroy (UserIdParam 69179963)
-- APIRequest "POST" "https://api.twitter.com/1.1/friendships/destroy.json" [("user_id","69179963")]
friendshipsDestroy :: UserParam -> APIRequest FriendshipsDestroy User
friendshipsDestroy :: UserParam -> APIRequest DirectMessagesDestroy User
friendshipsDestroy UserParam
user = Method
-> String -> APIQuery -> APIRequest DirectMessagesDestroy User
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"friendships/destroy.json") (UserParam -> APIQuery
mkUserParam UserParam
user)
type FriendshipsDestroy = EmptyParams

-- | Returns query data which asks a cursored collection of user objects for every user the specified users is following.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'friendsList' ('ScreenNameParam' \"thimura\")
-- @
--
-- Or, you can iterate with 'sourceWithCursor':
--
-- @
-- 'sourceWithCursor' ('friendsList' ('ScreenNameParam' \"thimura\")) $$ CL.consume
-- @
--
-- >>> friendsList (ScreenNameParam "thimura")
-- APIRequest "GET" "https://api.twitter.com/1.1/friends/list.json" [("screen_name","thimura")]
-- >>> friendsList (UserIdParam 69179963)
-- APIRequest "GET" "https://api.twitter.com/1.1/friends/list.json" [("user_id","69179963")]
friendsList :: UserParam -> APIRequest FriendsList (WithCursor Integer UsersCursorKey User)
friendsList :: UserParam
-> APIRequest FriendsList (WithCursor StatusId UsersCursorKey User)
friendsList UserParam
q = Method
-> String
-> APIQuery
-> APIRequest FriendsList (WithCursor StatusId UsersCursorKey User)
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
"friends/list.json") (UserParam -> APIQuery
mkUserParam UserParam
q)
type FriendsList = '[
      "count" ':= Integer
    , "cursor" ':= Integer
    , "skip_status" ':= Bool
    , "include_user_entities" ':= Bool
    ]

-- | Returns query data which asks a cursored collection of user objects for users following the specified user.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'followersList' ('ScreenNameParam' \"thimura\")
-- @
--
-- Or, you can iterate with 'sourceWithCursor':
--
-- @
-- 'sourceWithCursor' ('followersList' ('ScreenNameParam' \"thimura\")) $$ CL.consume
-- @
--
-- >>> followersList (ScreenNameParam "thimura")
-- APIRequest "GET" "https://api.twitter.com/1.1/followers/list.json" [("screen_name","thimura")]
-- >>> followersList (UserIdParam 69179963)
-- APIRequest "GET" "https://api.twitter.com/1.1/followers/list.json" [("user_id","69179963")]
followersList :: UserParam -> APIRequest FollowersList (WithCursor Integer UsersCursorKey User)
followersList :: UserParam
-> APIRequest FriendsList (WithCursor StatusId UsersCursorKey User)
followersList UserParam
q = Method
-> String
-> APIQuery
-> APIRequest FriendsList (WithCursor StatusId UsersCursorKey User)
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
"followers/list.json") (UserParam -> APIQuery
mkUserParam UserParam
q)
type FollowersList = '[
      "count" ':= Integer
    , "cursor" ':= Integer
    , "skip_status" ':= Bool
    , "include_user_entities" ':= Bool
    ]

-- | Returns query data asks that the credential is valid.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'accountVerifyCredentials'
-- @
--
-- >>> accountVerifyCredentials
-- APIRequest "GET" "https://api.twitter.com/1.1/account/verify_credentials.json" []
accountVerifyCredentials :: APIRequest AccountVerifyCredentials User
accountVerifyCredentials :: APIRequest AccountVerifyCredentials User
accountVerifyCredentials = Method
-> String -> APIQuery -> APIRequest AccountVerifyCredentials User
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
"account/verify_credentials.json") []
type AccountVerifyCredentials = '[
      "include_entities" ':= Bool
    , "skip_status" ':= Bool
    , "include_email" ':= Bool
    ]

-- | Returns user object with updated fields.
-- Note that while no specific parameter is required, you need to provide at least one parameter before executing the query.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'accountUpdateProfile' & #url ?~ \"http://www.example.com\"
-- @
--
-- >>> accountUpdateProfile & #url ?~ "http://www.example.com"
-- APIRequest "POST" "https://api.twitter.com/1.1/account/update_profile.json" [("url","http://www.example.com")]
accountUpdateProfile :: APIRequest AccountUpdateProfile User
accountUpdateProfile :: APIRequest AccountUpdateProfile User
accountUpdateProfile = Method
-> String -> APIQuery -> APIRequest AccountUpdateProfile User
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"account/update_profile.json") []
type AccountUpdateProfile = '[
      "include_entities" ':= Bool
    , "skip_status" ':= Bool
    , "name" ':= T.Text
    , "url" ':= URIString
    , "location" ':= T.Text
    , "description" ':= T.Text
    , "profile_link_color" ':= T.Text
    ]

-- | Returns query data asks user objects.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'usersLookup' ('ScreenNameListParam' [\"thimura\", \"twitterapi\"])
-- @
--
-- >>> usersLookup (ScreenNameListParam ["thimura", "twitterapi"])
-- APIRequest "GET" "https://api.twitter.com/1.1/users/lookup.json" [("screen_name","thimura,twitterapi")]
usersLookup :: UserListParam -> APIRequest UsersLookup [User]
usersLookup :: UserListParam -> APIRequest UsersLookup [User]
usersLookup UserListParam
q = Method -> String -> APIQuery -> APIRequest UsersLookup [User]
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
"users/lookup.json") (UserListParam -> APIQuery
mkUserListParam UserListParam
q)
type UsersLookup = '[
      "include_entities" ':= Bool
    ]

-- | Returns query data asks the user specified by user id or screen name parameter.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'usersShow' ('ScreenNameParam' \"thimura\")
-- @
--
-- >>> usersShow (ScreenNameParam "thimura")
-- APIRequest "GET" "https://api.twitter.com/1.1/users/show.json" [("screen_name","thimura")]
usersShow :: UserParam -> APIRequest UsersShow User
usersShow :: UserParam -> APIRequest UsersLookup User
usersShow UserParam
q = Method -> String -> APIQuery -> APIRequest UsersLookup User
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
"users/show.json") (UserParam -> APIQuery
mkUserParam UserParam
q)
type UsersShow = '[
      "include_entities" ':= Bool
    ]

-- | Returns the 20 most recent Tweets favorited by the specified user.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'favoritesList' (ScreenNameParam \"thimura\")
-- @
--
-- >>> favoritesList Nothing
-- APIRequest "GET" "https://api.twitter.com/1.1/favorites/list.json" []
-- >>> favoritesList (Just (ScreenNameParam "thimura"))
-- APIRequest "GET" "https://api.twitter.com/1.1/favorites/list.json" [("screen_name","thimura")]
-- >>> favoritesList (Just (UserIdParam 69179963))
-- APIRequest "GET" "https://api.twitter.com/1.1/favorites/list.json" [("user_id","69179963")]
favoritesList :: Maybe UserParam -> APIRequest FavoritesList [Status]
favoritesList :: Maybe UserParam -> APIRequest FavoritesList [Status]
favoritesList Maybe UserParam
mbuser = Method -> String -> APIQuery -> APIRequest FavoritesList [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
"favorites/list.json") (Maybe UserParam -> APIQuery
mkParam Maybe UserParam
mbuser)
  where
    mkParam :: Maybe UserParam -> APIQuery
mkParam Maybe UserParam
Nothing = []
    mkParam (Just UserParam
usr) = UserParam -> APIQuery
mkUserParam UserParam
usr
type FavoritesList = '[
      "count" ':= Integer
    , "since_id" ':= Integer
    , "max_id" ':= Integer
    , "include_entities" ':= Bool
    ]

-- | Returns post data which favorites the status specified in the ID parameter as the authenticating user.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'favoritesCreate' 1234567890
-- @
--
-- >>> favoritesCreate 1234567890
-- APIRequest "POST" "https://api.twitter.com/1.1/favorites/create.json" [("id","1234567890")]
favoritesCreate :: StatusId -> APIRequest FavoritesCreate Status
favoritesCreate :: StatusId -> APIRequest UsersLookup Status
favoritesCreate StatusId
sid = Method -> String -> APIQuery -> APIRequest UsersLookup Status
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"favorites/create.json") [(Method
"id", StatusId -> PV
PVInteger StatusId
sid)]
type FavoritesCreate = '[
      "include_entities" ':= Bool
    ]

-- | Returns post data unfavorites the status specified in the ID paramter as the authenticating user.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'favoritesDestroy' 1234567890
-- @
--
-- >>> favoritesDestroy 1234567890
-- APIRequest "POST" "https://api.twitter.com/1.1/favorites/destroy.json" [("id","1234567890")]
favoritesDestroy :: StatusId -> APIRequest FavoritesDestroy Status
favoritesDestroy :: StatusId -> APIRequest UsersLookup Status
favoritesDestroy StatusId
sid = Method -> String -> APIQuery -> APIRequest UsersLookup Status
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"favorites/destroy.json") [(Method
"id", StatusId -> PV
PVInteger StatusId
sid)]
type FavoritesDestroy = '[
      "include_entities" ':= Bool
    ]

-- | Returns the query parameter which fetches a timeline of tweets authored by members of the specified list.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsStatuses' ('ListNameParam' "thimura/haskell")
-- @
--
-- If you need more statuses, you can obtain those by using 'sourceWithMaxId':
-- @
-- res <- sourceWithMaxId ('listsStatuses' ('ListNameParam' "thimura/haskell") & #count ?~ 200) $$ CL.take 1000
-- @
--
-- >>> listsStatuses (ListNameParam "thimura/haskell")
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/statuses.json" [("slug","haskell"),("owner_screen_name","thimura")]
-- >>> listsStatuses (ListIdParam 20849097)
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/statuses.json" [("list_id","20849097")]
listsStatuses :: ListParam -> APIRequest ListsStatuses [Status]
listsStatuses :: ListParam -> APIRequest ListsStatuses [Status]
listsStatuses ListParam
q = Method -> String -> APIQuery -> APIRequest ListsStatuses [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
"lists/statuses.json") (ListParam -> APIQuery
mkListParam ListParam
q)
type ListsStatuses = '[
      "since_id" ':= Integer
    , "max_id" ':= Integer
    , "count" ':= Integer
    , "include_entities" ':= Bool
    , "include_rts" ':= Bool
    ]

-- | Returns the post parameter which removes the specified member from the list.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsMembersDestroy' ('ListNameParam' "thimura/haskell") ('ScreenNameParam' "thimura")
-- @
--
-- >>> listsMembersDestroy (ListNameParam "thimura/haskell") (ScreenNameParam "thimura")
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/members/destroy.json" [("slug","haskell"),("owner_screen_name","thimura"),("screen_name","thimura")]
-- >>> listsMembersDestroy (ListIdParam 20849097) (UserIdParam 69179963)
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/members/destroy.json" [("list_id","20849097"),("user_id","69179963")]
listsMembersDestroy :: ListParam -> UserParam -> APIRequest ListsMembersDestroy List
listsMembersDestroy :: ListParam -> UserParam -> APIRequest DirectMessagesDestroy List
listsMembersDestroy ListParam
list UserParam
user = Method
-> String -> APIQuery -> APIRequest DirectMessagesDestroy List
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"lists/members/destroy.json") (ListParam -> APIQuery
mkListParam ListParam
list APIQuery -> APIQuery -> APIQuery
forall a. [a] -> [a] -> [a]
++ UserParam -> APIQuery
mkUserParam UserParam
user)
type ListsMembersDestroy = EmptyParams

-- | Returns the request parameters which asks the lists the specified user has been added to.
-- If 'UserParam' are not provided, the memberships for the authenticating user are returned.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsMemberships' ('ListNameParam' "thimura/haskell")
-- @
--
-- >>> listsMemberships Nothing
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/memberships.json" []
-- >>> listsMemberships (Just (ScreenNameParam "thimura"))
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/memberships.json" [("screen_name","thimura")]
-- >>> listsMemberships (Just (UserIdParam 69179963))
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/memberships.json" [("user_id","69179963")]
listsMemberships :: Maybe UserParam -> APIRequest ListsMemberships (WithCursor Integer ListsCursorKey List)
listsMemberships :: Maybe UserParam
-> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List)
listsMemberships Maybe UserParam
q = Method
-> String
-> APIQuery
-> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List)
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
"lists/memberships.json") (APIQuery
 -> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List))
-> APIQuery
-> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List)
forall a b. (a -> b) -> a -> b
$ APIQuery -> (UserParam -> APIQuery) -> Maybe UserParam -> APIQuery
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] UserParam -> APIQuery
mkUserParam Maybe UserParam
q
type ListsMemberships = '[
      "count" ':= Integer
    , "cursor" ':= Integer
    ]

-- | Returns the request parameter which asks the subscribers of the specified list.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsSubscribers' ('ListNameParam' "thimura/haskell")
-- @
--
-- >>> listsSubscribers (ListNameParam "thimura/haskell")
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/subscribers.json" [("slug","haskell"),("owner_screen_name","thimura")]
-- >>> listsSubscribers (ListIdParam 20849097)
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/subscribers.json" [("list_id","20849097")]
listsSubscribers :: ListParam -> APIRequest ListsSubscribers (WithCursor Integer UsersCursorKey User)
listsSubscribers :: ListParam
-> APIRequest
     ListsSubscribers (WithCursor StatusId UsersCursorKey User)
listsSubscribers ListParam
q = Method
-> String
-> APIQuery
-> APIRequest
     ListsSubscribers (WithCursor StatusId UsersCursorKey User)
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
"lists/subscribers.json") (ListParam -> APIQuery
mkListParam ListParam
q)
type ListsSubscribers = '[
      "count" ':= Integer
    , "cursor" ':= Integer
    , "skip_status" ':= Bool
    ]

-- | Returns the request parameter which obtains a collection of the lists the specified user is subscribed to.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsSubscriptions' ('ListNameParam' "thimura/haskell")
-- @
--
-- >>> listsSubscriptions Nothing
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/subscriptions.json" []
-- >>> listsSubscriptions (Just (ScreenNameParam "thimura"))
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/subscriptions.json" [("screen_name","thimura")]
-- >>> listsSubscriptions (Just (UserIdParam 69179963))
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/subscriptions.json" [("user_id","69179963")]
listsSubscriptions :: Maybe UserParam -> APIRequest ListsSubscriptions (WithCursor Integer ListsCursorKey List)
listsSubscriptions :: Maybe UserParam
-> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List)
listsSubscriptions Maybe UserParam
q = Method
-> String
-> APIQuery
-> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List)
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
"lists/subscriptions.json") (APIQuery
 -> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List))
-> APIQuery
-> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List)
forall a b. (a -> b) -> a -> b
$ APIQuery -> (UserParam -> APIQuery) -> Maybe UserParam -> APIQuery
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] UserParam -> APIQuery
mkUserParam Maybe UserParam
q
type ListsSubscriptions = '[
      "count" ':= Integer
    , "cursor" ':= Integer
    ]

-- | Returns the request parameter which asks the lists owned by the specified Twitter user.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsOwnerships' ('ListNameParam' "thimura/haskell")
-- @
--
-- >>> listsOwnerships Nothing
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/ownerships.json" []
-- >>> listsOwnerships (Just (ScreenNameParam "thimura"))
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/ownerships.json" [("screen_name","thimura")]
-- >>> listsOwnerships (Just (UserIdParam 69179963))
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/ownerships.json" [("user_id","69179963")]
listsOwnerships :: Maybe UserParam -> APIRequest ListsOwnerships (WithCursor Integer ListsCursorKey List)
listsOwnerships :: Maybe UserParam
-> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List)
listsOwnerships Maybe UserParam
q = Method
-> String
-> APIQuery
-> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List)
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
"lists/ownerships.json") (APIQuery
 -> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List))
-> APIQuery
-> APIRequest FriendsIds (WithCursor StatusId ListsCursorKey List)
forall a b. (a -> b) -> a -> b
$ APIQuery -> (UserParam -> APIQuery) -> Maybe UserParam -> APIQuery
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] UserParam -> APIQuery
mkUserParam Maybe UserParam
q
type ListsOwnerships = '[
      "count" ':= Integer
    , "cursor" ':= Integer
    ]

-- | Adds multiple members to a list.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsMembersCreateAll' ('ListNameParam' "thimura/haskell") ('ScreenNameListParam' [\"thimura\", \"twitterapi\"])
-- @
--
-- >>> listsMembersCreateAll (ListNameParam "thimura/haskell") (ScreenNameListParam ["thimura", "twitterapi"])
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/members/create_all.json" [("slug","haskell"),("owner_screen_name","thimura"),("screen_name","thimura,twitterapi")]
-- >>> listsMembersCreateAll (ListIdParam 20849097) (UserIdListParam [69179963, 6253282])
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/members/create_all.json" [("list_id","20849097"),("user_id","69179963,6253282")]
listsMembersCreateAll :: ListParam -> UserListParam -> APIRequest ListsMembersCreateAll List
listsMembersCreateAll :: ListParam -> UserListParam -> APIRequest DirectMessagesDestroy List
listsMembersCreateAll ListParam
list UserListParam
users = Method
-> String -> APIQuery -> APIRequest DirectMessagesDestroy List
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"lists/members/create_all.json") (ListParam -> APIQuery
mkListParam ListParam
list APIQuery -> APIQuery -> APIQuery
forall a. [a] -> [a] -> [a]
++ UserListParam -> APIQuery
mkUserListParam UserListParam
users)
type ListsMembersCreateAll = EmptyParams

-- | Adds multiple members to a list.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsMembersDestroyAll' ('ListNameParam' "thimura/haskell") ('ScreenNameListParam' [\"thimura\", \"twitterapi\"])
-- @
--
-- >>> listsMembersDestroyAll (ListNameParam "thimura/haskell") (ScreenNameListParam ["thimura", "twitterapi"])
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/members/destroy_all.json" [("slug","haskell"),("owner_screen_name","thimura"),("screen_name","thimura,twitterapi")]
-- >>> listsMembersDestroyAll (ListIdParam 20849097) (UserIdListParam [69179963, 6253282])
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/members/destroy_all.json" [("list_id","20849097"),("user_id","69179963,6253282")]
listsMembersDestroyAll :: ListParam -> UserListParam -> APIRequest ListsMembersDestroyAll List
listsMembersDestroyAll :: ListParam -> UserListParam -> APIRequest DirectMessagesDestroy List
listsMembersDestroyAll ListParam
list UserListParam
users = Method
-> String -> APIQuery -> APIRequest DirectMessagesDestroy List
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"lists/members/destroy_all.json") (ListParam -> APIQuery
mkListParam ListParam
list APIQuery -> APIQuery -> APIQuery
forall a. [a] -> [a] -> [a]
++ UserListParam -> APIQuery
mkUserListParam UserListParam
users)
type ListsMembersDestroyAll = EmptyParams

-- | Returns query data asks the members of the specified list.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsMembers' ('ListNameParam' "thimura/haskell")
-- @
--
-- >>> listsMembers (ListNameParam "thimura/haskell")
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/members.json" [("slug","haskell"),("owner_screen_name","thimura")]
-- >>> listsMembers (ListIdParam 20849097)
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/members.json" [("list_id","20849097")]
listsMembers :: ListParam -> APIRequest ListsMembers (WithCursor Integer UsersCursorKey User)
listsMembers :: ListParam
-> APIRequest
     ListsSubscribers (WithCursor StatusId UsersCursorKey User)
listsMembers ListParam
q = Method
-> String
-> APIQuery
-> APIRequest
     ListsSubscribers (WithCursor StatusId UsersCursorKey User)
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
"lists/members.json") (ListParam -> APIQuery
mkListParam ListParam
q)
type ListsMembers = '[
      "count" ':= Integer
    , "cursor" ':= Integer
    , "skip_status" ':= Bool
    ]

-- | Returns the post parameter which adds a member to a list.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsMembersCreate' ('ListNameParam' "thimura/haskell") ('ScreenNameParam' "thimura")
-- @
--
-- >>> listsMembersCreate (ListNameParam "thimura/haskell") (ScreenNameParam "thimura")
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/members/create.json" [("slug","haskell"),("owner_screen_name","thimura"),("screen_name","thimura")]
-- >>> listsMembersCreate (ListIdParam 20849097) (UserIdParam 69179963)
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/members/create.json" [("list_id","20849097"),("user_id","69179963")]
listsMembersCreate :: ListParam -> UserParam -> APIRequest ListsMembersCreate List
listsMembersCreate :: ListParam -> UserParam -> APIRequest DirectMessagesDestroy List
listsMembersCreate ListParam
list UserParam
user = Method
-> String -> APIQuery -> APIRequest DirectMessagesDestroy List
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"lists/members/create.json") (ListParam -> APIQuery
mkListParam ListParam
list APIQuery -> APIQuery -> APIQuery
forall a. [a] -> [a] -> [a]
++ UserParam -> APIQuery
mkUserParam UserParam
user)
type ListsMembersCreate = EmptyParams

-- | Returns the post parameter which deletes the specified list.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsDestroy' ('ListNameParam' "thimura/haskell")
-- @
--
-- >>> listsDestroy (ListNameParam "thimura/haskell")
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/destroy.json" [("slug","haskell"),("owner_screen_name","thimura")]
-- >>> listsDestroy (ListIdParam 20849097)
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/destroy.json" [("list_id","20849097")]
listsDestroy :: ListParam -> APIRequest ListsDestroy List
listsDestroy :: ListParam -> APIRequest DirectMessagesDestroy List
listsDestroy ListParam
list = Method
-> String -> APIQuery -> APIRequest DirectMessagesDestroy List
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"lists/destroy.json") (ListParam -> APIQuery
mkListParam ListParam
list)
type ListsDestroy = EmptyParams

-- | Returns the post parameter which updates the specified list.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsUpdate' ('ListNameParam' "thimura/haskell") True (Just "Haskellers")
-- @
--
-- >>> listsUpdate (ListNameParam "thimura/haskell") True (Just "Haskellers")
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/update.json" [("slug","haskell"),("owner_screen_name","thimura"),("description","Haskellers"),("mode","public")]
listsUpdate :: ListParam
            -> Bool -- ^ is public
            -> Maybe T.Text -- ^ description
            -> APIRequest ListsUpdate List
listsUpdate :: ListParam
-> Bool -> Maybe Text -> APIRequest DirectMessagesDestroy List
listsUpdate ListParam
list Bool
isPublic Maybe Text
description = Method
-> String -> APIQuery -> APIRequest DirectMessagesDestroy List
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"lists/update.json") (ListParam -> APIQuery
mkListParam ListParam
list APIQuery -> APIQuery -> APIQuery
forall a. [a] -> [a] -> [a]
++ APIQuery
p')
  where
    p :: APIQuery
p = [(Method
"mode", Text -> PV
PVString (Text -> PV) -> (Bool -> Text) -> Bool -> PV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Text
forall p. IsString p => Bool -> p
mode (Bool -> PV) -> Bool -> PV
forall a b. (a -> b) -> a -> b
$ Bool
isPublic)]
    p' :: APIQuery
p' = (APIQuery -> APIQuery)
-> (Text -> APIQuery -> APIQuery)
-> Maybe Text
-> APIQuery
-> APIQuery
forall b a. b -> (a -> b) -> Maybe a -> b
maybe APIQuery -> APIQuery
forall a. a -> a
id (\Text
d -> ((Method
"description", Text -> PV
PVString Text
d)(Method, PV) -> APIQuery -> APIQuery
forall a. a -> [a] -> [a]
:)) Maybe Text
description APIQuery
p
    mode :: Bool -> p
mode Bool
True = p
"public"
    mode Bool
False = p
"private"
type ListsUpdate = EmptyParams

-- | Returns the post parameter which creates a new list for the authenticated user.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsCreate' ('ListNameParam' "thimura/haskell")
-- @
--
-- >>> listsCreate "haskell" True Nothing
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/create.json" [("name","haskell"),("mode","public")]
-- >>> listsCreate "haskell" False Nothing
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/create.json" [("name","haskell"),("mode","private")]
-- >>> listsCreate "haskell" True (Just "Haskellers")
-- APIRequest "POST" "https://api.twitter.com/1.1/lists/create.json" [("description","Haskellers"),("name","haskell"),("mode","public")]
listsCreate :: T.Text -- ^ list name
            -> Bool -- ^ whether public(True) or private(False)
            -> Maybe T.Text -- ^ the description to give the list
            -> APIRequest ListsCreate List
listsCreate :: Text -> Bool -> Maybe Text -> APIRequest DirectMessagesDestroy List
listsCreate Text
name Bool
isPublic Maybe Text
description = Method
-> String -> APIQuery -> APIRequest DirectMessagesDestroy List
forall (supports :: [Param Symbol *]) responseType.
Method -> String -> APIQuery -> APIRequest supports responseType
APIRequest Method
"POST" (String
endpoint String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"lists/create.json") APIQuery
p'
  where
    p :: APIQuery
p = [(Method
"name", Text -> PV
PVString Text
name), (Method
"mode", Text -> PV
PVString (Text -> PV) -> (Bool -> Text) -> Bool -> PV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Text
forall p. IsString p => Bool -> p
mode (Bool -> PV) -> Bool -> PV
forall a b. (a -> b) -> a -> b
$ Bool
isPublic)]
    p' :: APIQuery
p' = (APIQuery -> APIQuery)
-> (Text -> APIQuery -> APIQuery)
-> Maybe Text
-> APIQuery
-> APIQuery
forall b a. b -> (a -> b) -> Maybe a -> b
maybe APIQuery -> APIQuery
forall a. a -> a
id (\Text
d -> ((Method
"description", Text -> PV
PVString Text
d)(Method, PV) -> APIQuery -> APIQuery
forall a. a -> [a] -> [a]
:)) Maybe Text
description APIQuery
p
    mode :: Bool -> p
mode Bool
True = p
"public"
    mode Bool
False = p
"private"
type ListsCreate = EmptyParams

-- | Returns the request parameter which asks the specified list.
--
-- You can perform request by using 'call':
--
-- @
-- res <- 'call' twInfo mgr '$' 'listsShow' ('ListNameParam' "thimura/haskell")
-- @
--
-- >>> listsShow (ListNameParam "thimura/haskell")
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/show.json" [("slug","haskell"),("owner_screen_name","thimura")]
-- >>> listsShow (ListIdParam 20849097)
-- APIRequest "GET" "https://api.twitter.com/1.1/lists/show.json" [("list_id","20849097")]
listsShow :: ListParam -> APIRequest ListsShow List
listsShow :: ListParam -> APIRequest DirectMessagesDestroy List
listsShow ListParam
q = Method
-> String -> APIQuery -> APIRequest DirectMessagesDestroy List
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
"lists/show.json") (ListParam -> APIQuery
mkListParam ListParam
q)
type ListsShow = EmptyParams

-- | Upload media and returns the media data.
--
-- You can update your status with multiple media by calling 'mediaUpload' and 'update' successively.
--
-- First, you should upload media with 'mediaUpload':
--
-- @
-- res1 <- 'call' twInfo mgr '$' 'mediaUpload' ('MediaFromFile' \"\/path\/to\/upload\/file1.png\")
-- res2 <- 'call' twInfo mgr '$' 'mediaUpload' ('MediaRequestBody' \"file2.png\" \"[.. file body ..]\")
-- @
--
-- and then collect the resulting media IDs and update your status by calling 'update':
--
-- @
-- 'call' twInfo mgr '$' 'update' \"Hello World\" '&' #media_ids '?~' ['uploadedMediaId' res1, 'uploadedMediaId' res2]
-- @
--
-- See: <https://dev.twitter.com/docs/api/multiple-media-extended-entities>
--
-- >>> mediaUpload (MediaFromFile "/home/test/test.png")
-- APIRequestMultipart "POST" "https://upload.twitter.com/1.1/media/upload.json" []
mediaUpload :: MediaData
            -> APIRequest MediaUpload UploadedMedia
mediaUpload :: MediaData -> APIRequest DirectMessagesDestroy UploadedMedia
mediaUpload MediaData
mediaData =
    Method
-> String
-> APIQuery
-> [Part]
-> APIRequest DirectMessagesDestroy UploadedMedia
forall (supports :: [Param Symbol *]) responseType.
Method
-> String -> APIQuery -> [Part] -> APIRequest supports responseType
APIRequestMultipart Method
"POST" String
uri [] [MediaData -> Part
mediaBody MediaData
mediaData]
  where
    uri :: String
uri = String
"https://upload.twitter.com/1.1/media/upload.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 MediaUpload = EmptyParams

statusesMentionsTimeline :: APIRequest Status.StatusesMentionsTimeline [Status]
statusesMentionsTimeline :: APIRequest StatusesMentionsTimeline [Status]
statusesMentionsTimeline = APIRequest StatusesMentionsTimeline [Status]
Status.mentionsTimeline
statusesUserTimeline :: UserParam -> APIRequest Status.StatusesUserTimeline [Status]
statusesUserTimeline :: UserParam -> APIRequest StatusesUserTimeline [Status]
statusesUserTimeline = UserParam -> APIRequest StatusesUserTimeline [Status]
Status.userTimeline
statusesHomeTimeline :: APIRequest Status.StatusesHomeTimeline [Status]
statusesHomeTimeline :: APIRequest StatusesHomeTimeline [Status]
statusesHomeTimeline = APIRequest StatusesHomeTimeline [Status]
Status.homeTimeline
statusesRetweetsOfMe :: APIRequest Status.StatusesRetweetsOfMe [Status]
statusesRetweetsOfMe :: APIRequest StatusesRetweetsOfMe [Status]
statusesRetweetsOfMe = APIRequest StatusesRetweetsOfMe [Status]
Status.retweetsOfMe
statusesRetweetsId :: StatusId -> APIRequest Status.StatusesRetweetsId [RetweetedStatus]
statusesRetweetsId :: StatusId -> APIRequest StatusesRetweetsId [RetweetedStatus]
statusesRetweetsId = StatusId -> APIRequest StatusesRetweetsId [RetweetedStatus]
Status.retweetsId
statusesShowId :: StatusId -> APIRequest Status.StatusesShowId Status
statusesShowId :: StatusId -> APIRequest StatusesShowId Status
statusesShowId = StatusId -> APIRequest StatusesShowId Status
Status.showId
statusesDestroyId :: StatusId -> APIRequest Status.StatusesDestroyId Status
statusesDestroyId :: StatusId -> APIRequest StatusesDestroyId Status
statusesDestroyId = StatusId -> APIRequest StatusesDestroyId Status
Status.destroyId
statusesUpdate :: T.Text -> APIRequest Status.StatusesUpdate Status
statusesUpdate :: Text -> APIRequest StatusesUpdate Status
statusesUpdate = Text -> APIRequest StatusesUpdate Status
Status.update
statusesRetweetId :: StatusId -> APIRequest Status.StatusesRetweetId RetweetedStatus
statusesRetweetId :: StatusId -> APIRequest StatusesRetweetId RetweetedStatus
statusesRetweetId = StatusId -> APIRequest StatusesRetweetId RetweetedStatus
Status.retweetId
statusesUpdateWithMedia :: T.Text -> MediaData -> APIRequest Status.StatusesUpdateWithMedia Status
statusesUpdateWithMedia :: Text -> MediaData -> APIRequest StatusesUpdateWithMedia Status
statusesUpdateWithMedia = Text -> MediaData -> APIRequest StatusesUpdateWithMedia Status
Status.updateWithMedia
statusesLookup :: [StatusId] -> APIRequest Status.StatusesLookup [Status]
statusesLookup :: [StatusId] -> APIRequest StatusesLookup [Status]
statusesLookup = [StatusId] -> APIRequest StatusesLookup [Status]
Status.lookup