{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Telegram.Bot.API.Types.PollType where

import Data.Aeson (Value(String), FromJSON (..), ToJSON (..))
import Data.Text (Text)
import GHC.Generics (Generic)

import Telegram.Bot.API.Internal.Utils

-- ** 'PollType'

data PollType =
  PollTypeQuiz | PollTypeRegular
  deriving ((forall x. PollType -> Rep PollType x)
-> (forall x. Rep PollType x -> PollType) -> Generic PollType
forall x. Rep PollType x -> PollType
forall x. PollType -> Rep PollType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PollType -> Rep PollType x
from :: forall x. PollType -> Rep PollType x
$cto :: forall x. Rep PollType x -> PollType
to :: forall x. Rep PollType x -> PollType
Generic, Int -> PollType -> ShowS
[PollType] -> ShowS
PollType -> String
(Int -> PollType -> ShowS)
-> (PollType -> String) -> ([PollType] -> ShowS) -> Show PollType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PollType -> ShowS
showsPrec :: Int -> PollType -> ShowS
$cshow :: PollType -> String
show :: PollType -> String
$cshowList :: [PollType] -> ShowS
showList :: [PollType] -> ShowS
Show)

getPollType :: PollType -> Text
getPollType :: PollType -> Text
getPollType PollType
PollTypeQuiz = Text
"quiz"
getPollType PollType
PollTypeRegular = Text
"regular"

instance ToJSON PollType where
  toJSON :: PollType -> Value
toJSON = Text -> Value
String (Text -> Value) -> (PollType -> Text) -> PollType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PollType -> Text
getPollType

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