{-# LANGUAGE TemplateHaskell #-}

-- | Voice channels
module Calamity.Types.Model.Channel.Guild.Voice (VoiceChannel (..)) where

import Calamity.Internal.SnowflakeMap (SnowflakeMap)
import {-# SOURCE #-} Calamity.Types.Model.Channel
import Calamity.Types.Model.Channel.Guild.Category
import {-# SOURCE #-} Calamity.Types.Model.Guild.Guild
import Calamity.Types.Model.Guild.Overwrite
import Calamity.Types.Snowflake
import Data.Aeson ((.:), (.:?))
import qualified Data.Aeson as Aeson
import Data.Text (Text)
import Optics.TH
import TextShow.TH

data VoiceChannel = VoiceChannel
  { VoiceChannel -> Snowflake VoiceChannel
id :: Snowflake VoiceChannel
  , VoiceChannel -> Snowflake Guild
guildID :: Snowflake Guild
  , VoiceChannel -> Int
position :: Int
  , VoiceChannel -> SnowflakeMap Overwrite
permissionOverwrites :: SnowflakeMap Overwrite
  , VoiceChannel -> Text
name :: Text
  , VoiceChannel -> Int
bitrate :: Int
  , VoiceChannel -> Int
userLimit :: Int
  , VoiceChannel -> Maybe (Snowflake Category)
parentID :: Maybe (Snowflake Category)
  }
  deriving (Int -> VoiceChannel -> ShowS
[VoiceChannel] -> ShowS
VoiceChannel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VoiceChannel] -> ShowS
$cshowList :: [VoiceChannel] -> ShowS
show :: VoiceChannel -> String
$cshow :: VoiceChannel -> String
showsPrec :: Int -> VoiceChannel -> ShowS
$cshowsPrec :: Int -> VoiceChannel -> ShowS
Show, VoiceChannel -> VoiceChannel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VoiceChannel -> VoiceChannel -> Bool
$c/= :: VoiceChannel -> VoiceChannel -> Bool
== :: VoiceChannel -> VoiceChannel -> Bool
$c== :: VoiceChannel -> VoiceChannel -> Bool
Eq)
  deriving (HasID VoiceChannel) via HasIDField "id" VoiceChannel
  deriving (HasID Channel) via HasIDFieldCoerce' "id" VoiceChannel
  deriving (HasID Guild) via HasIDField "guildID" VoiceChannel

instance Aeson.FromJSON VoiceChannel where
  parseJSON :: Value -> Parser VoiceChannel
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"TextChannel" forall a b. (a -> b) -> a -> b
$ \Object
v ->
    Snowflake VoiceChannel
-> Snowflake Guild
-> Int
-> SnowflakeMap Overwrite
-> Text
-> Int
-> Int
-> Maybe (Snowflake Category)
-> VoiceChannel
VoiceChannel
      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
"guild_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
"position"
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"permission_overwrites"
      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 a
.: Key
"bitrate"
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user_limit"
      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
"parent_id"

$(deriveTextShow ''VoiceChannel)
$(makeFieldLabelsNoPrefix ''VoiceChannel)