{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Telegram.Bot.API.Types.InputMedia where
import Data.Aeson (ToJSON (..), KeyValue ((.=)))
import Data.Aeson.Text (encodeToLazyText)
import Data.Bool (bool)
import Data.Maybe (catMaybes)
import Data.Functor ((<&>))
import Data.Text (Text, pack)
import GHC.Generics (Generic)
import Servant.Multipart.API
import System.FilePath
import qualified Data.Text.Lazy as TL
import Telegram.Bot.API.Types.Common
import Telegram.Bot.API.Types.MessageEntity
import Telegram.Bot.API.Internal.Utils
data InputMediaGeneric = InputMediaGeneric
  { InputMediaGeneric -> InputFile
inputMediaGenericMedia :: InputFile 
  , InputMediaGeneric -> Maybe Text
inputMediaGenericCaption :: Maybe Text 
  , InputMediaGeneric -> Maybe Text
inputMediaGenericParseMode :: Maybe Text 
  , InputMediaGeneric -> Maybe [MessageEntity]
inputMediaGenericCaptionEntities :: Maybe [MessageEntity] 
  , InputMediaGeneric -> Maybe Bool
inputMediaGenericShowCaptionAboveMedia :: Maybe Bool 
  }
  deriving (forall x. InputMediaGeneric -> Rep InputMediaGeneric x)
-> (forall x. Rep InputMediaGeneric x -> InputMediaGeneric)
-> Generic InputMediaGeneric
forall x. Rep InputMediaGeneric x -> InputMediaGeneric
forall x. InputMediaGeneric -> Rep InputMediaGeneric x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InputMediaGeneric -> Rep InputMediaGeneric x
from :: forall x. InputMediaGeneric -> Rep InputMediaGeneric x
$cto :: forall x. Rep InputMediaGeneric x -> InputMediaGeneric
to :: forall x. Rep InputMediaGeneric x -> InputMediaGeneric
Generic
instance ToJSON InputMediaGeneric where toJSON :: InputMediaGeneric -> Value
toJSON = InputMediaGeneric -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance ToMultipart Tmp InputMediaGeneric where
  toMultipart :: InputMediaGeneric -> MultipartData Tmp
toMultipart InputMediaGeneric{Maybe Bool
Maybe [MessageEntity]
Maybe Text
InputFile
inputMediaGenericMedia :: InputMediaGeneric -> InputFile
inputMediaGenericCaption :: InputMediaGeneric -> Maybe Text
inputMediaGenericParseMode :: InputMediaGeneric -> Maybe Text
inputMediaGenericCaptionEntities :: InputMediaGeneric -> Maybe [MessageEntity]
inputMediaGenericShowCaptionAboveMedia :: InputMediaGeneric -> Maybe Bool
inputMediaGenericMedia :: InputFile
inputMediaGenericCaption :: Maybe Text
inputMediaGenericParseMode :: Maybe Text
inputMediaGenericCaptionEntities :: Maybe [MessageEntity]
inputMediaGenericShowCaptionAboveMedia :: Maybe Bool
..} = Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"media" InputFile
inputMediaGenericMedia ([Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields []) where
    fields :: [Input]
fields = [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes
      [ Maybe Text
inputMediaGenericCaption Maybe Text -> (Text -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"caption" Text
t
      , Maybe Text
inputMediaGenericParseMode Maybe Text -> (Text -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"parse_mode" Text
t
      , Maybe [MessageEntity]
inputMediaGenericCaptionEntities Maybe [MessageEntity] -> ([MessageEntity] -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \[MessageEntity]
t -> Text -> Text -> Input
Input Text
"caption_entities" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [MessageEntity] -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
      ]
data InputMediaGenericThumbnail = InputMediaGenericThumbnail
  { InputMediaGenericThumbnail -> InputMediaGeneric
inputMediaGenericGeneric :: InputMediaGeneric
  , InputMediaGenericThumbnail -> Maybe InputFile
inputMediaGenericThumbnail :: Maybe InputFile 
  }
instance ToJSON InputMediaGenericThumbnail where
  toJSON :: InputMediaGenericThumbnail -> Value
toJSON InputMediaGenericThumbnail{Maybe InputFile
InputMediaGeneric
inputMediaGenericGeneric :: InputMediaGenericThumbnail -> InputMediaGeneric
inputMediaGenericThumbnail :: InputMediaGenericThumbnail -> Maybe InputFile
inputMediaGenericGeneric :: InputMediaGeneric
inputMediaGenericThumbnail :: Maybe InputFile
..}
    = Value -> [Pair] -> Value
addJsonFields (InputMediaGeneric -> Value
forall a. ToJSON a => a -> Value
toJSON InputMediaGeneric
inputMediaGenericGeneric)
      [Key
"thumbnail" Key -> Maybe InputFile -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe InputFile
inputMediaGenericThumbnail]
instance ToMultipart Tmp InputMediaGenericThumbnail where
  toMultipart :: InputMediaGenericThumbnail -> MultipartData Tmp
toMultipart = \case
    InputMediaGenericThumbnail InputMediaGeneric
generic Maybe InputFile
Nothing -> InputMediaGeneric -> MultipartData Tmp
forall tag a. ToMultipart tag a => a -> MultipartData tag
toMultipart InputMediaGeneric
generic
    InputMediaGenericThumbnail InputMediaGeneric
generic (Just InputFile
thumbnail) ->
      Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumbnail" InputFile
thumbnail (InputMediaGeneric -> MultipartData Tmp
forall tag a. ToMultipart tag a => a -> MultipartData tag
toMultipart InputMediaGeneric
generic)
data InputMedia
  = InputMediaPhoto 
    { InputMedia -> InputMediaGeneric
inputMediaPhotoGeneric :: InputMediaGeneric
    , InputMedia -> Maybe Bool
inputMediaPhotoHasSpoiler :: Maybe Bool 
    }
  | InputMediaVideo 
    { InputMedia -> InputMediaGenericThumbnail
inputMediaVideoGeneric :: InputMediaGenericThumbnail
    , InputMedia -> Maybe Integer
inputMediaVideoWidth :: Maybe Integer 
    , InputMedia -> Maybe Integer
inputMediaVideoHeight :: Maybe Integer 
    , InputMedia -> Maybe Integer
inputMediaVideoDuration :: Maybe Integer 
    , InputMedia -> Maybe Bool
inputMediaVideoSupportsStreaming :: Maybe Bool 
    , InputMedia -> Maybe Bool
inputMediaVideoHasSpoiler :: Maybe Bool 
    }
  | InputMediaAnimation 
    { InputMedia -> InputMediaGenericThumbnail
inputMediaAnimationGeneric :: InputMediaGenericThumbnail
    , InputMedia -> Maybe Integer
inputMediaAnimationWidth :: Maybe Integer 
    , InputMedia -> Maybe Integer
inputMediaAnimationHeight :: Maybe Integer 
    , InputMedia -> Maybe Integer
inputMediaAnimationDuration :: Maybe Integer 
    , InputMedia -> Maybe Bool
inputMediaAnimationHasSpoiler :: Maybe Bool 
    }
  | InputMediaAudio 
    { InputMedia -> InputMediaGenericThumbnail
inputMediaAudioGeneric :: InputMediaGenericThumbnail
    , InputMedia -> Maybe Integer
inputMediaAudioDuration :: Maybe Integer 
    , InputMedia -> Maybe Text
inputMediaAudioPerformer :: Maybe Text 
    , InputMedia -> Maybe Text
inputMediaAudioTitle :: Maybe Text 
    }
  | InputMediaDocument 
    { InputMedia -> InputMediaGenericThumbnail
inputMediaDocumentGeneric :: InputMediaGenericThumbnail
    , InputMedia -> Maybe Bool
inputMediaDocumentDisableContentTypeDetection :: Maybe Bool 
    }
instance ToJSON InputMedia where
  toJSON :: InputMedia -> Value
toJSON = \case
    InputMediaPhoto InputMediaGeneric
img Maybe Bool
spoiler ->
      Value -> [Pair] -> Value
addJsonFields (InputMediaGeneric -> Value
forall a. ToJSON a => a -> Value
toJSON InputMediaGeneric
img) (Text -> [Pair] -> [Pair]
addType Text
"photo" [ Key
"has_spoiler" 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
spoiler])
    InputMediaVideo InputMediaGenericThumbnail
imgt Maybe Integer
width Maybe Integer
height Maybe Integer
duration Maybe Bool
streaming Maybe Bool
spoiler ->
      Value -> [Pair] -> Value
addJsonFields (InputMediaGenericThumbnail -> Value
forall a. ToJSON a => a -> Value
toJSON InputMediaGenericThumbnail
imgt)
                (Text -> [Pair] -> [Pair]
addType Text
"video"
                [ Key
"width" Key -> Maybe Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Integer
width
                , Key
"height" Key -> Maybe Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Integer
height
                , Key
"duration" Key -> Maybe Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Integer
duration
                , Key
"support_streaming" 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
streaming
                , Key
"has_spoiler" 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
spoiler
                ])
    InputMediaAnimation InputMediaGenericThumbnail
imgt Maybe Integer
width Maybe Integer
height Maybe Integer
duration Maybe Bool
spoiler ->
      Value -> [Pair] -> Value
addJsonFields (InputMediaGenericThumbnail -> Value
forall a. ToJSON a => a -> Value
toJSON InputMediaGenericThumbnail
imgt)
                (Text -> [Pair] -> [Pair]
addType Text
"animation"
                [ Key
"width" Key -> Maybe Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Integer
width
                , Key
"height" Key -> Maybe Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Integer
height
                , Key
"duration" Key -> Maybe Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Integer
duration
                , Key
"has_spoiler" 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
spoiler
                ])
    InputMediaAudio InputMediaGenericThumbnail
imgt Maybe Integer
duration Maybe Text
performer Maybe Text
title ->
      Value -> [Pair] -> Value
addJsonFields (InputMediaGenericThumbnail -> Value
forall a. ToJSON a => a -> Value
toJSON InputMediaGenericThumbnail
imgt)
                (Text -> [Pair] -> [Pair]
addType Text
"audio"
                [ Key
"duration" Key -> Maybe Integer -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Integer
duration
                , Key
"performer" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
performer
                , Key
"title" Key -> Maybe Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe Text
title
                ])
    InputMediaDocument InputMediaGenericThumbnail
imgt Maybe Bool
dctd ->
      Value -> [Pair] -> Value
addJsonFields (InputMediaGenericThumbnail -> Value
forall a. ToJSON a => a -> Value
toJSON InputMediaGenericThumbnail
imgt)
                (Text -> [Pair] -> [Pair]
addType Text
"document" [Key
"disable_content_type_detection" 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
dctd])
instance ToMultipart Tmp InputMedia where
  toMultipart :: InputMedia -> MultipartData Tmp
toMultipart = let
    in \case
    InputMediaPhoto InputMediaGeneric
img Maybe Bool
spoiler ->
      [Input] -> MultipartData Tmp -> MultipartData Tmp
forall tag. [Input] -> MultipartData tag -> MultipartData tag
addMultipartFields
      (Text -> Text -> Input
Input Text
"type" Text
"photo"
       Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
: [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes
        [ Maybe Bool
spoiler Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
          \Bool
t -> Text -> Text -> Input
Input Text
"has_spoiler" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
        ]) (InputMediaGeneric -> MultipartData Tmp
forall tag a. ToMultipart tag a => a -> MultipartData tag
toMultipart InputMediaGeneric
img)
    InputMediaVideo InputMediaGenericThumbnail
imgt Maybe Integer
width Maybe Integer
height Maybe Integer
duration Maybe Bool
streaming Maybe Bool
spoiler ->
      [Input] -> MultipartData Tmp -> MultipartData Tmp
forall tag. [Input] -> MultipartData tag -> MultipartData tag
addMultipartFields
      (Text -> Text -> Input
Input Text
"type" Text
"video"
      Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
: [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes 
      [ Maybe Integer
width Maybe Integer -> (Integer -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Integer
t -> Text -> Text -> Input
Input Text
"width" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Integer
t)
      , Maybe Integer
height Maybe Integer -> (Integer -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Integer
t -> Text -> Text -> Input
Input Text
"height" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Integer
t)
      , Maybe Integer
duration Maybe Integer -> (Integer -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Integer
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Integer
t)
      , Maybe Bool
streaming Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"support_streaming" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe Bool
spoiler Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"has_spoiler" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      ]) (InputMediaGenericThumbnail -> MultipartData Tmp
forall tag a. ToMultipart tag a => a -> MultipartData tag
toMultipart InputMediaGenericThumbnail
imgt)
    InputMediaAnimation InputMediaGenericThumbnail
imgt Maybe Integer
width Maybe Integer
height Maybe Integer
duration Maybe Bool
spoiler ->
      [Input] -> MultipartData Tmp -> MultipartData Tmp
forall tag. [Input] -> MultipartData tag -> MultipartData tag
addMultipartFields
      (Text -> Text -> Input
Input Text
"type" Text
"animation"
      Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
: [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes 
      [ Maybe Integer
width Maybe Integer -> (Integer -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Integer
t -> Text -> Text -> Input
Input Text
"width" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Integer
t)
      , Maybe Integer
height Maybe Integer -> (Integer -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Integer
t -> Text -> Text -> Input
Input Text
"height" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Integer
t)
      , Maybe Integer
duration Maybe Integer -> (Integer -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Integer
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Integer
t)
      , Maybe Bool
spoiler Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"has_spoiler" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      ]) (InputMediaGenericThumbnail -> MultipartData Tmp
forall tag a. ToMultipart tag a => a -> MultipartData tag
toMultipart InputMediaGenericThumbnail
imgt)
    InputMediaAudio InputMediaGenericThumbnail
imgt Maybe Integer
duration Maybe Text
performer Maybe Text
title ->
      [Input] -> MultipartData Tmp -> MultipartData Tmp
forall tag. [Input] -> MultipartData tag -> MultipartData tag
addMultipartFields
      (Text -> Text -> Input
Input Text
"type" Text
"audio"
      Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
: [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes 
      [ Maybe Integer
duration Maybe Integer -> (Integer -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Integer
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Integer
t)
      , Maybe Text
performer Maybe Text -> (Text -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"performer" Text
t
      , Maybe Text
title Maybe Text -> (Text -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"title" Text
t
      ]) (InputMediaGenericThumbnail -> MultipartData Tmp
forall tag a. ToMultipart tag a => a -> MultipartData tag
toMultipart InputMediaGenericThumbnail
imgt)
    InputMediaDocument InputMediaGenericThumbnail
imgt Maybe Bool
dctd ->
      [Input] -> MultipartData Tmp -> MultipartData Tmp
forall tag. [Input] -> MultipartData tag -> MultipartData tag
addMultipartFields
      (Text -> Text -> Input
Input Text
"type" Text
"document"
      Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
: [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes 
      [ Maybe Bool
dctd Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> 
         \Bool
t -> Text -> Text -> Input
Input Text
"disable_content_type_detection" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      ]) (InputMediaGenericThumbnail -> MultipartData Tmp
forall tag a. ToMultipart tag a => a -> MultipartData tag
toMultipart InputMediaGenericThumbnail
imgt)
type ContentType = Text
data InputFile
  = InputFileId FileId
  | FileUrl Text
  | InputFile FilePath ContentType
  deriving ((forall x. InputFile -> Rep InputFile x)
-> (forall x. Rep InputFile x -> InputFile) -> Generic InputFile
forall x. Rep InputFile x -> InputFile
forall x. InputFile -> Rep InputFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InputFile -> Rep InputFile x
from :: forall x. InputFile -> Rep InputFile x
$cto :: forall x. Rep InputFile x -> InputFile
to :: forall x. Rep InputFile x -> InputFile
Generic, Int -> InputFile -> ShowS
[InputFile] -> ShowS
InputFile -> String
(Int -> InputFile -> ShowS)
-> (InputFile -> String)
-> ([InputFile] -> ShowS)
-> Show InputFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InputFile -> ShowS
showsPrec :: Int -> InputFile -> ShowS
$cshow :: InputFile -> String
show :: InputFile -> String
$cshowList :: [InputFile] -> ShowS
showList :: [InputFile] -> ShowS
Show)
instance ToJSON InputFile where
  toJSON :: InputFile -> Value
toJSON (InputFileId FileId
i) = FileId -> Value
forall a. ToJSON a => a -> Value
toJSON FileId
i
  toJSON (FileUrl Text
t) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
t
  toJSON (InputFile String
f Text
_) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text
"attach://" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
pack (ShowS
takeFileName String
f))
makeFile :: Text -> InputFile ->  MultipartData Tmp ->  MultipartData Tmp
makeFile :: Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
name (InputFile String
path Text
ct) (MultipartData [Input]
fields [FileData Tmp]
files) = 
  [Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData 
    (Text -> Text -> Input
Input Text
name (Text
"attach://" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name) Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
: [Input]
fields) 
    (Text -> Text -> Text -> MultipartResult Tmp -> FileData Tmp
forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
name (String -> Text
pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ShowS
takeFileName String
path) Text
ct String
MultipartResult Tmp
path FileData Tmp -> [FileData Tmp] -> [FileData Tmp]
forall a. a -> [a] -> [a]
: [FileData Tmp]
files)
makeFile Text
name InputFile
file (MultipartData [Input]
fields [FileData Tmp]
files) = 
  [Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData 
    (Text -> Text -> Input
Input Text
name (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ InputFile -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText InputFile
file) Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
: [Input]
fields) 
    [FileData Tmp]
files