{-# LANGUAGE BlockArguments #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} module Telegram.Bot.API.Types.ReactionType where import Data.Aeson (FromJSON (..), ToJSON (..), KeyValue ((.=)), Value (..), withObject, (.:)) import Data.Aeson.Types (Parser) import Data.Text (Text) import Telegram.Bot.API.Types.Common import Telegram.Bot.API.Internal.Utils import qualified Data.Text as Text -- ** 'ReactionType' -- | This object describes the type of a reaction. Currently, it can be one of -- -- * 'ReactionTypeEmoji', -- * 'ReactionTypeCustomEmoji'. -- data ReactionType -- ^ The reaction is based on an emoji. = ReactionTypeEmoji { reactionTypeEmojiType :: Text -- ^ Type of the reaction, always โ€œemojiโ€. , reactionTypeEmojiEmoji :: Text -- ^ Reaction emoji. Currently, it can be one of "๐Ÿ‘", "๐Ÿ‘Ž", "โค", "๐Ÿ”ฅ", "๐Ÿฅฐ", "๐Ÿ‘", "๐Ÿ˜", "๐Ÿค”", "๐Ÿคฏ", "๐Ÿ˜ฑ", "๐Ÿคฌ", "๐Ÿ˜ข", "๐ŸŽ‰", "๐Ÿคฉ", "๐Ÿคฎ", "๐Ÿ’ฉ", "๐Ÿ™", "๐Ÿ‘Œ", "๐Ÿ•Š", "๐Ÿคก", "๐Ÿฅฑ", "๐Ÿฅด", "๐Ÿ˜", "๐Ÿณ", "โคโ€๐Ÿ”ฅ", "๐ŸŒš", "๐ŸŒญ", "๐Ÿ’ฏ", "๐Ÿคฃ", "โšก", "๐ŸŒ", "๐Ÿ†", "๐Ÿ’”", "๐Ÿคจ", "๐Ÿ˜", "๐Ÿ“", "๐Ÿพ", "๐Ÿ’‹", "๐Ÿ–•", "๐Ÿ˜ˆ", "๐Ÿ˜ด", "๐Ÿ˜ญ", "๐Ÿค“", "๐Ÿ‘ป", "๐Ÿ‘จโ€๐Ÿ’ป", "๐Ÿ‘€", "๐ŸŽƒ", "๐Ÿ™ˆ", "๐Ÿ˜‡", "๐Ÿ˜จ", "๐Ÿค", "โœ", "๐Ÿค—", "๐Ÿซก", "๐ŸŽ…", "๐ŸŽ„", "โ˜ƒ", "๐Ÿ’…", "๐Ÿคช", "๐Ÿ—ฟ", "๐Ÿ†’", "๐Ÿ’˜", "๐Ÿ™‰", "๐Ÿฆ„", "๐Ÿ˜˜", "๐Ÿ’Š", "๐Ÿ™Š", "๐Ÿ˜Ž", "๐Ÿ‘พ", "๐Ÿคทโ€โ™‚", "๐Ÿคท", "๐Ÿคทโ€โ™€", "๐Ÿ˜ก". } -- ^ The reaction is based on a custom emoji. | ReactionTypeCustomEmoji { reactionTypeCustomEmojiType :: Text -- ^ Type of the reaction, always โ€œcustom_emojiโ€. , reactionTypeCustomEmojiCustomEmojiId :: Text -- ^ Custom emoji identifier. } deriving Show instance ToJSON ReactionType where toJSON = \case ReactionTypeEmoji _t e -> addJsonFields (Object mempty) (addType "emoji" ["emoji" .= e]) ReactionTypeCustomEmoji _t cei -> addJsonFields (Object mempty) (addType "custom_emoji" ["custom_emoji_id" .= cei]) instance FromJSON ReactionType where parseJSON = withObject "ReactionType" \o -> (o .: "type" :: Parser Text) >>= \case "emoji" -> ReactionTypeEmoji <$> o .: "type" <*> o .: "emoji" "custom_emoji" -> ReactionTypeCustomEmoji <$> o .: "type" <*> o .: "custom_emoji_id" t -> fail $ Text.unpack ("Unknown type: " <> t)