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

Calamity.Types.Tellable

Description

Things that are messageable

Synopsis

Documentation

class ToMessage a where Source #

Things that can be used to send a message

Can be used to compose text, embeds, and files. e.g.

intoMsg Text "A message" <> intoMsg Embed (def & #description ?~ "Embed description")

Methods

intoMsg :: a -> Endo CreateMessageOptions Source #

Turn a into a CreateMessageOptions builder

Instances

Instances details
ToMessage String Source #

Message content, (<>) concatenates the content

Instance details

Defined in Calamity.Types.Tellable

ToMessage Text Source #

Message content, (<>) concatenates the content

Instance details

Defined in Calamity.Types.Tellable

ToMessage Text Source #

Message content, (<>) concatenates the content

Instance details

Defined in Calamity.Types.Tellable

ToMessage Embed Source #

Message embed, (<>) merges embeds using (<>)

Instance details

Defined in Calamity.Types.Tellable

ToMessage AllowedMentions Source #

Allowed mentions, (<>) combines allowed mentions

Instance details

Defined in Calamity.Types.Tellable

ToMessage CreateMessageOptions Source # 
Instance details

Defined in Calamity.Types.Tellable

ToMessage TFile Source #

Message file, (<>) keeps the last added file

Instance details

Defined in Calamity.Types.Tellable

ToMessage (Endo CreateMessageOptions) Source # 
Instance details

Defined in Calamity.Types.Tellable

ToMessage (TMention Member) Source #

Add a Member id to the list of allowed user mentions

Instance details

Defined in Calamity.Types.Tellable

ToMessage (TMention User) Source #

Add a User id to the list of allowed user mentions

Instance details

Defined in Calamity.Types.Tellable

ToMessage (TMention Role) Source #

Add a Role id to the list of allowed role mentions

Instance details

Defined in Calamity.Types.Tellable

ToMessage (CreateMessageOptions -> CreateMessageOptions) Source # 
Instance details

Defined in Calamity.Types.Tellable

class Tellable a where Source #

Methods

getChannel :: (BotC r, Member (Error RestError) r) => a -> Sem r (Snowflake Channel) Source #

Instances

Instances details
Tellable Context Source # 
Instance details

Defined in Calamity.Commands.Context

Methods

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

Tellable Channel Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

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

Tellable Message Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

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

Tellable Member Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

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

Tellable User Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

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

Tellable DMChannel Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

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

Tellable TextChannel Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

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

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 #

newtype TFile Source #

A wrapper type for sending files

Constructors

TFile ByteString 

Instances

Instances details
Show TFile Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

showsPrec :: Int -> TFile -> ShowS #

show :: TFile -> String #

showList :: [TFile] -> ShowS #

Generic TFile Source # 
Instance details

Defined in Calamity.Types.Tellable

Associated Types

type Rep TFile :: Type -> Type #

Methods

from :: TFile -> Rep TFile x #

to :: Rep TFile x -> TFile #

ToMessage TFile Source #

Message file, (<>) keeps the last added file

Instance details

Defined in Calamity.Types.Tellable

type Rep TFile Source # 
Instance details

Defined in Calamity.Types.Tellable

type Rep TFile = D1 ('MetaData "TFile" "Calamity.Types.Tellable" "calamity-0.1.14.5-inplace" 'True) (C1 ('MetaCons "TFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype TMention a Source #

A wrapper type for allowing mentions

Constructors

TMention (Snowflake a) 

Instances

Instances details
Show (TMention a) Source # 
Instance details

Defined in Calamity.Types.Tellable

Methods

showsPrec :: Int -> TMention a -> ShowS #

show :: TMention a -> String #

showList :: [TMention a] -> ShowS #

Generic (TMention a) Source # 
Instance details

Defined in Calamity.Types.Tellable

Associated Types

type Rep (TMention a) :: Type -> Type #

Methods

from :: TMention a -> Rep (TMention a) x #

to :: Rep (TMention a) x -> TMention a #

ToMessage (TMention Member) Source #

Add a Member id to the list of allowed user mentions

Instance details

Defined in Calamity.Types.Tellable

ToMessage (TMention User) Source #

Add a User id to the list of allowed user mentions

Instance details

Defined in Calamity.Types.Tellable

ToMessage (TMention Role) Source #

Add a Role id to the list of allowed role mentions

Instance details

Defined in Calamity.Types.Tellable

type Rep (TMention a) Source # 
Instance details

Defined in Calamity.Types.Tellable

type Rep (TMention a) = D1 ('MetaData "TMention" "Calamity.Types.Tellable" "calamity-0.1.14.5-inplace" 'True) (C1 ('MetaCons "TMention" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Snowflake a))))

tell :: forall msg r t. (BotC r, ToMessage msg, Tellable t) => t -> msg -> Sem r (Either RestError Message) Source #

Send a message to something that is messageable

To send a string literal you'll probably want to use TypeApplication to specify the type of msg

Examples

Sending a string:

void $ tell @Text m ("Somebody told me to tell you about: " <> s)