calamity-0.1.4.3: A library for writing discord bots
Safe HaskellNone
LanguageHaskell2010

Calamity.Types.Snowflake

Description

The snowflake type

Synopsis

Documentation

newtype Snowflake t Source #

Constructors

Snowflake 

Instances

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

Defined in Calamity.Types.Snowflake

Methods

getID :: Snowflake a -> Snowflake a Source #

Vector Vector (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Snowflake t) -> m (Vector (Snowflake t))

basicUnsafeThaw :: PrimMonad m => Vector (Snowflake t) -> m (Mutable Vector (PrimState m) (Snowflake t))

basicLength :: Vector (Snowflake t) -> Int

basicUnsafeSlice :: Int -> Int -> Vector (Snowflake t) -> Vector (Snowflake t)

basicUnsafeIndexM :: Monad m => Vector (Snowflake t) -> Int -> m (Snowflake t)

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Snowflake t) -> Vector (Snowflake t) -> m ()

elemseq :: Vector (Snowflake t) -> Snowflake t -> b -> b

MVector MVector (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

basicLength :: MVector s (Snowflake t) -> Int

basicUnsafeSlice :: Int -> Int -> MVector s (Snowflake t) -> MVector s (Snowflake t)

basicOverlaps :: MVector s (Snowflake t) -> MVector s (Snowflake t) -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Snowflake t))

basicInitialize :: PrimMonad m => MVector (PrimState m) (Snowflake t) -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Snowflake t -> m (MVector (PrimState m) (Snowflake t))

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Snowflake t) -> Int -> m (Snowflake t)

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Snowflake t) -> Int -> Snowflake t -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) (Snowflake t) -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) (Snowflake t) -> Snowflake t -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Snowflake t) -> MVector (PrimState m) (Snowflake t) -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Snowflake t) -> MVector (PrimState m) (Snowflake t) -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Snowflake t) -> Int -> m (MVector (PrimState m) (Snowflake t))

Eq (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

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

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

(Typeable t, Typeable k) => 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 #

NFData (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

rnf :: Snowflake t -> () #

FromJSON (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

parseJSON :: Value -> Parser (Snowflake t)

parseJSONList :: Value -> Parser [Snowflake t]

ToJSON (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

toJSON :: Snowflake t -> Value

toEncoding :: Snowflake t -> Encoding

toJSONList :: [Snowflake t] -> Value

toEncodingList :: [Snowflake t] -> Encoding

ToJSONKey (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

toJSONKey :: ToJSONKeyFunction (Snowflake t)

toJSONKeyList :: ToJSONKeyFunction [Snowflake t]

Hashable (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

hashWithSalt :: Int -> Snowflake t -> Int

hash :: Snowflake t -> Int

Unbox (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

TextShow (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

newtype MVector s (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

newtype MVector s (Snowflake t) = MV_Snowflake (MVector s Word64)
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.4.3-inplace" 'True) (C1 ('MetaCons "Snowflake" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromSnowflake") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))
newtype Vector (Snowflake t) Source # 
Instance details

Defined in Calamity.Types.Snowflake

newtype Vector (Snowflake t) = V_Snowflake (Vector Word64)

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 (a :: k) (Snowflake a) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

getID :: Snowflake a -> Snowflake a Source #

(HasID b c, HasField' field a c) => HasID (b :: k) (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 :: k2) (HasIDFieldCoerce field a c) Source # 
Instance details

Defined in Calamity.Types.Snowflake

Methods

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

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 UpdatedMessage Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Message

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 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 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 Category Category Source # 
Instance details

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

HasID Message UpdatedMessage Source # 
Instance details

Defined in Calamity.Types.Model.Channel.Message

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 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 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 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 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 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

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 :: k) (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 :: k2) (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 #