{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE TypeApplications           #-}
{-# LANGUAGE TypeOperators              #-}
module Telegram.Bot.API.GettingUpdates where

import           Data.Aeson                      (FromJSON (..), ToJSON (..))
import           Data.Foldable                   (asum)
import           Data.Int                        (Int32)
import           Data.Proxy
import           GHC.Generics                    (Generic)

import           Servant.API
import           Servant.Client                  hiding (Response)

import           Telegram.Bot.API.Internal.Utils
import           Telegram.Bot.API.MakingRequests
import           Telegram.Bot.API.Types
import           Telegram.Bot.API.InlineMode

-- ** 'Update'

newtype UpdateId = UpdateId Int32
  deriving (UpdateId -> UpdateId -> Bool
(UpdateId -> UpdateId -> Bool)
-> (UpdateId -> UpdateId -> Bool) -> Eq UpdateId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateId -> UpdateId -> Bool
$c/= :: UpdateId -> UpdateId -> Bool
== :: UpdateId -> UpdateId -> Bool
$c== :: UpdateId -> UpdateId -> Bool
Eq, Eq UpdateId
Eq UpdateId
-> (UpdateId -> UpdateId -> Ordering)
-> (UpdateId -> UpdateId -> Bool)
-> (UpdateId -> UpdateId -> Bool)
-> (UpdateId -> UpdateId -> Bool)
-> (UpdateId -> UpdateId -> Bool)
-> (UpdateId -> UpdateId -> UpdateId)
-> (UpdateId -> UpdateId -> UpdateId)
-> Ord UpdateId
UpdateId -> UpdateId -> Bool
UpdateId -> UpdateId -> Ordering
UpdateId -> UpdateId -> UpdateId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UpdateId -> UpdateId -> UpdateId
$cmin :: UpdateId -> UpdateId -> UpdateId
max :: UpdateId -> UpdateId -> UpdateId
$cmax :: UpdateId -> UpdateId -> UpdateId
>= :: UpdateId -> UpdateId -> Bool
$c>= :: UpdateId -> UpdateId -> Bool
> :: UpdateId -> UpdateId -> Bool
$c> :: UpdateId -> UpdateId -> Bool
<= :: UpdateId -> UpdateId -> Bool
$c<= :: UpdateId -> UpdateId -> Bool
< :: UpdateId -> UpdateId -> Bool
$c< :: UpdateId -> UpdateId -> Bool
compare :: UpdateId -> UpdateId -> Ordering
$ccompare :: UpdateId -> UpdateId -> Ordering
$cp1Ord :: Eq UpdateId
Ord, Int -> UpdateId -> ShowS
[UpdateId] -> ShowS
UpdateId -> String
(Int -> UpdateId -> ShowS)
-> (UpdateId -> String) -> ([UpdateId] -> ShowS) -> Show UpdateId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateId] -> ShowS
$cshowList :: [UpdateId] -> ShowS
show :: UpdateId -> String
$cshow :: UpdateId -> String
showsPrec :: Int -> UpdateId -> ShowS
$cshowsPrec :: Int -> UpdateId -> ShowS
Show, [UpdateId] -> Encoding
[UpdateId] -> Value
UpdateId -> Encoding
UpdateId -> Value
(UpdateId -> Value)
-> (UpdateId -> Encoding)
-> ([UpdateId] -> Value)
-> ([UpdateId] -> Encoding)
-> ToJSON UpdateId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [UpdateId] -> Encoding
$ctoEncodingList :: [UpdateId] -> Encoding
toJSONList :: [UpdateId] -> Value
$ctoJSONList :: [UpdateId] -> Value
toEncoding :: UpdateId -> Encoding
$ctoEncoding :: UpdateId -> Encoding
toJSON :: UpdateId -> Value
$ctoJSON :: UpdateId -> Value
ToJSON, Value -> Parser [UpdateId]
Value -> Parser UpdateId
(Value -> Parser UpdateId)
-> (Value -> Parser [UpdateId]) -> FromJSON UpdateId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [UpdateId]
$cparseJSONList :: Value -> Parser [UpdateId]
parseJSON :: Value -> Parser UpdateId
$cparseJSON :: Value -> Parser UpdateId
FromJSON)

-- | This object represents an incoming update.
-- At most __one__ of the optional parameters can be present in any given update.
data Update = Update
  { Update -> UpdateId
updateUpdateId          :: UpdateId -- ^ The update‘s unique identifier. Update identifiers start from a certain positive number and increase sequentially. This ID becomes especially handy if you’re using Webhooks, since it allows you to ignore repeated updates or to restore the correct update sequence, should they get out of order. If there are no new updates for at least a week, then identifier of the next update will be chosen randomly instead of sequentially.
  , Update -> Maybe Message
updateMessage           :: Maybe Message -- ^ New incoming message of any kind — text, photo, sticker, etc.
  , Update -> Maybe Message
updateEditedMessage     :: Maybe Message -- ^ New version of a message that is known to the bot and was edited
  , Update -> Maybe Message
updateChannelPost       :: Maybe Message -- ^ New incoming channel post of any kind — text, photo, sticker, etc.
  , Update -> Maybe Message
updateEditedChannelPost :: Maybe Message -- ^ New version of a channel post that is known to the bot and was edited

  , Update -> Maybe InlineQuery
updateInlineQuery :: Maybe InlineQuery -- ^ New incoming inline query
--   , updateChosenInlineResult :: Maybe ChosenInlineResult -- ^ The result of an inline query that was chosen by a user and sent to their chat partner. Please see our documentation on the feedback collecting for details on how to enable these updates for your bot.

  , Update -> Maybe CallbackQuery
updateCallbackQuery     :: Maybe CallbackQuery -- ^ New incoming callback query

--   , updateShippingQuery :: Maybe ShippingQuery -- ^ New incoming shipping query. Only for invoices with flexible price
--   , updatePreCheckoutQuery :: Maybe PreCheckoutQuery -- ^ New incoming pre-checkout query. Contains full information about checkout
  } deriving ((forall x. Update -> Rep Update x)
-> (forall x. Rep Update x -> Update) -> Generic Update
forall x. Rep Update x -> Update
forall x. Update -> Rep Update x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Update x -> Update
$cfrom :: forall x. Update -> Rep Update x
Generic, Int -> Update -> ShowS
[Update] -> ShowS
Update -> String
(Int -> Update -> ShowS)
-> (Update -> String) -> ([Update] -> ShowS) -> Show Update
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Update] -> ShowS
$cshowList :: [Update] -> ShowS
show :: Update -> String
$cshow :: Update -> String
showsPrec :: Int -> Update -> ShowS
$cshowsPrec :: Int -> Update -> ShowS
Show)

instance ToJSON   Update where toJSON :: Update -> Value
toJSON = Update -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON Update where parseJSON :: Value -> Parser Update
parseJSON = Value -> Parser Update
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON

updateChatId :: Update -> Maybe ChatId
updateChatId :: Update -> Maybe ChatId
updateChatId = (Message -> ChatId) -> Maybe Message -> Maybe ChatId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Chat -> ChatId
chatId (Chat -> ChatId) -> (Message -> Chat) -> Message -> ChatId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Message -> Chat
messageChat) (Maybe Message -> Maybe ChatId)
-> (Update -> Maybe Message) -> Update -> Maybe ChatId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Update -> Maybe Message
extractUpdateMessage

extractUpdateMessage :: Update -> Maybe Message
extractUpdateMessage :: Update -> Maybe Message
extractUpdateMessage Update{Maybe CallbackQuery
Maybe Message
Maybe InlineQuery
UpdateId
updateCallbackQuery :: Maybe CallbackQuery
updateInlineQuery :: Maybe InlineQuery
updateEditedChannelPost :: Maybe Message
updateChannelPost :: Maybe Message
updateEditedMessage :: Maybe Message
updateMessage :: Maybe Message
updateUpdateId :: UpdateId
updateCallbackQuery :: Update -> Maybe CallbackQuery
updateInlineQuery :: Update -> Maybe InlineQuery
updateEditedChannelPost :: Update -> Maybe Message
updateChannelPost :: Update -> Maybe Message
updateEditedMessage :: Update -> Maybe Message
updateMessage :: Update -> Maybe Message
updateUpdateId :: Update -> UpdateId
..} = [Maybe Message] -> Maybe Message
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum
  [ Maybe Message
updateMessage
  , Maybe Message
updateEditedMessage
  , Maybe Message
updateChannelPost
  , Maybe Message
updateEditedChannelPost
  , Maybe CallbackQuery
updateCallbackQuery Maybe CallbackQuery
-> (CallbackQuery -> Maybe Message) -> Maybe Message
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CallbackQuery -> Maybe Message
callbackQueryMessage
  ]

-- ** 'getUpdates'

type GetUpdates
  = "getUpdates" :> ReqBody '[JSON] GetUpdatesRequest :> Get '[JSON] (Response [Update])

-- | Use this method to receive incoming updates using long polling.
-- An list of 'Update' objects is returned.
--
-- NOTE: This method will not work if an outgoing webhook is set up.
--
-- NOTE: In order to avoid getting duplicate updates, recalculate offset after each server response.
getUpdates :: GetUpdatesRequest -> ClientM (Response [Update])
getUpdates :: GetUpdatesRequest -> ClientM (Response [Update])
getUpdates = Proxy GetUpdates -> Client ClientM GetUpdates
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetUpdates
forall k (t :: k). Proxy t
Proxy @GetUpdates)

-- | Request parameters for 'getUpdates'.
data GetUpdatesRequest = GetUpdatesRequest
  { GetUpdatesRequest -> Maybe UpdateId
getUpdatesOffset         :: Maybe UpdateId -- ^ Identifier of the first update to be returned. Must be greater by one than the highest among the identifiers of previously received updates. By default, updates starting with the earliest unconfirmed update are returned. An update is considered confirmed as soon as getUpdates is called with an offset higher than its update_id. The negative offset can be specified to retrieve updates starting from -offset update from the end of the updates queue. All previous updates will forgotten.
  , GetUpdatesRequest -> Maybe Int32
getUpdatesLimit          :: Maybe Int32 -- ^ Limits the number of updates to be retrieved. Values between 1—100 are accepted. Defaults to 100.
  , GetUpdatesRequest -> Maybe Seconds
getUpdatesTimeout        :: Maybe Seconds -- ^ Timeout in seconds for long polling. Defaults to 0, i.e. usual short polling. Should be positive, short polling should be used for testing purposes only.
  , GetUpdatesRequest -> Maybe [UpdateType]
getUpdatesAllowedUpdates :: Maybe [UpdateType] -- ^ List the types of updates you want your bot to receive. For example, specify [“message”, “edited_channel_post”, “callback_query”] to only receive updates of these types. See GetUpdates for a complete list of available update types. Specify an empty list to receive all updates regardless of type (default). If not specified, the previous setting will be used. Please note that this parameter doesn't affect updates created before the call to the getUpdates, so unwanted updates may be received for a short period of time.
  } deriving ((forall x. GetUpdatesRequest -> Rep GetUpdatesRequest x)
-> (forall x. Rep GetUpdatesRequest x -> GetUpdatesRequest)
-> Generic GetUpdatesRequest
forall x. Rep GetUpdatesRequest x -> GetUpdatesRequest
forall x. GetUpdatesRequest -> Rep GetUpdatesRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetUpdatesRequest x -> GetUpdatesRequest
$cfrom :: forall x. GetUpdatesRequest -> Rep GetUpdatesRequest x
Generic)

instance ToJSON   GetUpdatesRequest where toJSON :: GetUpdatesRequest -> Value
toJSON = GetUpdatesRequest -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON GetUpdatesRequest where parseJSON :: Value -> Parser GetUpdatesRequest
parseJSON = Value -> Parser GetUpdatesRequest
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON

data UpdateType
  = UpdateMessage
  | UpdateEditedMessage
  | UpdateChannelPost
  | UpdateEditedChannelPost
  | UpdateInlineQuery
  | UpdateChosenInlineResult
  | UpdateCallbackQuery
  | UpdateShippingQuery
  | UpdatePreCheckoutQuery
  deriving ((forall x. UpdateType -> Rep UpdateType x)
-> (forall x. Rep UpdateType x -> UpdateType) -> Generic UpdateType
forall x. Rep UpdateType x -> UpdateType
forall x. UpdateType -> Rep UpdateType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateType x -> UpdateType
$cfrom :: forall x. UpdateType -> Rep UpdateType x
Generic)

instance ToJSON   UpdateType where toJSON :: UpdateType -> Value
toJSON = UpdateType -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON UpdateType where parseJSON :: Value -> Parser UpdateType
parseJSON = Value -> Parser UpdateType
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON