discord-haskell-1.12.5: Write bots for Discord in Haskell
Safe HaskellNone
LanguageHaskell2010

Discord.Internal.Types.Guild

Description

Types relating to Discord Guilds (servers)

Synopsis

Documentation

data Guild Source #

Guilds in Discord represent a collection of users and channels into an isolated Server

https://discord.com/developers/docs/resources/guild#guild-object

Constructors

Guild 

Fields

Instances

Instances details
Eq Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

(==) :: Guild -> Guild -> Bool #

(/=) :: Guild -> Guild -> Bool #

Ord Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

compare :: Guild -> Guild -> Ordering #

(<) :: Guild -> Guild -> Bool #

(<=) :: Guild -> Guild -> Bool #

(>) :: Guild -> Guild -> Bool #

(>=) :: Guild -> Guild -> Bool #

max :: Guild -> Guild -> Guild #

min :: Guild -> Guild -> Guild #

Read Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

showsPrec :: Int -> Guild -> ShowS #

show :: Guild -> String #

showList :: [Guild] -> ShowS #

FromJSON Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

newtype GuildUnavailable Source #

Constructors

GuildUnavailable 

data Activity Source #

Object for a single activity

https://discord.com/developers/docs/topics/gateway#activity-object

When setting a bot's activity, only the name, url, and type are sent - and it seems that not many types are permitted either.

Constructors

Activity 

Fields

data ActivityTimestamps Source #

Constructors

ActivityTimestamps 

Fields

data ActivityType Source #

Instances

Instances details
Eq ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Data ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ActivityType -> c ActivityType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ActivityType #

toConstr :: ActivityType -> Constr #

dataTypeOf :: ActivityType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ActivityType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ActivityType) #

gmapT :: (forall b. Data b => b -> b) -> ActivityType -> ActivityType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ActivityType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ActivityType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ActivityType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ActivityType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ActivityType -> m ActivityType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ActivityType -> m ActivityType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ActivityType -> m ActivityType #

Ord ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Read ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

FromJSON ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

InternalDiscordEnum ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data Role Source #

Roles represent a set of permissions attached to a group of users. Roles have unique names, colors, and can be "pinned" to the side bar, causing their members to be listed separately. Roles are unique per guild, and can have separate permission profiles for the global context (guild) and channel context.

Constructors

Role 

Fields

Instances

Instances details
Eq Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

(==) :: Role -> Role -> Bool #

(/=) :: Role -> Role -> Bool #

Ord Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

(>=) :: Role -> Role -> Bool #

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

Read Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

FromJSON Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data VoiceRegion Source #

VoiceRegion is only refrenced in Guild endpoints, will be moved when voice support is added

Constructors

VoiceRegion 

Fields

data Invite Source #

Represents a code to add a user to a guild

Constructors

Invite 

Fields

Instances

Instances details
Eq Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

(==) :: Invite -> Invite -> Bool #

(/=) :: Invite -> Invite -> Bool #

Ord Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Read Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

FromJSON Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data InviteWithMeta Source #

Invite code with additional metadata

Instances

Instances details
FromJSON InviteWithMeta Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data InviteMeta Source #

Additional metadata about an invite.

Constructors

InviteMeta 

Fields

data Integration Source #

Represents the behavior of a third party account link.

Constructors

Integration 

Fields

data IntegrationAccount Source #

Represents a third party account link.

Constructors

IntegrationAccount 

Fields

data GuildWidget Source #

Represents an image to be used in third party sites to link to a discord channel

Constructors

GuildWidget 

Fields