module Calamity.Types.Model.Voice.VoiceState (VoiceState (..)) where import Calamity.Internal.AesonThings import Calamity.Types.Model.Channel.Guild.Voice 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 Control.DeepSeq (NFData) import TextShow import qualified TextShow.Generic as TSG data VoiceState = VoiceState { VoiceState -> Maybe (Snowflake Guild) guildID :: Maybe (Snowflake Guild) , VoiceState -> Maybe (Snowflake VoiceChannel) channelID :: Maybe (Snowflake VoiceChannel) , VoiceState -> Snowflake User userID :: Snowflake User , VoiceState -> Text sessionID :: Text , VoiceState -> Bool deaf :: Bool , VoiceState -> Bool mute :: Bool , VoiceState -> Bool selfDeaf :: Bool , VoiceState -> Bool selfMute :: Bool , VoiceState -> Bool suppress :: Bool } deriving (Int -> VoiceState -> ShowS [VoiceState] -> ShowS VoiceState -> String (Int -> VoiceState -> ShowS) -> (VoiceState -> String) -> ([VoiceState] -> ShowS) -> Show VoiceState forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [VoiceState] -> ShowS $cshowList :: [VoiceState] -> ShowS show :: VoiceState -> String $cshow :: VoiceState -> String showsPrec :: Int -> VoiceState -> ShowS $cshowsPrec :: Int -> VoiceState -> ShowS Show, VoiceState -> VoiceState -> Bool (VoiceState -> VoiceState -> Bool) -> (VoiceState -> VoiceState -> Bool) -> Eq VoiceState forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: VoiceState -> VoiceState -> Bool $c/= :: VoiceState -> VoiceState -> Bool == :: VoiceState -> VoiceState -> Bool $c== :: VoiceState -> VoiceState -> Bool Eq, (forall x. VoiceState -> Rep VoiceState x) -> (forall x. Rep VoiceState x -> VoiceState) -> Generic VoiceState forall x. Rep VoiceState x -> VoiceState forall x. VoiceState -> Rep VoiceState x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep VoiceState x -> VoiceState $cfrom :: forall x. VoiceState -> Rep VoiceState x Generic, VoiceState -> () (VoiceState -> ()) -> NFData VoiceState forall a. (a -> ()) -> NFData a rnf :: VoiceState -> () $crnf :: VoiceState -> () NFData) deriving (Int -> VoiceState -> Builder Int -> VoiceState -> Text Int -> VoiceState -> Text [VoiceState] -> Builder [VoiceState] -> Text [VoiceState] -> Text VoiceState -> Builder VoiceState -> Text VoiceState -> Text (Int -> VoiceState -> Builder) -> (VoiceState -> Builder) -> ([VoiceState] -> Builder) -> (Int -> VoiceState -> Text) -> (VoiceState -> Text) -> ([VoiceState] -> Text) -> (Int -> VoiceState -> Text) -> (VoiceState -> Text) -> ([VoiceState] -> Text) -> TextShow VoiceState 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 :: [VoiceState] -> Text $cshowtlList :: [VoiceState] -> Text showtl :: VoiceState -> Text $cshowtl :: VoiceState -> Text showtlPrec :: Int -> VoiceState -> Text $cshowtlPrec :: Int -> VoiceState -> Text showtList :: [VoiceState] -> Text $cshowtList :: [VoiceState] -> Text showt :: VoiceState -> Text $cshowt :: VoiceState -> Text showtPrec :: Int -> VoiceState -> Text $cshowtPrec :: Int -> VoiceState -> Text showbList :: [VoiceState] -> Builder $cshowbList :: [VoiceState] -> Builder showb :: VoiceState -> Builder $cshowb :: VoiceState -> Builder showbPrec :: Int -> VoiceState -> Builder $cshowbPrec :: Int -> VoiceState -> Builder TextShow) via TSG.FromGeneric VoiceState deriving ([VoiceState] -> Encoding [VoiceState] -> Value VoiceState -> Encoding VoiceState -> Value (VoiceState -> Value) -> (VoiceState -> Encoding) -> ([VoiceState] -> Value) -> ([VoiceState] -> Encoding) -> ToJSON VoiceState forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [VoiceState] -> Encoding $ctoEncodingList :: [VoiceState] -> Encoding toJSONList :: [VoiceState] -> Value $ctoJSONList :: [VoiceState] -> Value toEncoding :: VoiceState -> Encoding $ctoEncoding :: VoiceState -> Encoding toJSON :: VoiceState -> Value $ctoJSON :: VoiceState -> Value ToJSON, Value -> Parser [VoiceState] Value -> Parser VoiceState (Value -> Parser VoiceState) -> (Value -> Parser [VoiceState]) -> FromJSON VoiceState forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [VoiceState] $cparseJSONList :: Value -> Parser [VoiceState] parseJSON :: Value -> Parser VoiceState $cparseJSON :: Value -> Parser VoiceState FromJSON) via CalamityJSON VoiceState