sdl2-2.5.2.0: Both high- and low-level bindings to the SDL library (version 2.0.6+).
Safe HaskellNone
LanguageHaskell2010

SDL.Audio

Description

SDL.Audio provides a high-level API to SDL's audio device capabilities.

Synopsis

Managing AudioDevices

data AudioDevice Source #

An open audio device. These can be created via openAudioDevice and should be closed with closeAudioDevice

Instances

Instances details
Eq AudioDevice Source # 
Instance details

Defined in SDL.Audio

Methods

(==) :: AudioDevice -> AudioDevice -> Bool

(/=) :: AudioDevice -> AudioDevice -> Bool

Opening and Closing AudioDevices

openAudioDevice :: MonadIO m => OpenDeviceSpec -> m (AudioDevice, AudioSpec) Source #

Attempt to open the closest matching AudioDevice, as specified by the given OpenDeviceSpec.

See SDL_OpenAudioDevice for C documentation.

closeAudioDevice :: MonadIO m => AudioDevice -> m () Source #

See SDL_CloseAudioDevice for C documentation.

data OpenDeviceSpec Source #

A specification to openAudioDevice, indicating the desired output format. Note that many of these properties are Changeable, meaning that you can choose whether or not SDL should interpret your specification as an unbreakable request (Mandate), or as an approximation Desire.

Constructors

forall sampleType. OpenDeviceSpec 

Fields

data AudioDeviceUsage Source #

How you intend to use an AudioDevice

Constructors

ForPlayback

The device will be used for sample playback.

ForCapture

The device will be used for sample capture.

Instances

Instances details
Bounded AudioDeviceUsage Source # 
Instance details

Defined in SDL.Audio

Enum AudioDeviceUsage Source # 
Instance details

Defined in SDL.Audio

Eq AudioDeviceUsage Source # 
Instance details

Defined in SDL.Audio

Data AudioDeviceUsage Source # 
Instance details

Defined in SDL.Audio

Methods

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

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

toConstr :: AudioDeviceUsage -> Constr

dataTypeOf :: AudioDeviceUsage -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> AudioDeviceUsage -> AudioDeviceUsage

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

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

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

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

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

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

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

Ord AudioDeviceUsage Source # 
Instance details

Defined in SDL.Audio

Read AudioDeviceUsage Source # 
Instance details

Defined in SDL.Audio

Show AudioDeviceUsage Source # 
Instance details

Defined in SDL.Audio

Methods

showsPrec :: Int -> AudioDeviceUsage -> ShowS

show :: AudioDeviceUsage -> String

showList :: [AudioDeviceUsage] -> ShowS

Generic AudioDeviceUsage Source # 
Instance details

Defined in SDL.Audio

Associated Types

type Rep AudioDeviceUsage :: Type -> Type

type Rep AudioDeviceUsage Source # 
Instance details

Defined in SDL.Audio

type Rep AudioDeviceUsage = D1 ('MetaData "AudioDeviceUsage" "SDL.Audio" "sdl2-2.5.2.0-Cx4Ipj2keSJFpflqvJYEGr" 'False) (C1 ('MetaCons "ForPlayback" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ForCapture" 'PrefixI 'False) (U1 :: Type -> Type))

data Channels Source #

How many channels audio should be played on

Constructors

Mono

A single speaker configuration

Stereo

A traditional left/right stereo system

Quad 
FivePointOne
  1. 1 surround sound

Instances

Instances details
Bounded Channels Source # 
Instance details

Defined in SDL.Audio

Enum Channels Source # 
Instance details

Defined in SDL.Audio

Eq Channels Source # 
Instance details

Defined in SDL.Audio

Methods

(==) :: Channels -> Channels -> Bool

(/=) :: Channels -> Channels -> Bool

Data Channels Source # 
Instance details

Defined in SDL.Audio

Methods

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

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

toConstr :: Channels -> Constr

dataTypeOf :: Channels -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> Channels -> Channels

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

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

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

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

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

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

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

Ord Channels Source # 
Instance details

Defined in SDL.Audio

Methods

compare :: Channels -> Channels -> Ordering

(<) :: Channels -> Channels -> Bool

(<=) :: Channels -> Channels -> Bool

(>) :: Channels -> Channels -> Bool

(>=) :: Channels -> Channels -> Bool

max :: Channels -> Channels -> Channels

min :: Channels -> Channels -> Channels

Read Channels Source # 
Instance details

Defined in SDL.Audio

Methods

readsPrec :: Int -> ReadS Channels

readList :: ReadS [Channels]

readPrec :: ReadPrec Channels

readListPrec :: ReadPrec [Channels]

Show Channels Source # 
Instance details

Defined in SDL.Audio

Methods

showsPrec :: Int -> Channels -> ShowS

show :: Channels -> String

showList :: [Channels] -> ShowS

Generic Channels Source # 
Instance details

Defined in SDL.Audio

Associated Types

type Rep Channels :: Type -> Type

Methods

from :: Channels -> Rep Channels x

to :: Rep Channels x -> Channels

type Rep Channels Source # 
Instance details

Defined in SDL.Audio

type Rep Channels = D1 ('MetaData "Channels" "SDL.Audio" "sdl2-2.5.2.0-Cx4Ipj2keSJFpflqvJYEGr" 'False) ((C1 ('MetaCons "Mono" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Stereo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Quad" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FivePointOne" 'PrefixI 'False) (U1 :: Type -> Type)))

data Changeable a Source #

Used to indicate to SDL whether it is allowed to open other audio devices (if a property is marked as a Desire) or if it should fail if the device is unavailable (Mandate).

Constructors

Mandate !a

Mandate this exact property value, and fail if a matching audio device cannot be found.

Desire !a

Desire this property value, but allow other audio devices to be opened.

Instances

Instances details
Functor Changeable Source # 
Instance details

Defined in SDL.Audio

Methods

fmap :: (a -> b) -> Changeable a -> Changeable b

(<$) :: a -> Changeable b -> Changeable a

Foldable Changeable Source # 
Instance details

Defined in SDL.Audio

Methods

fold :: Monoid m => Changeable m -> m

foldMap :: Monoid m => (a -> m) -> Changeable a -> m

foldMap' :: Monoid m => (a -> m) -> Changeable a -> m

foldr :: (a -> b -> b) -> b -> Changeable a -> b

foldr' :: (a -> b -> b) -> b -> Changeable a -> b

foldl :: (b -> a -> b) -> b -> Changeable a -> b

foldl' :: (b -> a -> b) -> b -> Changeable a -> b

foldr1 :: (a -> a -> a) -> Changeable a -> a

foldl1 :: (a -> a -> a) -> Changeable a -> a

toList :: Changeable a -> [a]

null :: Changeable a -> Bool

length :: Changeable a -> Int

elem :: Eq a => a -> Changeable a -> Bool

maximum :: Ord a => Changeable a -> a

minimum :: Ord a => Changeable a -> a

sum :: Num a => Changeable a -> a

product :: Num a => Changeable a -> a

Traversable Changeable Source # 
Instance details

Defined in SDL.Audio

Methods

traverse :: Applicative f => (a -> f b) -> Changeable a -> f (Changeable b)

sequenceA :: Applicative f => Changeable (f a) -> f (Changeable a)

mapM :: Monad m => (a -> m b) -> Changeable a -> m (Changeable b)

sequence :: Monad m => Changeable (m a) -> m (Changeable a)

Eq a => Eq (Changeable a) Source # 
Instance details

Defined in SDL.Audio

Methods

(==) :: Changeable a -> Changeable a -> Bool

(/=) :: Changeable a -> Changeable a -> Bool

Data a => Data (Changeable a) Source # 
Instance details

Defined in SDL.Audio

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Changeable a -> c (Changeable a)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Changeable a)

toConstr :: Changeable a -> Constr

dataTypeOf :: Changeable a -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Changeable a))

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

gmapT :: (forall b. Data b => b -> b) -> Changeable a -> Changeable a

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Changeable a -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Changeable a -> r

gmapQ :: (forall d. Data d => d -> u) -> Changeable a -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Changeable a -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Changeable a -> m (Changeable a)

Read a => Read (Changeable a) Source # 
Instance details

Defined in SDL.Audio

Methods

readsPrec :: Int -> ReadS (Changeable a)

readList :: ReadS [Changeable a]

readPrec :: ReadPrec (Changeable a)

readListPrec :: ReadPrec [Changeable a]

Show a => Show (Changeable a) Source # 
Instance details

Defined in SDL.Audio

Methods

showsPrec :: Int -> Changeable a -> ShowS

show :: Changeable a -> String

showList :: [Changeable a] -> ShowS

Generic (Changeable a) Source # 
Instance details

Defined in SDL.Audio

Associated Types

type Rep (Changeable a) :: Type -> Type

Methods

from :: Changeable a -> Rep (Changeable a) x

to :: Rep (Changeable a) x -> Changeable a

type Rep (Changeable a) Source # 
Instance details

Defined in SDL.Audio

type Rep (Changeable a) = D1 ('MetaData "Changeable" "SDL.Audio" "sdl2-2.5.2.0-Cx4Ipj2keSJFpflqvJYEGr" 'False) (C1 ('MetaCons "Mandate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "Desire" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))

Working with Opened Devices

Locking AudioDevices

setAudioDeviceLocked :: MonadIO m => AudioDevice -> LockState -> m () Source #

Lock an AudioDevice such that its associated callback will not be called until the device is unlocked.

data LockState Source #

Whether a device should be locked or unlocked.

Constructors

Locked

Lock the device, preventing the callback from producing data.

Unlocked

Unlock the device, resuming calls to the callback.

Instances

Instances details
Bounded LockState Source # 
Instance details

Defined in SDL.Audio

Enum LockState Source # 
Instance details

Defined in SDL.Audio

Eq LockState Source # 
Instance details

Defined in SDL.Audio

Methods

(==) :: LockState -> LockState -> Bool

(/=) :: LockState -> LockState -> Bool

Data LockState Source # 
Instance details

Defined in SDL.Audio

Methods

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

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

toConstr :: LockState -> Constr

dataTypeOf :: LockState -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> LockState -> LockState

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

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

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

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

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

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

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

Ord LockState Source # 
Instance details

Defined in SDL.Audio

Methods

compare :: LockState -> LockState -> Ordering

(<) :: LockState -> LockState -> Bool

(<=) :: LockState -> LockState -> Bool

(>) :: LockState -> LockState -> Bool

(>=) :: LockState -> LockState -> Bool

max :: LockState -> LockState -> LockState

min :: LockState -> LockState -> LockState

Read LockState Source # 
Instance details

Defined in SDL.Audio

Methods

readsPrec :: Int -> ReadS LockState

readList :: ReadS [LockState]

readPrec :: ReadPrec LockState

readListPrec :: ReadPrec [LockState]

Show LockState Source # 
Instance details

Defined in SDL.Audio

Methods

showsPrec :: Int -> LockState -> ShowS

show :: LockState -> String

showList :: [LockState] -> ShowS

Generic LockState Source # 
Instance details

Defined in SDL.Audio

Associated Types

type Rep LockState :: Type -> Type

Methods

from :: LockState -> Rep LockState x

to :: Rep LockState x -> LockState

type Rep LockState Source # 
Instance details

Defined in SDL.Audio

type Rep LockState = D1 ('MetaData "LockState" "SDL.Audio" "sdl2-2.5.2.0-Cx4Ipj2keSJFpflqvJYEGr" 'False) (C1 ('MetaCons "Locked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unlocked" 'PrefixI 'False) (U1 :: Type -> Type))

Switching Playback States

data PlaybackState Source #

Whether to allow an AudioDevice to play sound or remain paused.

Constructors

Pause

Pause the AudioDevice, which will stop producing/capturing audio.

Play

Resume the AudioDevice.

Instances

Instances details
Bounded PlaybackState Source # 
Instance details

Defined in SDL.Audio

Enum PlaybackState Source # 
Instance details

Defined in SDL.Audio

Eq PlaybackState Source # 
Instance details

Defined in SDL.Audio

Data PlaybackState Source # 
Instance details

Defined in SDL.Audio

Methods

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

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

toConstr :: PlaybackState -> Constr

dataTypeOf :: PlaybackState -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> PlaybackState -> PlaybackState

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

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

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

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

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

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

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

Ord PlaybackState Source # 
Instance details

Defined in SDL.Audio

Read PlaybackState Source # 
Instance details

Defined in SDL.Audio

Methods

readsPrec :: Int -> ReadS PlaybackState

readList :: ReadS [PlaybackState]

readPrec :: ReadPrec PlaybackState

readListPrec :: ReadPrec [PlaybackState]

Show PlaybackState Source # 
Instance details

Defined in SDL.Audio

Methods

showsPrec :: Int -> PlaybackState -> ShowS

show :: PlaybackState -> String

showList :: [PlaybackState] -> ShowS

Generic PlaybackState Source # 
Instance details

Defined in SDL.Audio

Associated Types

type Rep PlaybackState :: Type -> Type

type Rep PlaybackState Source # 
Instance details

Defined in SDL.Audio

type Rep PlaybackState = D1 ('MetaData "PlaybackState" "SDL.Audio" "sdl2-2.5.2.0-Cx4Ipj2keSJFpflqvJYEGr" 'False) (C1 ('MetaCons "Pause" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Play" 'PrefixI 'False) (U1 :: Type -> Type))

setAudioDevicePlaybackState :: MonadIO m => AudioDevice -> PlaybackState -> m () Source #

Change the playback state of an AudioDevice.

Querying an AudioDevices Status.

data AudioDeviceStatus Source #

Opened devices are always Playing or Paused in normal circumstances. A failing device may change its status to Stopped at any time, and closing a device will progress to Stopped too.

Constructors

Playing

The AudioDevice is playing.

Paused

The AudioDevice is paused.

Stopped

The AudioDevice is stopped.

Instances

Instances details
Bounded AudioDeviceStatus Source # 
Instance details

Defined in SDL.Audio

Enum AudioDeviceStatus Source # 
Instance details

Defined in SDL.Audio

Eq AudioDeviceStatus Source # 
Instance details

Defined in SDL.Audio

Data AudioDeviceStatus Source # 
Instance details

Defined in SDL.Audio

Methods

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

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

toConstr :: AudioDeviceStatus -> Constr

dataTypeOf :: AudioDeviceStatus -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> AudioDeviceStatus -> AudioDeviceStatus

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

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

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

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

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

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

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

Ord AudioDeviceStatus Source # 
Instance details

Defined in SDL.Audio

Read AudioDeviceStatus Source # 
Instance details

Defined in SDL.Audio

Show AudioDeviceStatus Source # 
Instance details

Defined in SDL.Audio

Methods

showsPrec :: Int -> AudioDeviceStatus -> ShowS

show :: AudioDeviceStatus -> String

showList :: [AudioDeviceStatus] -> ShowS

Generic AudioDeviceStatus Source # 
Instance details

Defined in SDL.Audio

Associated Types

type Rep AudioDeviceStatus :: Type -> Type

type Rep AudioDeviceStatus Source # 
Instance details

Defined in SDL.Audio

type Rep AudioDeviceStatus = D1 ('MetaData "AudioDeviceStatus" "SDL.Audio" "sdl2-2.5.2.0-Cx4Ipj2keSJFpflqvJYEGr" 'False) (C1 ('MetaCons "Playing" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Paused" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Stopped" 'PrefixI 'False) (U1 :: Type -> Type)))

audioDeviceStatus :: MonadIO m => AudioDevice -> m AudioDeviceStatus Source #

Query the state of an AudioDevice.

AudioFormat

data AudioFormat sampleType where Source #

Information about what format an audio bytestream is. The type variable t indicates the type used for audio buffer samples. It is determined by the choice of the provided SampleBitSize. For example:

AudioFormat UnsignedInteger Sample8Bit Native :: AudioFormat Word8

Indicating that an 8-bit audio format in the platforms native endianness uses a buffer of Word8 values.

Instances

Instances details
Eq (AudioFormat sampleType) Source # 
Instance details

Defined in SDL.Audio

Methods

(==) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool

(/=) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool

Ord (AudioFormat sampleType) Source # 
Instance details

Defined in SDL.Audio

Methods

compare :: AudioFormat sampleType -> AudioFormat sampleType -> Ordering

(<) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool

(<=) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool

(>) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool

(>=) :: AudioFormat sampleType -> AudioFormat sampleType -> Bool

max :: AudioFormat sampleType -> AudioFormat sampleType -> AudioFormat sampleType

min :: AudioFormat sampleType -> AudioFormat sampleType -> AudioFormat sampleType

Show (AudioFormat sampleType) Source # 
Instance details

Defined in SDL.Audio

Methods

showsPrec :: Int -> AudioFormat sampleType -> ShowS

show :: AudioFormat sampleType -> String

showList :: [AudioFormat sampleType] -> ShowS

Enumerating AudioDevices

getAudioDeviceNames :: MonadIO m => AudioDeviceUsage -> m (Maybe (Vector Text)) Source #

Enumerate all AudioDevices attached to this system, that can be used as specified by the given AudioDeviceUsage. SDL cannot always guarantee that this list can be produced, in which case Nothing will be returned.

AudioSpec

data AudioSpec Source #

AudioSpec is the concrete specification of how an AudioDevice was sucessfully opened. Unlike OpenDeviceSpec, which specifies what you want, AudioSpec specifies what you have.

audioSpecFreq :: AudioSpec -> CInt Source #

DSP frequency (samples per second)

audioSpecFormat :: AudioSpec -> AudioFormat sampleType Source #

Audio data format

audioSpecChannels :: AudioSpec -> Channels Source #

Number of separate sound channels

audioSpecSilence :: AudioSpec -> Word8 Source #

Calculated udio buffer silence value

audioSpecSize :: AudioSpec -> Word32 Source #

Calculated audio buffer size in bytes

audioSpecCallback :: AudioSpec -> AudioFormat sampleType -> IOVector sampleType -> IO () Source #

The function to call when the audio device needs more data

Audio Drivers

getAudioDrivers :: MonadIO m => m (Vector AudioDriver) Source #

Obtain a list of all possible audio drivers for this system. These drivers can be used to specificially initialize the audio system.

currentAudioDriver :: MonadIO m => m (Maybe Text) Source #

Query SDL for the name of the currently initialized audio driver, if possible. This will return Nothing if no driver has been initialized.

data AudioDriver Source #

An abstract description of an audio driver on the host machine.

Instances

Instances details
Eq AudioDriver Source # 
Instance details

Defined in SDL.Audio

Methods

(==) :: AudioDriver -> AudioDriver -> Bool

(/=) :: AudioDriver -> AudioDriver -> Bool

Show AudioDriver Source # 
Instance details

Defined in SDL.Audio

Methods

showsPrec :: Int -> AudioDriver -> ShowS

show :: AudioDriver -> String

showList :: [AudioDriver] -> ShowS

audioDriverName :: AudioDriver -> Text Source #

Get the human readable name of an AudioDriver

Explicit Initialization

audioInit :: MonadIO m => AudioDriver -> m () Source #

Explicitly initialize the audio system against a specific AudioDriver. Note that most users will not need to do this, as the normal initialization routines will already take care of this for you.