-- | Message attachments
module Calamity.Types.Model.Channel.Attachment
    ( Attachment(..) ) where

import           Calamity.Internal.AesonThings ()
import           Calamity.Types.Snowflake
import           Data.Aeson
import           Data.Text.Lazy                ( Text )
import           Data.Word
import           GHC.Generics
import           TextShow
import qualified TextShow.Generic              as TSG

fuseTup2 :: Monad f => (f a, f b) -> f (a, b)
fuseTup2 :: (f a, f b) -> f (a, b)
fuseTup2 (f a
a, f b
b) = do
  !a
a' <- f a
a
  !b
b' <- f b
b
  (a, b) -> f (a, b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
a', b
b')

data Attachment = Attachment
  { Attachment -> Snowflake Attachment
id         :: Snowflake Attachment
  , Attachment -> Text
filename   :: !Text
  , Attachment -> Word64
size       :: Word64
  , Attachment -> Text
url        :: !Text
  , Attachment -> Text
proxyUrl   :: !Text
  , Attachment -> Maybe (Word64, Word64)
dimensions :: !(Maybe (Word64, Word64))
  }
  deriving ( Attachment -> Attachment -> Bool
(Attachment -> Attachment -> Bool)
-> (Attachment -> Attachment -> Bool) -> Eq Attachment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Attachment -> Attachment -> Bool
$c/= :: Attachment -> Attachment -> Bool
== :: Attachment -> Attachment -> Bool
$c== :: Attachment -> Attachment -> Bool
Eq, Int -> Attachment -> ShowS
[Attachment] -> ShowS
Attachment -> String
(Int -> Attachment -> ShowS)
-> (Attachment -> String)
-> ([Attachment] -> ShowS)
-> Show Attachment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Attachment] -> ShowS
$cshowList :: [Attachment] -> ShowS
show :: Attachment -> String
$cshow :: Attachment -> String
showsPrec :: Int -> Attachment -> ShowS
$cshowsPrec :: Int -> Attachment -> ShowS
Show, (forall x. Attachment -> Rep Attachment x)
-> (forall x. Rep Attachment x -> Attachment) -> Generic Attachment
forall x. Rep Attachment x -> Attachment
forall x. Attachment -> Rep Attachment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Attachment x -> Attachment
$cfrom :: forall x. Attachment -> Rep Attachment x
Generic )
  deriving ( Int -> Attachment -> Builder
Int -> Attachment -> Text
Int -> Attachment -> Text
[Attachment] -> Builder
[Attachment] -> Text
[Attachment] -> Text
Attachment -> Builder
Attachment -> Text
Attachment -> Text
(Int -> Attachment -> Builder)
-> (Attachment -> Builder)
-> ([Attachment] -> Builder)
-> (Int -> Attachment -> Text)
-> (Attachment -> Text)
-> ([Attachment] -> Text)
-> (Int -> Attachment -> Text)
-> (Attachment -> Text)
-> ([Attachment] -> Text)
-> TextShow Attachment
forall a.
(Int -> a -> Builder)
-> (a -> Builder)
-> ([a] -> Builder)
-> (Int -> a -> Text)
-> (a -> Text)
-> ([a] -> Text)
-> (Int -> a -> Text)
-> (a -> Text)
-> ([a] -> Text)
-> TextShow a
showtlList :: [Attachment] -> Text
$cshowtlList :: [Attachment] -> Text
showtl :: Attachment -> Text
$cshowtl :: Attachment -> Text
showtlPrec :: Int -> Attachment -> Text
$cshowtlPrec :: Int -> Attachment -> Text
showtList :: [Attachment] -> Text
$cshowtList :: [Attachment] -> Text
showt :: Attachment -> Text
$cshowt :: Attachment -> Text
showtPrec :: Int -> Attachment -> Text
$cshowtPrec :: Int -> Attachment -> Text
showbList :: [Attachment] -> Builder
$cshowbList :: [Attachment] -> Builder
showb :: Attachment -> Builder
$cshowb :: Attachment -> Builder
showbPrec :: Int -> Attachment -> Builder
$cshowbPrec :: Int -> Attachment -> Builder
TextShow ) via TSG.FromGeneric Attachment
  deriving ( HasID Attachment ) via HasIDField "id" Attachment

instance ToJSON Attachment where
  toJSON :: Attachment -> Value
toJSON Attachment { Snowflake Attachment
id :: Snowflake Attachment
$sel:id:Attachment :: Attachment -> Snowflake Attachment
id, Text
filename :: Text
$sel:filename:Attachment :: Attachment -> Text
filename, Word64
size :: Word64
$sel:size:Attachment :: Attachment -> Word64
size, Text
url :: Text
$sel:url:Attachment :: Attachment -> Text
url, Text
proxyUrl :: Text
$sel:proxyUrl:Attachment :: Attachment -> Text
proxyUrl, $sel:dimensions:Attachment :: Attachment -> Maybe (Word64, Word64)
dimensions = Just (Word64
width, Word64
height) } = [Pair] -> Value
object
    [ Text
"id" Text -> Snowflake Attachment -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Snowflake Attachment
id
    , Text
"filename" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
filename
    , Text
"size" Text -> Word64 -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Word64
size
    , Text
"url" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
url
    , Text
"proxy_url" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
proxyUrl
    , Text
"width" Text -> Word64 -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Word64
width
    , Text
"height" Text -> Word64 -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Word64
height]
  toJSON Attachment { Snowflake Attachment
id :: Snowflake Attachment
$sel:id:Attachment :: Attachment -> Snowflake Attachment
id, Text
filename :: Text
$sel:filename:Attachment :: Attachment -> Text
filename, Word64
size :: Word64
$sel:size:Attachment :: Attachment -> Word64
size, Text
url :: Text
$sel:url:Attachment :: Attachment -> Text
url, Text
proxyUrl :: Text
$sel:proxyUrl:Attachment :: Attachment -> Text
proxyUrl } =
    [Pair] -> Value
object [Text
"id" Text -> Snowflake Attachment -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Snowflake Attachment
id, Text
"filename" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
filename, Text
"size" Text -> Word64 -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Word64
size, Text
"url" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
url, Text
"proxy_url" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
proxyUrl]

instance FromJSON Attachment where
  parseJSON :: Value -> Parser Attachment
parseJSON = String
-> (Object -> Parser Attachment) -> Value -> Parser Attachment
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Attachment" ((Object -> Parser Attachment) -> Value -> Parser Attachment)
-> (Object -> Parser Attachment) -> Value -> Parser Attachment
forall a b. (a -> b) -> a -> b
$ \Object
v -> do
    Maybe Word64
width <- Object
v Object -> Text -> Parser (Maybe Word64)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"width"
    Maybe Word64
height <- Object
v Object -> Text -> Parser (Maybe Word64)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"height"

    Snowflake Attachment
-> Text
-> Word64
-> Text
-> Text
-> Maybe (Word64, Word64)
-> Attachment
Attachment (Snowflake Attachment
 -> Text
 -> Word64
 -> Text
 -> Text
 -> Maybe (Word64, Word64)
 -> Attachment)
-> Parser (Snowflake Attachment)
-> Parser
     (Text
      -> Word64 -> Text -> Text -> Maybe (Word64, Word64) -> Attachment)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Snowflake Attachment)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id" Parser
  (Text
   -> Word64 -> Text -> Text -> Maybe (Word64, Word64) -> Attachment)
-> Parser Text
-> Parser
     (Word64 -> Text -> Text -> Maybe (Word64, Word64) -> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"filename" Parser
  (Word64 -> Text -> Text -> Maybe (Word64, Word64) -> Attachment)
-> Parser Word64
-> Parser (Text -> Text -> Maybe (Word64, Word64) -> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Word64
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"size" Parser (Text -> Text -> Maybe (Word64, Word64) -> Attachment)
-> Parser Text
-> Parser (Text -> Maybe (Word64, Word64) -> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"url" Parser (Text -> Maybe (Word64, Word64) -> Attachment)
-> Parser Text -> Parser (Maybe (Word64, Word64) -> Attachment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"proxy_url" Parser (Maybe (Word64, Word64) -> Attachment)
-> Parser (Maybe (Word64, Word64)) -> Parser Attachment
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe (Word64, Word64) -> Parser (Maybe (Word64, Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure
      ((Maybe Word64, Maybe Word64) -> Maybe (Word64, Word64)
forall (f :: * -> *) a b. Monad f => (f a, f b) -> f (a, b)
fuseTup2 (Maybe Word64
width, Maybe Word64
height))