Copyright | (c) Yuto Takano (2021) |
---|---|
License | MIT |
Maintainer | moa17stock@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
Discord.Internal.Types.VoiceCommon
Description
WARNING
This module is considered internal.
The Package Versioning Policy does not apply.
The contents of this module may change in any way whatsoever and without any warning between minor versions of this package.
Description
This module defines the types for handles, errors, base monads, and other types applicable to both the UPD and Websocket components of the Voice API. Many of the structures defined in this module have Lenses derived for them using Template Haskell.
Synopsis
- newtype Voice a = Voice {}
- data VoiceError
- data SubprocessException = SubprocessException String
- data DiscordVoiceHandle = DiscordVoiceHandle {}
- data DiscordBroadcastHandle = DiscordBroadcastHandle {}
- data VoiceWebsocketException
- type VoiceWebsocketReceiveChan = Chan (Either VoiceWebsocketException VoiceWebsocketReceivable)
- type VoiceWebsocketSendChan = Chan VoiceWebsocketSendable
- type VoiceUDPReceiveChan = Chan VoiceUDPPacket
- type VoiceUDPSendChan = BoundedChan ByteString
- data WebsocketLaunchOpts = WebsocketLaunchOpts {
- websocketLaunchOptsBotUserId :: UserId
- websocketLaunchOptsSessionId :: Text
- websocketLaunchOptsToken :: Text
- websocketLaunchOptsGuildId :: GuildId
- websocketLaunchOptsEndpoint :: Text
- websocketLaunchOptsWsHandle :: (VoiceWebsocketReceiveChan, VoiceWebsocketSendChan)
- websocketLaunchOptsUdpTid :: MVar (Weak ThreadId)
- websocketLaunchOptsUdpHandle :: (VoiceUDPReceiveChan, VoiceUDPSendChan)
- websocketLaunchOptsSsrc :: MVar Integer
- data WebsocketConn = WebsocketConn {}
- data UDPLaunchOpts = UDPLaunchOpts {}
- data UDPConn = UDPConn {}
- class HasChannelId s a | s -> a where
- class HasGuildId s a | s -> a where
- class HasSsrc s a | s -> a where
- class HasUdp s a | s -> a where
- class HasWebsocket s a | s -> a where
- class HasMutEx s a | s -> a where
- class HasVoiceHandles s a | s -> a where
- voiceHandles :: Lens' s a
- class HasBotUserId s a | s -> a where
- class HasEndpoint s a | s -> a where
- class HasSessionId s a | s -> a where
- class HasToken s a | s -> a where
- class HasUdpHandle s a | s -> a where
- class HasUdpTid s a | s -> a where
- class HasWsHandle s a | s -> a where
- class HasConnection s a | s -> a where
- connection :: Lens' s a
- class HasLaunchOpts s a | s -> a where
- launchOpts :: Lens' s a
- class HasIp s a | s -> a where
- class HasMode s a | s -> a where
- class HasPort s a | s -> a where
- class HasSecretKey s a | s -> a where
- class HasSocket s a | s -> a where
Documentation
Voice
is a newtype Monad containing a composition of ReaderT and ExceptT
transformers over the DiscordHandler
monad. It holds references to
voice connections/threads. The content of the reader handle is strictly
internal and is hidden deliberately behind the newtype wrapper.
Developer Note: ExceptT is on the base rather than ReaderT, so that when a
critical exception/error occurs in Voice
, it can propagate down the
transformer stack, kill the threads referenced in the Reader state as
necessary, and halt the entire computation and return to DiscordHandler
.
If ExceptT were on top of ReaderT, then errors would be swallowed before it
propagates below ReaderT, and the monad would not halt there, continuing
computation with an unstable state.
Constructors
Voice | |
Fields |
Instances
data VoiceError Source #
VoiceError
represents the potential errors when initialising a voice
connection. It does not account for errors that occur after the initial
handshake (technically, because they are in IO and not ExceptT).
Constructors
VoiceNotAvailable | |
NoServerAvailable | |
InvalidPayloadOrder |
Instances
Eq VoiceError Source # | |
Defined in Discord.Internal.Types.VoiceCommon | |
Show VoiceError Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods showsPrec :: Int -> VoiceError -> ShowS # show :: VoiceError -> String # showList :: [VoiceError] -> ShowS # | |
MonadError VoiceError Voice Source # | MonadError is for internal use, to propagate errors. |
Defined in Discord.Internal.Types.VoiceCommon Methods throwError :: VoiceError -> Voice a # catchError :: Voice a -> (VoiceError -> Voice a) -> Voice a # |
data SubprocessException Source #
SubprocessException
is an Exception that may be thrown when a subprocess
such as FFmpeg encounters an error.
TODO: This has never actually been seen, so it's untested whether it works.
Constructors
SubprocessException String |
Instances
Eq SubprocessException Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods (==) :: SubprocessException -> SubprocessException -> Bool # (/=) :: SubprocessException -> SubprocessException -> Bool # | |
Show SubprocessException Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods showsPrec :: Int -> SubprocessException -> ShowS # show :: SubprocessException -> String # showList :: [SubprocessException] -> ShowS # | |
Exception SubprocessException Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods toException :: SubprocessException -> SomeException # fromException :: SomeException -> Maybe SubprocessException # |
data DiscordVoiceHandle Source #
DiscordVoiceHandle
represents the handles for a single voice connection
(to a specific voice channel).
Lenses are defined for this type using Template Haskell.
Constructors
DiscordVoiceHandle | |
Fields
|
Instances
data DiscordBroadcastHandle Source #
DiscordBroadcastHandle
represents a "stream" or a "broadcast", which is
a mutable list of voice connection handles that share the same audio stream.
Lenses are defined for this type using Template Haskell.
Constructors
DiscordBroadcastHandle | |
Fields
|
Instances
MonadReader DiscordBroadcastHandle Voice Source # | MonadReader is for internal use, to read the held broadcast handle. |
Defined in Discord.Internal.Types.VoiceCommon Methods ask :: Voice DiscordBroadcastHandle # local :: (DiscordBroadcastHandle -> DiscordBroadcastHandle) -> Voice a -> Voice a # reader :: (DiscordBroadcastHandle -> a) -> Voice a # | |
HasVoiceHandles DiscordBroadcastHandle (MVar [DiscordVoiceHandle]) Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods voiceHandles :: Lens' DiscordBroadcastHandle (MVar [DiscordVoiceHandle]) Source # | |
HasMutEx DiscordBroadcastHandle (MVar ()) Source # | |
Defined in Discord.Internal.Types.VoiceCommon |
data VoiceWebsocketException Source #
Deprecated. TODO: remove, unused
Constructors
VoiceWebsocketCouldNotConnect Text | |
VoiceWebsocketEventParseError Text | |
VoiceWebsocketUnexpected VoiceWebsocketReceivable Text | |
VoiceWebsocketConnection ConnectionException Text |
Instances
type VoiceWebsocketReceiveChan = Chan (Either VoiceWebsocketException VoiceWebsocketReceivable) Source #
type VoiceUDPReceiveChan = Chan VoiceUDPPacket Source #
type VoiceUDPSendChan = BoundedChan ByteString Source #
data WebsocketLaunchOpts Source #
WebsocketLaunchOpts
represents all the data necessary to start a
Websocket connection to Discord's Voice Gateway.
Lenses are defined for this type using Template Haskell.
Constructors
Instances
data WebsocketConn Source #
WebsocketConn
represents an active connection to Discord's Voice Gateway
websocket, and contains the Connection as well as the options that launched
it.
Lenses are defined for this type using Template Haskell.
Constructors
WebsocketConn | |
Instances
HasLaunchOpts WebsocketConn WebsocketLaunchOpts Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods launchOpts :: Lens' WebsocketConn WebsocketLaunchOpts Source # | |
HasConnection WebsocketConn Connection Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods |
data UDPLaunchOpts Source #
UDPLaunchOpts
represents all the data necessary to start a UDP connection
to Discord. Field names for this ADT are cased weirdly because I want to keep
the UDP part uppercase in the type and data constructor. Since field
accessors are rarely used anyway (lenses are preferred instead), we can
write the field prefixes as "uDP" and take advantage of Lenses as normal.
Lenses are defined for this type using Template Haskell.
Constructors
UDPLaunchOpts | |
Instances
HasSsrc UDPLaunchOpts Integer Source # | |
Defined in Discord.Internal.Types.VoiceCommon | |
HasLaunchOpts UDPConn UDPLaunchOpts Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods | |
HasPort UDPLaunchOpts Integer Source # | |
Defined in Discord.Internal.Types.VoiceCommon | |
HasMode UDPLaunchOpts Text Source # | |
Defined in Discord.Internal.Types.VoiceCommon | |
HasIp UDPLaunchOpts Text Source # | |
Defined in Discord.Internal.Types.VoiceCommon | |
HasSecretKey UDPLaunchOpts (MVar [Word8]) Source # | |
Defined in Discord.Internal.Types.VoiceCommon | |
HasUdpHandle UDPLaunchOpts (VoiceUDPReceiveChan, VoiceUDPSendChan) Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods udpHandle :: Lens' UDPLaunchOpts (VoiceUDPReceiveChan, VoiceUDPSendChan) Source # |
UDPConn
represents an active UDP connection to Discord, and contains the
Socket as well as the options that launched it.
Lenses are defined for this type using Template Haskell.
Constructors
UDPConn | |
Fields |
Instances
HasLaunchOpts UDPConn UDPLaunchOpts Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods | |
HasSocket UDPConn Socket Source # | |
class HasChannelId s a | s -> a where Source #
Instances
class HasGuildId s a | s -> a where Source #
Instances
class HasSsrc s a | s -> a where Source #
Instances
class HasUdp s a | s -> a where Source #
Instances
HasUdp DiscordVoiceHandle (Weak ThreadId, (VoiceUDPReceiveChan, VoiceUDPSendChan)) Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods udp :: Lens' DiscordVoiceHandle (Weak ThreadId, (VoiceUDPReceiveChan, VoiceUDPSendChan)) Source # |
class HasWebsocket s a | s -> a where Source #
Instances
class HasMutEx s a | s -> a where Source #
Instances
HasMutEx DiscordBroadcastHandle (MVar ()) Source # | |
Defined in Discord.Internal.Types.VoiceCommon |
class HasVoiceHandles s a | s -> a where Source #
Methods
voiceHandles :: Lens' s a Source #
Instances
HasVoiceHandles DiscordBroadcastHandle (MVar [DiscordVoiceHandle]) Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods voiceHandles :: Lens' DiscordBroadcastHandle (MVar [DiscordVoiceHandle]) Source # |
class HasBotUserId s a | s -> a where Source #
Instances
class HasEndpoint s a | s -> a where Source #
Instances
class HasSessionId s a | s -> a where Source #
Instances
class HasToken s a | s -> a where Source #
Instances
class HasUdpHandle s a | s -> a where Source #
Instances
class HasWsHandle s a | s -> a where Source #
class HasConnection s a | s -> a where Source #
Methods
connection :: Lens' s a Source #
Instances
HasConnection WebsocketConn Connection Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods |
class HasLaunchOpts s a | s -> a where Source #
Methods
launchOpts :: Lens' s a Source #
Instances
HasLaunchOpts UDPConn UDPLaunchOpts Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods | |
HasLaunchOpts WebsocketConn WebsocketLaunchOpts Source # | |
Defined in Discord.Internal.Types.VoiceCommon Methods launchOpts :: Lens' WebsocketConn WebsocketLaunchOpts Source # |
class HasIp s a | s -> a where Source #
Instances
HasIp UDPLaunchOpts Text Source # | |
Defined in Discord.Internal.Types.VoiceCommon |
class HasMode s a | s -> a where Source #
Instances
class HasPort s a | s -> a where Source #
Instances
class HasSecretKey s a | s -> a where Source #
Instances
HasSecretKey UDPLaunchOpts (MVar [Word8]) Source # | |
Defined in Discord.Internal.Types.VoiceCommon |