{-# 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.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
newtype UpdateId = UpdateId Int
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)
data Update = Update
{ Update -> UpdateId
updateUpdateId :: UpdateId
, Update -> Maybe Message
updateMessage :: Maybe Message
, Update -> Maybe Message
updateEditedMessage :: Maybe Message
, Update -> Maybe Message
updateChannelPost :: Maybe Message
, Update -> Maybe Message
updateEditedChannelPost :: Maybe Message
, Update -> Maybe InlineQuery
updateInlineQuery :: Maybe InlineQuery
, Update -> Maybe ChosenInlineResult
updateChosenInlineResult :: Maybe ChosenInlineResult
, Update -> Maybe CallbackQuery
updateCallbackQuery :: Maybe CallbackQuery
, Update -> Maybe ShippingQuery
updateShippingQuery :: Maybe ShippingQuery
, Update -> Maybe PreCheckoutQuery
updatePreCheckoutQuery :: Maybe PreCheckoutQuery
} 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
Update{Maybe PreCheckoutQuery
Maybe ShippingQuery
Maybe CallbackQuery
Maybe Message
Maybe ChosenInlineResult
Maybe InlineQuery
UpdateId
updatePreCheckoutQuery :: Maybe PreCheckoutQuery
updateShippingQuery :: Maybe ShippingQuery
updateCallbackQuery :: Maybe CallbackQuery
updateChosenInlineResult :: Maybe ChosenInlineResult
updateInlineQuery :: Maybe InlineQuery
updateEditedChannelPost :: Maybe Message
updateChannelPost :: Maybe Message
updateEditedMessage :: Maybe Message
updateMessage :: Maybe Message
updateUpdateId :: UpdateId
updatePreCheckoutQuery :: Update -> Maybe PreCheckoutQuery
updateShippingQuery :: Update -> Maybe ShippingQuery
updateCallbackQuery :: Update -> Maybe CallbackQuery
updateChosenInlineResult :: Update -> Maybe ChosenInlineResult
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
]
type GetUpdates
= "getUpdates" :> ReqBody '[JSON] GetUpdatesRequest :> Get '[JSON] (Response [Update])
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)
data GetUpdatesRequest = GetUpdatesRequest
{ GetUpdatesRequest -> Maybe UpdateId
getUpdatesOffset :: Maybe UpdateId
, GetUpdatesRequest -> Maybe Int
getUpdatesLimit :: Maybe Int
, GetUpdatesRequest -> Maybe Seconds
getUpdatesTimeout :: Maybe Seconds
, GetUpdatesRequest -> Maybe [UpdateType]
getUpdatesAllowedUpdates :: Maybe [UpdateType]
} 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