{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Telegram.Bot.API.Types.BackgroundType where
import Data.Aeson (FromJSON (..), ToJSON (..), Value (..), (.=), (.:), (.:?), withObject)
import Data.Aeson.Types (Parser)
import Data.Text (Text)
import GHC.Generics (Generic)
import qualified Data.Text as Text
import Telegram.Bot.API.Types.BackgroundFill
import Telegram.Bot.API.Types.Common
import Telegram.Bot.API.Types.Document
import Telegram.Bot.API.Internal.Utils
data BackgroundType
= BackgroundTypeFill
{ BackgroundType -> Text
backgroundTypeFillType :: Text
, BackgroundType -> BackgroundFill
backgroundTypeFillFill :: BackgroundFill
, BackgroundType -> Int
backgroundTypeFillDarkThemeDimming :: Int
}
| BackgroundTypeWallpaper
{ BackgroundType -> Text
backgroundTypeWallpaperType :: Text
, BackgroundType -> Document
backgroundTypeWallpaperDocument :: Document
, BackgroundType -> Int
backgroundTypeWallpaperDarkThemeDimming :: Int
, BackgroundType -> Maybe Bool
backgroundTypeWallpaperIsBlurred :: Maybe Bool
, BackgroundType -> Maybe Bool
backgroundTypeWallpaperIsMoving :: Maybe Bool
}
| BackgroundTypePattern
{ BackgroundType -> Text
backgroundTypePatternType :: Text
, BackgroundType -> Document
backgroundTypePatternDocument :: Document
, BackgroundType -> BackgroundFill
backgroundTypePatternFill :: BackgroundFill
, BackgroundType -> Int
backgroundTypePatternIntensity :: Int
, BackgroundType -> Maybe Bool
backgroundTypePatternIsInverted :: Maybe Bool
, BackgroundType -> Maybe Bool
backgroundTypePatternIsMoving :: Maybe Bool
}
| BackgroundTypeChatTheme
{ BackgroundType -> Text
backgroundTypeChatThemeType :: Text
, BackgroundType -> Text
backgroundTypeChatThemeThemeName :: Text
}
deriving ((forall x. BackgroundType -> Rep BackgroundType x)
-> (forall x. Rep BackgroundType x -> BackgroundType)
-> Generic BackgroundType
forall x. Rep BackgroundType x -> BackgroundType
forall x. BackgroundType -> Rep BackgroundType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BackgroundType -> Rep BackgroundType x
from :: forall x. BackgroundType -> Rep BackgroundType x
$cto :: forall x. Rep BackgroundType x -> BackgroundType
to :: forall x. Rep BackgroundType x -> BackgroundType
Generic, Int -> BackgroundType -> ShowS
[BackgroundType] -> ShowS
BackgroundType -> String
(Int -> BackgroundType -> ShowS)
-> (BackgroundType -> String)
-> ([BackgroundType] -> ShowS)
-> Show BackgroundType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BackgroundType -> ShowS
showsPrec :: Int -> BackgroundType -> ShowS
$cshow :: BackgroundType -> String
show :: BackgroundType -> String
$cshowList :: [BackgroundType] -> ShowS
showList :: [BackgroundType] -> ShowS
Show)
instance ToJSON BackgroundType where
toJSON :: BackgroundType -> Value
toJSON = \case
BackgroundTypeFill Text
_t BackgroundFill
f Int
dtd -> Value -> [Pair] -> Value
addJsonFields
(Object -> Value
Object Object
forall a. Monoid a => a
mempty)
(Text -> [Pair] -> [Pair]
addType Text
"fill" [Key
"fill" Key -> BackgroundFill -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= BackgroundFill
f, Key
"dark_theme_dimming" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
dtd])
BackgroundTypeWallpaper Text
_t Document
d Int
dtd Maybe Bool
ib Maybe Bool
im -> Value -> [Pair] -> Value
addJsonFields
(Object -> Value
Object Object
forall a. Monoid a => a
mempty)
(Text -> [Pair] -> [Pair]
addType Text
"wallpaper" [Key
"document" Key -> Document -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Document
d, Key
"dark_theme_dimming" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
dtd, Key
"is_blurred" Key -> Maybe Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
ib, Key
"is_moving" Key -> Maybe Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
im])
BackgroundTypePattern Text
_t Document
d BackgroundFill
f Int
i Maybe Bool
ii Maybe Bool
im -> Value -> [Pair] -> Value
addJsonFields
(Object -> Value
Object Object
forall a. Monoid a => a
mempty)
(Text -> [Pair] -> [Pair]
addType Text
"pattern" [Key
"document" Key -> Document -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Document
d, Key
"fill" Key -> BackgroundFill -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= BackgroundFill
f, Key
"intensity" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
i, Key
"is_inverted" Key -> Maybe Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
ii, Key
"is_moving" Key -> Maybe Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Bool
im])
BackgroundTypeChatTheme Text
_t Text
tn -> Value -> [Pair] -> Value
addJsonFields
(Object -> Value
Object Object
forall a. Monoid a => a
mempty)
(Text -> [Pair] -> [Pair]
addType Text
"chat_theme" [Key
"theme_name" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
tn])
instance FromJSON BackgroundType where
parseJSON :: Value -> Parser BackgroundType
parseJSON = String
-> (Object -> Parser BackgroundType)
-> Value
-> Parser BackgroundType
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"BackgroundType" \Object
o ->
(Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type" :: Parser Text) Parser Text
-> (Text -> Parser BackgroundType) -> Parser BackgroundType
forall a b. Parser a -> (a -> Parser b) -> Parser b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Text
"fill" -> Text -> BackgroundFill -> Int -> BackgroundType
BackgroundTypeFill
(Text -> BackgroundFill -> Int -> BackgroundType)
-> Parser Text -> Parser (BackgroundFill -> Int -> BackgroundType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser (BackgroundFill -> Int -> BackgroundType)
-> Parser BackgroundFill -> Parser (Int -> BackgroundType)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser BackgroundFill
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fill"
Parser (Int -> BackgroundType)
-> Parser Int -> Parser BackgroundType
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"dark_theme_dimming"
Text
"wallpaper" -> Text
-> Document -> Int -> Maybe Bool -> Maybe Bool -> BackgroundType
BackgroundTypeWallpaper
(Text
-> Document -> Int -> Maybe Bool -> Maybe Bool -> BackgroundType)
-> Parser Text
-> Parser
(Document -> Int -> Maybe Bool -> Maybe Bool -> BackgroundType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser
(Document -> Int -> Maybe Bool -> Maybe Bool -> BackgroundType)
-> Parser Document
-> Parser (Int -> Maybe Bool -> Maybe Bool -> BackgroundType)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Document
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"document"
Parser (Int -> Maybe Bool -> Maybe Bool -> BackgroundType)
-> Parser Int
-> Parser (Maybe Bool -> Maybe Bool -> BackgroundType)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"dark_theme_dimming"
Parser (Maybe Bool -> Maybe Bool -> BackgroundType)
-> Parser (Maybe Bool) -> Parser (Maybe Bool -> BackgroundType)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"is_blurred"
Parser (Maybe Bool -> BackgroundType)
-> Parser (Maybe Bool) -> Parser BackgroundType
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"is_moving"
Text
"pattern" -> Text
-> Document
-> BackgroundFill
-> Int
-> Maybe Bool
-> Maybe Bool
-> BackgroundType
BackgroundTypePattern
(Text
-> Document
-> BackgroundFill
-> Int
-> Maybe Bool
-> Maybe Bool
-> BackgroundType)
-> Parser Text
-> Parser
(Document
-> BackgroundFill
-> Int
-> Maybe Bool
-> Maybe Bool
-> BackgroundType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser
(Document
-> BackgroundFill
-> Int
-> Maybe Bool
-> Maybe Bool
-> BackgroundType)
-> Parser Document
-> Parser
(BackgroundFill
-> Int -> Maybe Bool -> Maybe Bool -> BackgroundType)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Document
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"document"
Parser
(BackgroundFill
-> Int -> Maybe Bool -> Maybe Bool -> BackgroundType)
-> Parser BackgroundFill
-> Parser (Int -> Maybe Bool -> Maybe Bool -> BackgroundType)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser BackgroundFill
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"fill"
Parser (Int -> Maybe Bool -> Maybe Bool -> BackgroundType)
-> Parser Int
-> Parser (Maybe Bool -> Maybe Bool -> BackgroundType)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"intensity"
Parser (Maybe Bool -> Maybe Bool -> BackgroundType)
-> Parser (Maybe Bool) -> Parser (Maybe Bool -> BackgroundType)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"is_inverted"
Parser (Maybe Bool -> BackgroundType)
-> Parser (Maybe Bool) -> Parser BackgroundType
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"is_moving"
Text
"chat_theme" -> Text -> Text -> BackgroundType
BackgroundTypeChatTheme
(Text -> Text -> BackgroundType)
-> Parser Text -> Parser (Text -> BackgroundType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser (Text -> BackgroundType)
-> Parser Text -> Parser BackgroundType
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"theme_name"
Text
t -> String -> Parser BackgroundType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser BackgroundType)
-> String -> Parser BackgroundType
forall a b. (a -> b) -> a -> b
$ Text -> String
Text.unpack (Text
"Unknown type: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t)