{-# LANGUAGE TemplateHaskell #-}

-- | Emoji endpoints
module Calamity.HTTP.Emoji (
  EmojiRequest (..),
  CreateGuildEmojiOptions (..),
  ModifyGuildEmojiOptions (..),
) where

import Calamity.HTTP.Internal.Request
import Calamity.HTTP.Internal.Route
import Calamity.Internal.Utils (CalamityToJSON (..), CalamityToJSON' (..), (.=))
import Calamity.Types.Model.Guild
import Calamity.Types.Snowflake
import qualified Data.Aeson as Aeson
import Data.Function
import Data.Text (Text)
import Network.HTTP.Req
import Optics.TH

data CreateGuildEmojiOptions = CreateGuildEmojiOptions
  { CreateGuildEmojiOptions -> Text
name :: Text
  , CreateGuildEmojiOptions -> Text
image :: Text
  , CreateGuildEmojiOptions -> [Snowflake Role]
roles :: [Snowflake Role]
  }
  deriving (Int -> CreateGuildEmojiOptions -> ShowS
[CreateGuildEmojiOptions] -> ShowS
CreateGuildEmojiOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateGuildEmojiOptions] -> ShowS
$cshowList :: [CreateGuildEmojiOptions] -> ShowS
show :: CreateGuildEmojiOptions -> String
$cshow :: CreateGuildEmojiOptions -> String
showsPrec :: Int -> CreateGuildEmojiOptions -> ShowS
$cshowsPrec :: Int -> CreateGuildEmojiOptions -> ShowS
Show)
  deriving ([CreateGuildEmojiOptions] -> Encoding
[CreateGuildEmojiOptions] -> Value
CreateGuildEmojiOptions -> Encoding
CreateGuildEmojiOptions -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CreateGuildEmojiOptions] -> Encoding
$ctoEncodingList :: [CreateGuildEmojiOptions] -> Encoding
toJSONList :: [CreateGuildEmojiOptions] -> Value
$ctoJSONList :: [CreateGuildEmojiOptions] -> Value
toEncoding :: CreateGuildEmojiOptions -> Encoding
$ctoEncoding :: CreateGuildEmojiOptions -> Encoding
toJSON :: CreateGuildEmojiOptions -> Value
$ctoJSON :: CreateGuildEmojiOptions -> Value
Aeson.ToJSON) via CalamityToJSON CreateGuildEmojiOptions

instance CalamityToJSON' CreateGuildEmojiOptions where
  toPairs :: forall kv. KeyValue kv => CreateGuildEmojiOptions -> [Maybe kv]
toPairs CreateGuildEmojiOptions {[Snowflake Role]
Text
roles :: [Snowflake Role]
image :: Text
name :: Text
$sel:roles:CreateGuildEmojiOptions :: CreateGuildEmojiOptions -> [Snowflake Role]
$sel:image:CreateGuildEmojiOptions :: CreateGuildEmojiOptions -> Text
$sel:name:CreateGuildEmojiOptions :: CreateGuildEmojiOptions -> Text
..} =
    [ Key
"name" forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Text
name
    , Key
"image" forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Text
image
    , Key
"roles" forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= [Snowflake Role]
roles
    ]

data ModifyGuildEmojiOptions = ModifyGuildEmojiOptions
  { ModifyGuildEmojiOptions -> Text
name :: Text
  , ModifyGuildEmojiOptions -> [Snowflake Role]
roles :: [Snowflake Role]
  }
  deriving (Int -> ModifyGuildEmojiOptions -> ShowS
[ModifyGuildEmojiOptions] -> ShowS
ModifyGuildEmojiOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyGuildEmojiOptions] -> ShowS
$cshowList :: [ModifyGuildEmojiOptions] -> ShowS
show :: ModifyGuildEmojiOptions -> String
$cshow :: ModifyGuildEmojiOptions -> String
showsPrec :: Int -> ModifyGuildEmojiOptions -> ShowS
$cshowsPrec :: Int -> ModifyGuildEmojiOptions -> ShowS
Show)
  deriving ([ModifyGuildEmojiOptions] -> Encoding
[ModifyGuildEmojiOptions] -> Value
ModifyGuildEmojiOptions -> Encoding
ModifyGuildEmojiOptions -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ModifyGuildEmojiOptions] -> Encoding
$ctoEncodingList :: [ModifyGuildEmojiOptions] -> Encoding
toJSONList :: [ModifyGuildEmojiOptions] -> Value
$ctoJSONList :: [ModifyGuildEmojiOptions] -> Value
toEncoding :: ModifyGuildEmojiOptions -> Encoding
$ctoEncoding :: ModifyGuildEmojiOptions -> Encoding
toJSON :: ModifyGuildEmojiOptions -> Value
$ctoJSON :: ModifyGuildEmojiOptions -> Value
Aeson.ToJSON) via CalamityToJSON ModifyGuildEmojiOptions

instance CalamityToJSON' ModifyGuildEmojiOptions where
  toPairs :: forall kv. KeyValue kv => ModifyGuildEmojiOptions -> [Maybe kv]
toPairs ModifyGuildEmojiOptions {[Snowflake Role]
Text
roles :: [Snowflake Role]
name :: Text
$sel:roles:ModifyGuildEmojiOptions :: ModifyGuildEmojiOptions -> [Snowflake Role]
$sel:name:ModifyGuildEmojiOptions :: ModifyGuildEmojiOptions -> Text
..} =
    [ Key
"name" forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Text
name
    , Key
"roles" forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= [Snowflake Role]
roles
    ]

data EmojiRequest a where
  ListGuildEmojis :: (HasID Guild g) => g -> EmojiRequest [Emoji]
  GetGuildEmoji :: (HasID Guild g, HasID Emoji e) => g -> e -> EmojiRequest Emoji
  CreateGuildEmoji :: (HasID Guild g) => g -> CreateGuildEmojiOptions -> EmojiRequest Emoji
  ModifyGuildEmoji :: (HasID Guild g, HasID Emoji e) => g -> e -> ModifyGuildEmojiOptions -> EmojiRequest Emoji
  DeleteGuildEmoji :: (HasID Guild g, HasID Emoji e) => g -> e -> EmojiRequest ()

baseRoute :: Snowflake Guild -> RouteBuilder _
baseRoute :: Snowflake Guild
-> RouteBuilder
     '[ '( 'IDRequirement Guild, 'Satisfied),
        '( 'IDRequirement Guild,
           AddRequiredInner (Lookup ('IDRequirement Guild) '[]))]
baseRoute Snowflake Guild
id = RouteBuilder '[]
mkRouteBuilder forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"guilds" forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall {k} (a :: k). ID a
ID @Guild forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"emojis" forall a b. a -> (a -> b) -> b
& forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Guild
id

instance Request (EmojiRequest a) where
  type Result (EmojiRequest a) = a

  route :: EmojiRequest a -> Route
route (ListGuildEmojis (forall b a. HasID b a => a -> Snowflake b
getID -> Snowflake Guild
gid)) = Snowflake Guild
-> RouteBuilder
     '[ '( 'IDRequirement Guild, 'Satisfied),
        '( 'IDRequirement Guild, 'Required)]
baseRoute Snowflake Guild
gid forall a b. a -> (a -> b) -> b
& forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (GetGuildEmoji (forall b a. HasID b a => a -> Snowflake b
getID -> Snowflake Guild
gid) (forall b a. HasID b a => a -> Snowflake b
getID @Emoji -> Snowflake Emoji
eid)) =
    Snowflake Guild
-> RouteBuilder
     '[ '( 'IDRequirement Guild, 'Satisfied),
        '( 'IDRequirement Guild, 'Required)]
baseRoute Snowflake Guild
gid forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall {k} (a :: k). ID a
ID @Emoji
      forall a b. a -> (a -> b) -> b
& forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Emoji
eid
      forall a b. a -> (a -> b) -> b
& forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (CreateGuildEmoji (forall b a. HasID b a => a -> Snowflake b
getID -> Snowflake Guild
gid) CreateGuildEmojiOptions
_) = Snowflake Guild
-> RouteBuilder
     '[ '( 'IDRequirement Guild, 'Satisfied),
        '( 'IDRequirement Guild, 'Required)]
baseRoute Snowflake Guild
gid forall a b. a -> (a -> b) -> b
& forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (ModifyGuildEmoji (forall b a. HasID b a => a -> Snowflake b
getID -> Snowflake Guild
gid) (forall b a. HasID b a => a -> Snowflake b
getID @Emoji -> Snowflake Emoji
eid) ModifyGuildEmojiOptions
_) =
    Snowflake Guild
-> RouteBuilder
     '[ '( 'IDRequirement Guild, 'Satisfied),
        '( 'IDRequirement Guild, 'Required)]
baseRoute Snowflake Guild
gid forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall {k} (a :: k). ID a
ID @Emoji
      forall a b. a -> (a -> b) -> b
& forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Emoji
eid
      forall a b. a -> (a -> b) -> b
& forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (DeleteGuildEmoji (forall b a. HasID b a => a -> Snowflake b
getID -> Snowflake Guild
gid) (forall b a. HasID b a => a -> Snowflake b
getID @Emoji -> Snowflake Emoji
eid)) =
    Snowflake Guild
-> RouteBuilder
     '[ '( 'IDRequirement Guild, 'Satisfied),
        '( 'IDRequirement Guild, 'Required)]
baseRoute Snowflake Guild
gid forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall {k} (a :: k). ID a
ID @Emoji
      forall a b. a -> (a -> b) -> b
& forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Emoji
eid
      forall a b. a -> (a -> b) -> b
& forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute

  action :: EmojiRequest a -> Url 'Https -> Option 'Https -> Req LbsResponse
action (ListGuildEmojis g
_) = Url 'Https -> Option 'Https -> Req LbsResponse
getWith
  action (GetGuildEmoji g
_ e
_) = Url 'Https -> Option 'Https -> Req LbsResponse
getWith
  action (CreateGuildEmoji g
_ CreateGuildEmojiOptions
o) = forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
postWith' (forall a. a -> ReqBodyJson a
ReqBodyJson CreateGuildEmojiOptions
o)
  action (ModifyGuildEmoji g
_ e
_ ModifyGuildEmojiOptions
o) = forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
patchWith' (forall a. a -> ReqBodyJson a
ReqBodyJson ModifyGuildEmojiOptions
o)
  action (DeleteGuildEmoji g
_ e
_) = Url 'Https -> Option 'Https -> Req LbsResponse
deleteWith

$(makeFieldLabelsNoPrefix ''CreateGuildEmojiOptions)
$(makeFieldLabelsNoPrefix ''ModifyGuildEmojiOptions)