-- | Text channels
module Calamity.Types.Model.Channel.Guild.Text (TextChannel (..)) 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.Channel.Guild.Category
import {-# SOURCE #-} Calamity.Types.Model.Channel.Message
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 Data.Time
import GHC.Generics
import TextShow
import qualified TextShow.Generic as TSG

data TextChannel = TextChannel
  { TextChannel -> Snowflake TextChannel
id :: Snowflake TextChannel
  , TextChannel -> Snowflake Guild
guildID :: Snowflake Guild
  , TextChannel -> Int
position :: Int
  , TextChannel -> SnowflakeMap Overwrite
permissionOverwrites :: SnowflakeMap Overwrite
  , TextChannel -> Text
name :: Text
  , TextChannel -> Maybe Text
topic :: Maybe Text
  , TextChannel -> Bool
nsfw :: Bool
  , TextChannel -> Maybe (Snowflake Message)
lastMessageID :: Maybe (Snowflake Message)
  , TextChannel -> Maybe UTCTime
lastPinTimestamp :: Maybe UTCTime
  , TextChannel -> Maybe Int
rateLimitPerUser :: Maybe Int
  , TextChannel -> Maybe (Snowflake Category)
parentID :: Maybe (Snowflake Category)
  }
  deriving (Int -> TextChannel -> ShowS
[TextChannel] -> ShowS
TextChannel -> String
(Int -> TextChannel -> ShowS)
-> (TextChannel -> String)
-> ([TextChannel] -> ShowS)
-> Show TextChannel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextChannel] -> ShowS
$cshowList :: [TextChannel] -> ShowS
show :: TextChannel -> String
$cshow :: TextChannel -> String
showsPrec :: Int -> TextChannel -> ShowS
$cshowsPrec :: Int -> TextChannel -> ShowS
Show, TextChannel -> TextChannel -> Bool
(TextChannel -> TextChannel -> Bool)
-> (TextChannel -> TextChannel -> Bool) -> Eq TextChannel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextChannel -> TextChannel -> Bool
$c/= :: TextChannel -> TextChannel -> Bool
== :: TextChannel -> TextChannel -> Bool
$c== :: TextChannel -> TextChannel -> Bool
Eq, (forall x. TextChannel -> Rep TextChannel x)
-> (forall x. Rep TextChannel x -> TextChannel)
-> Generic TextChannel
forall x. Rep TextChannel x -> TextChannel
forall x. TextChannel -> Rep TextChannel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextChannel x -> TextChannel
$cfrom :: forall x. TextChannel -> Rep TextChannel x
Generic, TextChannel -> ()
(TextChannel -> ()) -> NFData TextChannel
forall a. (a -> ()) -> NFData a
rnf :: TextChannel -> ()
$crnf :: TextChannel -> ()
NFData)
  deriving (Int -> TextChannel -> Builder
Int -> TextChannel -> Text
Int -> TextChannel -> Text
[TextChannel] -> Builder
[TextChannel] -> Text
[TextChannel] -> Text
TextChannel -> Builder
TextChannel -> Text
TextChannel -> Text
(Int -> TextChannel -> Builder)
-> (TextChannel -> Builder)
-> ([TextChannel] -> Builder)
-> (Int -> TextChannel -> Text)
-> (TextChannel -> Text)
-> ([TextChannel] -> Text)
-> (Int -> TextChannel -> Text)
-> (TextChannel -> Text)
-> ([TextChannel] -> Text)
-> TextShow TextChannel
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 :: [TextChannel] -> Text
$cshowtlList :: [TextChannel] -> Text
showtl :: TextChannel -> Text
$cshowtl :: TextChannel -> Text
showtlPrec :: Int -> TextChannel -> Text
$cshowtlPrec :: Int -> TextChannel -> Text
showtList :: [TextChannel] -> Text
$cshowtList :: [TextChannel] -> Text
showt :: TextChannel -> Text
$cshowt :: TextChannel -> Text
showtPrec :: Int -> TextChannel -> Text
$cshowtPrec :: Int -> TextChannel -> Text
showbList :: [TextChannel] -> Builder
$cshowbList :: [TextChannel] -> Builder
showb :: TextChannel -> Builder
$cshowb :: TextChannel -> Builder
showbPrec :: Int -> TextChannel -> Builder
$cshowbPrec :: Int -> TextChannel -> Builder
TextShow) via TSG.FromGeneric TextChannel
  deriving ([TextChannel] -> Encoding
[TextChannel] -> Value
TextChannel -> Encoding
TextChannel -> Value
(TextChannel -> Value)
-> (TextChannel -> Encoding)
-> ([TextChannel] -> Value)
-> ([TextChannel] -> Encoding)
-> ToJSON TextChannel
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TextChannel] -> Encoding
$ctoEncodingList :: [TextChannel] -> Encoding
toJSONList :: [TextChannel] -> Value
$ctoJSONList :: [TextChannel] -> Value
toEncoding :: TextChannel -> Encoding
$ctoEncoding :: TextChannel -> Encoding
toJSON :: TextChannel -> Value
$ctoJSON :: TextChannel -> Value
ToJSON) via CalamityJSON TextChannel
  deriving
    (Value -> Parser [TextChannel]
Value -> Parser TextChannel
(Value -> Parser TextChannel)
-> (Value -> Parser [TextChannel]) -> FromJSON TextChannel
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TextChannel]
$cparseJSONList :: Value -> Parser [TextChannel]
parseJSON :: Value -> Parser TextChannel
$cparseJSON :: Value -> Parser TextChannel
FromJSON)
    via WithSpecialCases
          '[IfNoneThen "nsfw" DefaultToFalse]
          TextChannel
  deriving (HasID TextChannel) via HasIDField "id" TextChannel
  deriving (HasID Channel) via HasIDFieldCoerce' "id" TextChannel
  deriving (HasID Guild) via HasIDField "guildID" TextChannel