{-# LANGUAGE TemplateHaskell #-}

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

import Calamity.Types.Snowflake
import Data.Aeson ((.:), (.:?))
import qualified Data.Aeson as Aeson
import Data.Text (Text)
import Data.Word
import Optics.TH
import TextShow.TH

fuseTup2 :: Monad f => (f a, f b) -> f (a, b)
fuseTup2 :: forall (f :: * -> *) a b. Monad f => (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)
  deriving (HasID Attachment) via HasIDField "id" Attachment

$(deriveTextShow ''Attachment)
$(makeFieldLabelsNoPrefix ''Attachment)

instance Aeson.FromJSON Attachment where
  parseJSON :: Value -> Parser Attachment
parseJSON = String
-> (Object -> Parser Attachment) -> Value -> Parser Attachment
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.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 -> Key -> Parser (Maybe Word64)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"width"
    Maybe Word64
height <- Object
v Object -> Key -> Parser (Maybe Word64)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"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 -> Key -> Parser (Snowflake Attachment)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"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 -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"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 -> Key -> Parser Word64
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"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 -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"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 -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"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))