calamity-0.1.26.1: A library for writing discord bots in haskell
Safe HaskellNone
LanguageHaskell2010

Calamity.Types.Snowflake

Description

The snowflake type

Synopsis

Documentation

newtype Snowflake (t :: Type) Source #

Constructors

Snowflake 

Instances

Instances details
HasID a (Snowflake a) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

getID :: Snowflake a -> Snowflake a Source #

Upgradeable Channel (Snowflake Channel) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => Snowflake Channel -> Sem r (Maybe Channel) Source #

Upgradeable Category (Snowflake Category) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => Snowflake Category -> Sem r (Maybe Category) Source #

Upgradeable Guild (Snowflake Guild) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => Snowflake Guild -> Sem r (Maybe Guild) Source #

Upgradeable User (Snowflake User) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => Snowflake User -> Sem r (Maybe User) Source #

Upgradeable GroupChannel (Snowflake GroupChannel) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => Snowflake GroupChannel -> Sem r (Maybe GroupChannel) Source #

Upgradeable DMChannel (Snowflake DMChannel) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => Snowflake DMChannel -> Sem r (Maybe DMChannel) Source #

Upgradeable VoiceChannel (Snowflake VoiceChannel) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => Snowflake VoiceChannel -> Sem r (Maybe VoiceChannel) Source #

Upgradeable TextChannel (Snowflake TextChannel) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => Snowflake TextChannel -> Sem r (Maybe TextChannel) Source #

Upgradeable GuildChannel (Snowflake GuildChannel) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => Snowflake GuildChannel -> Sem r (Maybe GuildChannel) Source #

Upgradeable Member (Snowflake Guild, Snowflake Member) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => (Snowflake Guild, Snowflake Member) -> Sem r (Maybe Member) Source #

Upgradeable Role (Snowflake Guild, Snowflake Role) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => (Snowflake Guild, Snowflake Role) -> Sem r (Maybe Role) Source #

Upgradeable Emoji (Snowflake Guild, Snowflake Emoji) Source # 
Instance details

Defined in Calamity.Types.Upgradeable

Methods

upgrade :: forall (r :: [(Type -> Type) -> Type -> Type]). BotC r => (Snowflake Guild, Snowflake Emoji) -> Sem r (Maybe Emoji) Source #

Eq (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

(==) :: Snowflake t -> Snowflake t -> Bool #

(/=) :: Snowflake t -> Snowflake t -> Bool #

Data t => Data (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

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

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

toConstr :: Snowflake t -> Constr #

dataTypeOf :: Snowflake t -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Show (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Generic (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Associated Types

type Rep (Snowflake t) :: Type -> Type #

Methods

from :: Snowflake t -> Rep (Snowflake t) x #

to :: Rep (Snowflake t) x -> Snowflake t #

Hashable (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

hashWithSalt :: Int -> Snowflake t -> Int #

hash :: Snowflake t -> Int #

ToJSON (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

ToJSONKey (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

FromJSON (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

NFData (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

rnf :: Snowflake t -> () #

TextShow (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Unboxable (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Associated Types

type Rep (Snowflake t) #

type CoercibleRep (Snowflake t)

type IsTrivial (Snowflake t) :: Bool

Tellable (Snowflake Channel) Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

getChannel :: forall (r :: [(Type -> Type) -> Type -> Type]). (BotC r, Member (Error RestError) r) => Snowflake Channel -> Sem r (Snowflake Channel) Source #

Tellable (Snowflake Member) Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

getChannel :: forall (r :: [(Type -> Type) -> Type -> Type]). (BotC r, Member0 (Error RestError) r) => Snowflake Member -> Sem r (Snowflake Channel) Source #

Tellable (Snowflake User) Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

getChannel :: forall (r :: [(Type -> Type) -> Type -> Type]). (BotC r, Member (Error RestError) r) => Snowflake User -> Sem r (Snowflake Channel) Source #

Tellable (Snowflake DMChannel) Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

getChannel :: forall (r :: [(Type -> Type) -> Type -> Type]). (BotC r, Member (Error RestError) r) => Snowflake DMChannel -> Sem r (Snowflake Channel) Source #

Tellable (Snowflake TextChannel) Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

getChannel :: forall (r :: [(Type -> Type) -> Type -> Type]). (BotC r, Member (Error RestError) r) => Snowflake TextChannel -> Sem r (Snowflake Channel) Source #

Mentionable (Snowflake Channel) Source # 
Instance details

Defined in Calamity.Utils.Message

Mentionable (Snowflake Category) Source # 
Instance details

Defined in Calamity.Utils.Message

Mentionable (Snowflake Member) Source # 
Instance details

Defined in Calamity.Utils.Message

Mentionable (Snowflake User) Source # 
Instance details

Defined in Calamity.Utils.Message

Mentionable (Snowflake Role) Source # 
Instance details

Defined in Calamity.Utils.Message

Mentionable (Snowflake DMChannel) Source # 
Instance details

Defined in Calamity.Utils.Message

Mentionable (Snowflake VoiceChannel) Source # 
Instance details

Defined in Calamity.Utils.Message

Mentionable (Snowflake TextChannel) Source # 
Instance details

Defined in Calamity.Utils.Message

Mentionable (Snowflake GuildChannel) Source # 
Instance details

Defined in Calamity.Utils.Message

PermissionsIn' (Snowflake Guild) Source #

A Member's Permissions in a guild are just their roles

This will fetch the guild from the cache or http as needed

Instance details

Defined in Calamity.Utils.Permissions

Methods

permissionsIn' :: forall (r :: [(Type -> Type) -> Type -> Type]) u. (BotC r, HasID User u) => Snowflake Guild -> u -> Sem r Permissions Source #

PermissionsIn' (Snowflake GuildChannel) Source #

A Member's Permissions in a channel are their roles and overwrites

This will fetch the guild and channel from the cache or http as needed

Instance details

Defined in Calamity.Utils.Permissions

Methods

permissionsIn' :: forall (r :: [(Type -> Type) -> Type -> Type]) u. (BotC r, HasID User u) => Snowflake GuildChannel -> u -> Sem r Permissions Source #

Typeable (Snowflake a) => Parser (Snowflake a) r Source # 
Instance details

Defined in Calamity.Commands.Parser

Associated Types

type ParserResult (Snowflake a) Source #

Parser (Snowflake Channel) r Source #

Accepts both plain IDs and mentions

Instance details

Defined in Calamity.Commands.Parser

Associated Types

type ParserResult (Snowflake Channel) Source #

Parser (Snowflake Member) r Source #

Accepts both plain IDs and mentions

Instance details

Defined in Calamity.Commands.Parser

Associated Types

type ParserResult (Snowflake Member) Source #

Parser (Snowflake User) r Source #

Accepts both plain IDs and mentions

Instance details

Defined in Calamity.Commands.Parser

Associated Types

type ParserResult (Snowflake User) Source #

Parser (Snowflake Role) r Source #

Accepts both plain IDs and mentions

Instance details

Defined in Calamity.Commands.Parser

Associated Types

type ParserResult (Snowflake Role) Source #

Parser (Snowflake Emoji) r Source #

Accepts both plain IDs and uses of emoji

Instance details

Defined in Calamity.Commands.Parser

Associated Types

type ParserResult (Snowflake Emoji) Source #

type Rep (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

type Rep (Snowflake t) = D1 ('MetaData "Snowflake" "Calamity.Types.Snowflake" "calamity-0.1.26.1-AjA1jEhDhVM6S4JKzuqkqz" 'True) (C1 ('MetaCons "Snowflake" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromSnowflake") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))
type Rep (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

type Rep (Snowflake t) = Rep Word64
type CoercibleRep (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

type CoercibleRep (Snowflake t) = CoercibleRep Word64
type IsTrivial (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

type IsTrivial (Snowflake t) = IsTrivial Word64
type ParserResult (Snowflake a) Source # 
Instance details

Defined in Calamity.Commands.Parser

type ParserResult (Snowflake Channel) Source # 
Instance details

Defined in Calamity.Commands.Parser

type ParserResult (Snowflake Member) Source # 
Instance details

Defined in Calamity.Commands.Parser

type ParserResult (Snowflake User) Source # 
Instance details

Defined in Calamity.Commands.Parser

type ParserResult (Snowflake Role) Source # 
Instance details

Defined in Calamity.Commands.Parser

type ParserResult (Snowflake Emoji) Source # 
Instance details

Defined in Calamity.Commands.Parser

class HasID b a where Source #

A typeclass for types that contain snowflakes of type b

Methods

getID :: a -> Snowflake b Source #

Retrieve the ID from the type

Instances

Instances details
HasID Channel Channel Source # 
Instance details

Defined in Calamity.Types.Model.Channel

HasID Channel Category Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild.Category

HasID Channel Message Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Message

HasID Channel Reaction Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Reaction

HasID Channel GroupChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Group

HasID Channel DMChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.DM

HasID Channel VoiceChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild.Voice

HasID Channel TextChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild.Text

HasID Channel GuildChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild

HasID Channel UpdatedMessage Source # 
Instance details

Defined in Calamity.Types.Model.Channel.UpdatedMessage

HasID Category Category Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild.Category

HasID Message Message Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Message

HasID Message Reaction Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Reaction

HasID Message UpdatedMessage Source # 
Instance details

Defined in Calamity.Types.Model.Channel.UpdatedMessage

HasID Guild UpdatedGuild Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Guild

HasID Guild Guild Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Guild

HasID Guild Member Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Member

HasID Guild VoiceChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild.Voice

HasID Guild TextChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild.Text

HasID Guild GuildChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild

HasID Guild Presence Source # 
Instance details

Defined in Calamity.Types.Model.Presence.Presence

HasID Guild UnavailableGuild Source # 
Instance details

Defined in Calamity.Types.Model.Guild.UnavailableGuild

HasID Guild BanData Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Ban

HasID Member Member Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Member

HasID Member User Source # 
Instance details

Defined in Calamity.Types.Model.User

HasID User Message Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Message

HasID User Member Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Member

HasID User User Source # 
Instance details

Defined in Calamity.Types.Model.User

HasID User Reaction Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Reaction

HasID User GroupChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Group

HasID User AuditLogEntry Source # 
Instance details

Defined in Calamity.Types.Model.Guild.AuditLog

HasID User Presence Source # 
Instance details

Defined in Calamity.Types.Model.Presence.Presence

HasID User BanData Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Ban

HasID Role Role Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Role

HasID Overwrite Overwrite Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Overwrite

HasID Emoji Emoji Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Emoji

HasID Webhook Webhook Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Webhook

HasID GroupChannel GroupChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Group

HasID DMChannel DMChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.DM

HasID Attachment Attachment Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Attachment

HasID VoiceChannel VoiceChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild.Voice

HasID TextChannel TextChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild.Text

HasID GuildChannel GuildChannel Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Guild

HasID AuditLogEntry AuditLogEntry Source # 
Instance details

Defined in Calamity.Types.Model.Guild.AuditLog

HasID a (Snowflake a) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

getID :: Snowflake a -> Snowflake a Source #

HasID Channel (Partial Channel) Source # 
Instance details

Defined in Calamity.Types.Model.Channel

HasID Guild (Partial Guild) Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Guild

HasID User (Partial User) Source # 
Instance details

Defined in Calamity.Types.Model.User

HasID Emoji (Partial Emoji) Source # 
Instance details

Defined in Calamity.Types.Model.Guild.Emoji

(HasID b c, HasField' field a c) => HasID b (HasIDField field a) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

getID :: HasIDField field a -> Snowflake b Source #

(HasID c d, HasField' field a d) => HasID b (HasIDFieldCoerce field a c) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

getID :: HasIDFieldCoerce field a c -> Snowflake b Source #

type HasID' a = HasID a a Source #

newtype HasIDField field a Source #

A newtype wrapper for deriving HasID generically

Constructors

HasIDField a 

Instances

Instances details
(HasID b c, HasField' field a c) => HasID b (HasIDField field a) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

getID :: HasIDField field a -> Snowflake b Source #

newtype HasIDFieldCoerce field a c Source #

A data a which contains an ID of type `Snowflake c` which should be swapped with `Snowflake b` upon fetching

Constructors

HasIDFieldCoerce a 

Instances

Instances details
(HasID c d, HasField' field a d) => HasID b (HasIDFieldCoerce field a c) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

getID :: HasIDFieldCoerce field a c -> Snowflake b Source #

type HasIDFieldCoerce' field a = HasIDFieldCoerce field a a Source #