-- | Channel webhooks
module Calamity.Types.Model.Channel.Webhook (Webhook (..)) where

import Calamity.Internal.AesonThings
import {-# SOURCE #-} Calamity.Types.Model.Channel
import {-# SOURCE #-} Calamity.Types.Model.Guild.Guild
import Calamity.Types.Model.User
import Calamity.Types.Snowflake

import Data.Aeson
import Data.Text (Text)

import GHC.Generics

import TextShow
import qualified TextShow.Generic as TSG

data Webhook = Webhook
  { Webhook -> Snowflake Webhook
id :: Snowflake Webhook
  , Webhook -> Integer
type_ :: Integer
  , Webhook -> Maybe (Snowflake Guild)
guildID :: Maybe (Snowflake Guild)
  , Webhook -> Maybe (Snowflake Channel)
channelID :: Maybe (Snowflake Channel)
  , Webhook -> Maybe (Snowflake User)
user :: Maybe (Snowflake User)
  , Webhook -> Text
name :: Text
  , Webhook -> Text
avatar :: Text
  , Webhook -> Maybe Text
token :: Maybe Text
  }
  deriving (Webhook -> Webhook -> Bool
(Webhook -> Webhook -> Bool)
-> (Webhook -> Webhook -> Bool) -> Eq Webhook
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Webhook -> Webhook -> Bool
$c/= :: Webhook -> Webhook -> Bool
== :: Webhook -> Webhook -> Bool
$c== :: Webhook -> Webhook -> Bool
Eq, Int -> Webhook -> ShowS
[Webhook] -> ShowS
Webhook -> String
(Int -> Webhook -> ShowS)
-> (Webhook -> String) -> ([Webhook] -> ShowS) -> Show Webhook
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Webhook] -> ShowS
$cshowList :: [Webhook] -> ShowS
show :: Webhook -> String
$cshow :: Webhook -> String
showsPrec :: Int -> Webhook -> ShowS
$cshowsPrec :: Int -> Webhook -> ShowS
Show, (forall x. Webhook -> Rep Webhook x)
-> (forall x. Rep Webhook x -> Webhook) -> Generic Webhook
forall x. Rep Webhook x -> Webhook
forall x. Webhook -> Rep Webhook x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Webhook x -> Webhook
$cfrom :: forall x. Webhook -> Rep Webhook x
Generic)
  deriving (Int -> Webhook -> Builder
Int -> Webhook -> Text
Int -> Webhook -> Text
[Webhook] -> Builder
[Webhook] -> Text
[Webhook] -> Text
Webhook -> Builder
Webhook -> Text
Webhook -> Text
(Int -> Webhook -> Builder)
-> (Webhook -> Builder)
-> ([Webhook] -> Builder)
-> (Int -> Webhook -> Text)
-> (Webhook -> Text)
-> ([Webhook] -> Text)
-> (Int -> Webhook -> Text)
-> (Webhook -> Text)
-> ([Webhook] -> Text)
-> TextShow Webhook
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 :: [Webhook] -> Text
$cshowtlList :: [Webhook] -> Text
showtl :: Webhook -> Text
$cshowtl :: Webhook -> Text
showtlPrec :: Int -> Webhook -> Text
$cshowtlPrec :: Int -> Webhook -> Text
showtList :: [Webhook] -> Text
$cshowtList :: [Webhook] -> Text
showt :: Webhook -> Text
$cshowt :: Webhook -> Text
showtPrec :: Int -> Webhook -> Text
$cshowtPrec :: Int -> Webhook -> Text
showbList :: [Webhook] -> Builder
$cshowbList :: [Webhook] -> Builder
showb :: Webhook -> Builder
$cshowb :: Webhook -> Builder
showbPrec :: Int -> Webhook -> Builder
$cshowbPrec :: Int -> Webhook -> Builder
TextShow) via TSG.FromGeneric Webhook
  deriving (Value -> Parser [Webhook]
Value -> Parser Webhook
(Value -> Parser Webhook)
-> (Value -> Parser [Webhook]) -> FromJSON Webhook
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Webhook]
$cparseJSONList :: Value -> Parser [Webhook]
parseJSON :: Value -> Parser Webhook
$cparseJSON :: Value -> Parser Webhook
FromJSON) via WithSpecialCases '["user" `ExtractFieldFrom` "id"] Webhook
  deriving (HasID Webhook) via HasIDField "id" Webhook