{-# LANGUAGE TemplateHaskell #-}

-- | Discord emojis
module Calamity.Types.Model.Guild.Emoji (
  Emoji (..),
  Partial (PartialEmoji),
  RawEmoji (..),
  emojiAsRawEmoji,
) where

import Calamity.Internal.Utils (
  AesonVector (unAesonVector),
  CalamityToJSON (..),
  CalamityToJSON' (..),
  (.=),
 )
import Calamity.Types.CDNAsset (CDNAsset (..))
import Calamity.Types.Model.Guild.Role
import Calamity.Types.Model.User
import Calamity.Types.Snowflake
import Calamity.Utils.CDNUrl (cdnURL)
import Data.Aeson ((.!=), (.:), (.:?))
import qualified Data.Aeson as Aeson
import qualified Data.Text as T
import Data.Vector.Unboxing (Vector)
import Network.HTTP.Req ((/:))
import Optics.TH
import TextShow (showt)
import qualified TextShow

data Emoji = Emoji
  { Emoji -> Snowflake Emoji
id :: Snowflake Emoji
  , Emoji -> Text
name :: T.Text
  , Emoji -> Vector (Snowflake Role)
roles :: Vector (Snowflake Role)
  , Emoji -> Maybe User
user :: Maybe User
  , Emoji -> Bool
requireColons :: Bool
  , Emoji -> Bool
managed :: Bool
  , Emoji -> Bool
animated :: Bool
  }
  deriving (Emoji -> Emoji -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Emoji -> Emoji -> Bool
$c/= :: Emoji -> Emoji -> Bool
== :: Emoji -> Emoji -> Bool
$c== :: Emoji -> Emoji -> Bool
Eq, Int -> Emoji -> ShowS
[Emoji] -> ShowS
Emoji -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Emoji] -> ShowS
$cshowList :: [Emoji] -> ShowS
show :: Emoji -> String
$cshow :: Emoji -> String
showsPrec :: Int -> Emoji -> ShowS
$cshowsPrec :: Int -> Emoji -> ShowS
Show)
  deriving (Int -> Emoji -> Builder
Int -> Emoji -> Text
Int -> Emoji -> Text
[Emoji] -> Builder
[Emoji] -> Text
[Emoji] -> Text
Emoji -> Builder
Emoji -> Text
Emoji -> Text
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 :: [Emoji] -> Text
$cshowtlList :: [Emoji] -> Text
showtl :: Emoji -> Text
$cshowtl :: Emoji -> Text
showtlPrec :: Int -> Emoji -> Text
$cshowtlPrec :: Int -> Emoji -> Text
showtList :: [Emoji] -> Text
$cshowtList :: [Emoji] -> Text
showt :: Emoji -> Text
$cshowt :: Emoji -> Text
showtPrec :: Int -> Emoji -> Text
$cshowtPrec :: Int -> Emoji -> Text
showbList :: [Emoji] -> Builder
$cshowbList :: [Emoji] -> Builder
showb :: Emoji -> Builder
$cshowb :: Emoji -> Builder
showbPrec :: Int -> Emoji -> Builder
$cshowbPrec :: Int -> Emoji -> Builder
TextShow.TextShow) via TextShow.FromStringShow Emoji
  deriving (HasID Emoji) via HasIDField "id" Emoji

instance Aeson.FromJSON Emoji where
  parseJSON :: Value -> Parser Emoji
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"Emoji" forall a b. (a -> b) -> a -> b
$ \Object
v ->
    Snowflake Emoji
-> Text
-> Vector (Snowflake Role)
-> Maybe User
-> Bool
-> Bool
-> Bool
-> Emoji
Emoji
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. AesonVector a -> Vector a
unAesonVector forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"roles") forall a. Parser (Maybe a) -> a -> Parser a
.!= forall a. Monoid a => a
mempty
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"user"
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"require_colons" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"managed" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"animated" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False

instance CDNAsset Emoji where
  assetURL :: Emoji -> Url 'Https
assetURL Emoji {Snowflake Emoji
id :: Snowflake Emoji
$sel:id:Emoji :: Emoji -> Snowflake Emoji
id, Bool
animated :: Bool
$sel:animated:Emoji :: Emoji -> Bool
animated} =
    Url 'Https
cdnURL forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text
"emojis" forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: (forall a. TextShow a => a -> Text
showt Snowflake Emoji
id forall a. Semigroup a => a -> a -> a
<> if Bool
animated then Text
".gif" else Text
".png")

emojiAsRawEmoji :: Emoji -> RawEmoji
emojiAsRawEmoji :: Emoji -> RawEmoji
emojiAsRawEmoji Emoji {Snowflake Emoji
id :: Snowflake Emoji
$sel:id:Emoji :: Emoji -> Snowflake Emoji
id, Text
name :: Text
$sel:name:Emoji :: Emoji -> Text
name, Bool
animated :: Bool
$sel:animated:Emoji :: Emoji -> Bool
animated} = Partial Emoji -> RawEmoji
CustomEmoji forall a b. (a -> b) -> a -> b
$ Snowflake Emoji -> Text -> Bool -> Partial Emoji
PartialEmoji Snowflake Emoji
id Text
name Bool
animated

data instance Partial Emoji = PartialEmoji
  { Partial Emoji -> Snowflake Emoji
id :: Snowflake Emoji
  , Partial Emoji -> Text
name :: T.Text
  , Partial Emoji -> Bool
animated :: Bool
  }
  deriving (Partial Emoji -> Partial Emoji -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Partial Emoji -> Partial Emoji -> Bool
$c/= :: Partial Emoji -> Partial Emoji -> Bool
== :: Partial Emoji -> Partial Emoji -> Bool
$c== :: Partial Emoji -> Partial Emoji -> Bool
Eq)
  deriving (HasID Emoji) via HasIDField "id" (Partial Emoji)
  deriving ([Partial Emoji] -> Encoding
[Partial Emoji] -> Value
Partial Emoji -> Encoding
Partial Emoji -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Partial Emoji] -> Encoding
$ctoEncodingList :: [Partial Emoji] -> Encoding
toJSONList :: [Partial Emoji] -> Value
$ctoJSONList :: [Partial Emoji] -> Value
toEncoding :: Partial Emoji -> Encoding
$ctoEncoding :: Partial Emoji -> Encoding
toJSON :: Partial Emoji -> Value
$ctoJSON :: Partial Emoji -> Value
Aeson.ToJSON) via CalamityToJSON (Partial Emoji)

instance Aeson.FromJSON (Partial Emoji) where
  parseJSON :: Value -> Parser (Partial Emoji)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"Partial Emoji" forall a b. (a -> b) -> a -> b
$ \Object
v ->
    Snowflake Emoji -> Text -> Bool -> Partial Emoji
PartialEmoji
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"animated" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False

instance CalamityToJSON' (Partial Emoji) where
  toPairs :: forall kv. KeyValue kv => Partial Emoji -> [Maybe kv]
toPairs PartialEmoji {Bool
Text
Snowflake Emoji
animated :: Bool
name :: Text
id :: Snowflake Emoji
$sel:animated:PartialEmoji :: Partial Emoji -> Bool
$sel:name:PartialEmoji :: Partial Emoji -> Text
$sel:id:PartialEmoji :: Partial Emoji -> Snowflake Emoji
..} =
    [ Key
"id" forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Snowflake Emoji
id
    , Key
"name" forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Text
name
    , Key
"animated" forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Bool
animated
    ]

instance Show (Partial Emoji) where
  show :: Partial Emoji -> String
show PartialEmoji {Snowflake Emoji
id :: Snowflake Emoji
$sel:id:PartialEmoji :: Partial Emoji -> Snowflake Emoji
id, Text
name :: Text
$sel:name:PartialEmoji :: Partial Emoji -> Text
name, Bool
animated :: Bool
$sel:animated:PartialEmoji :: Partial Emoji -> Bool
animated} =
    String
"<" forall a. Semigroup a => a -> a -> a
<> String
a forall a. Semigroup a => a -> a -> a
<> String
":" forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
name forall a. Semigroup a => a -> a -> a
<> String
":" forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Snowflake Emoji
id forall a. Semigroup a => a -> a -> a
<> String
">"
    where
      a :: String
a = if Bool
animated then String
"a" else String
""

instance TextShow.TextShow (Partial Emoji) where
  showb :: Partial Emoji -> Builder
showb PartialEmoji {Snowflake Emoji
id :: Snowflake Emoji
$sel:id:PartialEmoji :: Partial Emoji -> Snowflake Emoji
id, Text
name :: Text
$sel:name:PartialEmoji :: Partial Emoji -> Text
name, Bool
animated :: Bool
$sel:animated:PartialEmoji :: Partial Emoji -> Bool
animated} =
    Builder
"<" forall a. Semigroup a => a -> a -> a
<> Builder
a forall a. Semigroup a => a -> a -> a
<> Builder
":" forall a. Semigroup a => a -> a -> a
<> Text -> Builder
TextShow.fromText Text
name forall a. Semigroup a => a -> a -> a
<> Builder
":" forall a. Semigroup a => a -> a -> a
<> forall a. TextShow a => a -> Builder
TextShow.showb Snowflake Emoji
id forall a. Semigroup a => a -> a -> a
<> Builder
">"
    where
      a :: Builder
a = if Bool
animated then Builder
"a" else Builder
""

data RawEmoji
  = UnicodeEmoji T.Text
  | CustomEmoji (Partial Emoji)
  deriving (RawEmoji -> RawEmoji -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RawEmoji -> RawEmoji -> Bool
$c/= :: RawEmoji -> RawEmoji -> Bool
== :: RawEmoji -> RawEmoji -> Bool
$c== :: RawEmoji -> RawEmoji -> Bool
Eq)

instance Show RawEmoji where
  show :: RawEmoji -> String
show (UnicodeEmoji Text
v) = Text -> String
T.unpack Text
v
  show (CustomEmoji Partial Emoji
p) = forall a. Show a => a -> String
show Partial Emoji
p

instance TextShow.TextShow RawEmoji where
  showb :: RawEmoji -> Builder
showb (UnicodeEmoji Text
v) = Text -> Builder
TextShow.fromText Text
v
  showb (CustomEmoji Partial Emoji
p) = forall a. TextShow a => a -> Builder
TextShow.showb Partial Emoji
p

instance Aeson.ToJSON RawEmoji where
  toJSON :: RawEmoji -> Value
toJSON (CustomEmoji Partial Emoji
e) = forall a. ToJSON a => a -> Value
Aeson.toJSON Partial Emoji
e
  toJSON (UnicodeEmoji Text
s) = [Pair] -> Value
Aeson.object [Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
s, Key
"id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= forall a. Maybe a
Nothing @()]
  toEncoding :: RawEmoji -> Encoding
toEncoding (CustomEmoji Partial Emoji
e) = forall a. ToJSON a => a -> Encoding
Aeson.toEncoding Partial Emoji
e
  toEncoding (UnicodeEmoji Text
s) = Series -> Encoding
Aeson.pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ [Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= Text
s, Key
"id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Aeson..= forall a. Maybe a
Nothing @()]

instance Aeson.FromJSON RawEmoji where
  parseJSON :: Value -> Parser RawEmoji
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"RawEmoji" forall a b. (a -> b) -> a -> b
$ \Object
v -> do
    Maybe (Snowflake Emoji)
m_id :: Maybe (Snowflake Emoji) <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"id"
    Bool
anim <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"animated" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
    Text
name :: T.Text <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"

    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ case Maybe (Snowflake Emoji)
m_id of
      Just Snowflake Emoji
id -> Partial Emoji -> RawEmoji
CustomEmoji forall a b. (a -> b) -> a -> b
$ Snowflake Emoji -> Text -> Bool -> Partial Emoji
PartialEmoji Snowflake Emoji
id Text
name Bool
anim
      Maybe (Snowflake Emoji)
Nothing -> Text -> RawEmoji
UnicodeEmoji Text
name

$(makeFieldLabelsNoPrefix ''Emoji)
$(makeFieldLabelsNoPrefix 'PartialEmoji)
$(makeFieldLabelsNoPrefix ''RawEmoji)