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

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

import Telegram.Bot.API.Types.Common 
import Telegram.Bot.API.Types.PhotoSize
import Telegram.Bot.API.Internal.Utils

-- ** 'Audio'

-- | This object represents an audio file to be treated as music by the Telegram clients.
data Audio = Audio
  { Audio -> FileId
audioFileId    :: FileId -- ^ Unique identifier for this file.
  , Audio -> FileId
audioFileUniqueId :: FileId -- ^ Unique identifier for this file, which is supposed to be the same over time and for different bots. Can't be used to download or reuse the file.
  , Audio -> Seconds
audioDuration  :: Seconds -- ^ Duration of the audio in seconds as defined by sender.
  , Audio -> Maybe Text
audioPerformer :: Maybe Text -- ^ Performer of the audio as defined by sender or by audio tags.
  , Audio -> Maybe Text
audioTitle     :: Maybe Text -- ^ Title of the audio as defined by sender or by audio tags.
  , Audio -> Maybe Text
audioFileName  :: Maybe Text -- ^ Original filename as defined by sender.
  , Audio -> Maybe Text
audioMimeType  :: Maybe Text -- ^ MIME type of the file as defined by sender.
  , Audio -> Maybe Integer
audioFileSize  :: Maybe Integer -- ^ File size in bytes.
  , Audio -> Maybe PhotoSize
audioThumb     :: Maybe PhotoSize -- ^ Thumbnail of the album cover to which the music file belongs.
  }
  deriving (forall x. Rep Audio x -> Audio
forall x. Audio -> Rep Audio x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Audio x -> Audio
$cfrom :: forall x. Audio -> Rep Audio x
Generic, Int -> Audio -> ShowS
[Audio] -> ShowS
Audio -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Audio] -> ShowS
$cshowList :: [Audio] -> ShowS
show :: Audio -> String
$cshow :: Audio -> String
showsPrec :: Int -> Audio -> ShowS
$cshowsPrec :: Int -> Audio -> ShowS
Show)

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