module Calamity.Types.Model.Channel.Guild.Category (Category (..)) where import Calamity.Internal.AesonThings import Calamity.Internal.SnowflakeMap (SnowflakeMap) import Calamity.Internal.Utils () import {-# SOURCE #-} Calamity.Types.Model.Channel import {-# SOURCE #-} Calamity.Types.Model.Guild.Guild import Calamity.Types.Model.Guild.Overwrite import Calamity.Types.Snowflake import Control.DeepSeq (NFData) import Data.Aeson import Data.Text.Lazy (Text) import GHC.Generics import TextShow import qualified TextShow.Generic as TSG data Category = Category { Category -> Snowflake Category id :: Snowflake Category , Category -> SnowflakeMap Overwrite permissionOverwrites :: SnowflakeMap Overwrite , Category -> Text name :: Text , Category -> Bool nsfw :: Bool , Category -> Int position :: Int , Category -> Snowflake Guild guildID :: Snowflake Guild } deriving (Int -> Category -> ShowS [Category] -> ShowS Category -> String (Int -> Category -> ShowS) -> (Category -> String) -> ([Category] -> ShowS) -> Show Category forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Category] -> ShowS $cshowList :: [Category] -> ShowS show :: Category -> String $cshow :: Category -> String showsPrec :: Int -> Category -> ShowS $cshowsPrec :: Int -> Category -> ShowS Show, Category -> Category -> Bool (Category -> Category -> Bool) -> (Category -> Category -> Bool) -> Eq Category forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Category -> Category -> Bool $c/= :: Category -> Category -> Bool == :: Category -> Category -> Bool $c== :: Category -> Category -> Bool Eq, (forall x. Category -> Rep Category x) -> (forall x. Rep Category x -> Category) -> Generic Category forall x. Rep Category x -> Category forall x. Category -> Rep Category x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Category x -> Category $cfrom :: forall x. Category -> Rep Category x Generic, Category -> () (Category -> ()) -> NFData Category forall a. (a -> ()) -> NFData a rnf :: Category -> () $crnf :: Category -> () NFData) deriving (Int -> Category -> Builder Int -> Category -> Text Int -> Category -> Text [Category] -> Builder [Category] -> Text [Category] -> Text Category -> Builder Category -> Text Category -> Text (Int -> Category -> Builder) -> (Category -> Builder) -> ([Category] -> Builder) -> (Int -> Category -> Text) -> (Category -> Text) -> ([Category] -> Text) -> (Int -> Category -> Text) -> (Category -> Text) -> ([Category] -> Text) -> TextShow Category 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 :: [Category] -> Text $cshowtlList :: [Category] -> Text showtl :: Category -> Text $cshowtl :: Category -> Text showtlPrec :: Int -> Category -> Text $cshowtlPrec :: Int -> Category -> Text showtList :: [Category] -> Text $cshowtList :: [Category] -> Text showt :: Category -> Text $cshowt :: Category -> Text showtPrec :: Int -> Category -> Text $cshowtPrec :: Int -> Category -> Text showbList :: [Category] -> Builder $cshowbList :: [Category] -> Builder showb :: Category -> Builder $cshowb :: Category -> Builder showbPrec :: Int -> Category -> Builder $cshowbPrec :: Int -> Category -> Builder TextShow) via TSG.FromGeneric Category deriving ([Category] -> Encoding [Category] -> Value Category -> Encoding Category -> Value (Category -> Value) -> (Category -> Encoding) -> ([Category] -> Value) -> ([Category] -> Encoding) -> ToJSON Category forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [Category] -> Encoding $ctoEncodingList :: [Category] -> Encoding toJSONList :: [Category] -> Value $ctoJSONList :: [Category] -> Value toEncoding :: Category -> Encoding $ctoEncoding :: Category -> Encoding toJSON :: Category -> Value $ctoJSON :: Category -> Value ToJSON) via CalamityJSON Category deriving (Value -> Parser [Category] Value -> Parser Category (Value -> Parser Category) -> (Value -> Parser [Category]) -> FromJSON Category forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a parseJSONList :: Value -> Parser [Category] $cparseJSONList :: Value -> Parser [Category] parseJSON :: Value -> Parser Category $cparseJSON :: Value -> Parser Category FromJSON) via WithSpecialCases '[IfNoneThen "nsfw" DefaultToFalse] Category deriving (HasID Category) via HasIDField "id" Category deriving (HasID Channel) via HasIDFieldCoerce' "id" Category