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

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

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

-- ** 'File'

-- | This object represents a file ready to be downloaded.
-- The file can be downloaded via the link @https://api.telegram.org/file/bot<token>/<file_path>@.
-- It is guaranteed that the link will be valid for at least 1 hour.
-- When the link expires, a new one can be requested by calling getFile.
data File = File
  { File -> FileId
fileFileId       :: FileId      -- ^ Unique identifier for this file.
  , File -> FileId
fileFileUniqueId :: 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.
  , File -> Maybe Integer
fileFileSize     :: Maybe Integer -- ^ File size in bytes, if known.
  , File -> Maybe Text
fileFilePath     :: Maybe Text  -- ^ File path. Use https://api.telegram.org/file/bot<token>/<file_path> to get the file.
  }
  deriving ((forall x. File -> Rep File x)
-> (forall x. Rep File x -> File) -> Generic File
forall x. Rep File x -> File
forall x. File -> Rep File x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. File -> Rep File x
from :: forall x. File -> Rep File x
$cto :: forall x. Rep File x -> File
to :: forall x. Rep File x -> File
Generic, Int -> File -> ShowS
[File] -> ShowS
File -> String
(Int -> File -> ShowS)
-> (File -> String) -> ([File] -> ShowS) -> Show File
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> File -> ShowS
showsPrec :: Int -> File -> ShowS
$cshow :: File -> String
show :: File -> String
$cshowList :: [File] -> ShowS
showList :: [File] -> ShowS
Show)

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