| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
SDL.Audio
Contents
Description
SDL.Audio provides a high-level API to SDL's audio device capabilities.
- data AudioDevice
- openAudioDevice :: MonadIO m => OpenDeviceSpec -> m (AudioDevice, AudioSpec)
- closeAudioDevice :: MonadIO m => AudioDevice -> m ()
- data OpenDeviceSpec = OpenDeviceSpec {- openDeviceFreq :: !(Changeable CInt)
- openDeviceFormat :: !(Changeable (AudioFormat sampleType))
- openDeviceChannels :: !(Changeable Channels)
- openDeviceSamples :: !Word16
- openDeviceCallback :: forall actualSampleType. AudioFormat actualSampleType -> IOVector actualSampleType -> IO ()
- openDeviceUsage :: !AudioDeviceUsage
- openDeviceName :: !(Maybe Text)
 
- data AudioDeviceUsage
- data Channels- = Mono
- | Stereo
- | Quad
- | FivePointOne
 
- data Changeable a
- setAudioDeviceLocked :: MonadIO m => AudioDevice -> LockState -> m ()
- data LockState
- data PlaybackState
- setAudioDevicePlaybackState :: MonadIO m => AudioDevice -> PlaybackState -> m ()
- data AudioDeviceStatus
- audioDeviceStatus :: MonadIO m => AudioDevice -> m AudioDeviceStatus
- data AudioFormat sampleType where- Signed8BitAudio :: AudioFormat Int8
- Unsigned8BitAudio :: AudioFormat Word8
- Signed16BitLEAudio :: AudioFormat Int16
- Signed16BitBEAudio :: AudioFormat Int16
- Signed16BitNativeAudio :: AudioFormat Int16
- Unsigned16BitLEAudio :: AudioFormat Word16
- Unsigned16BitBEAudio :: AudioFormat Word16
- Unsigned16BitNativeAudio :: AudioFormat Word16
- Signed32BitLEAudio :: AudioFormat Int32
- Signed32BitBEAudio :: AudioFormat Int32
- Signed32BitNativeAudio :: AudioFormat Int32
- FloatingLEAudio :: AudioFormat Float
- FloatingBEAudio :: AudioFormat Float
- FloatingNativeAudio :: AudioFormat Float
 
- getAudioDeviceNames :: MonadIO m => AudioDeviceUsage -> m (Maybe (Vector Text))
- data AudioSpec
- audioSpecFreq :: AudioSpec -> CInt
- audioSpecFormat :: AudioSpec -> AudioFormat sampleType
- audioSpecChannels :: AudioSpec -> Channels
- audioSpecSilence :: AudioSpec -> Word8
- audioSpecSize :: AudioSpec -> Word32
- audioSpecCallback :: AudioSpec -> AudioFormat sampleType -> IOVector sampleType -> IO ()
- getAudioDrivers :: MonadIO m => m (Vector AudioDriver)
- currentAudioDriver :: MonadIO m => m (Maybe Text)
- data AudioDriver
- audioDriverName :: AudioDriver -> Text
- audioInit :: MonadIO m => AudioDriver -> m ()
Managing AudioDevices
data AudioDevice Source #
An open audio device. These can be created via openAudioDevice and should be closed with closeAudioDevice
Instances
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
| 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. | 
How many channels audio should be played on
Constructors
| Mono | A single speaker configuration | 
| Stereo | A traditional left/right stereo system | 
| Quad | |
| FivePointOne | 
 | 
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 | 
 | 
| Desire !a | 
 | 
Instances
| Functor Changeable Source # | |
| Foldable Changeable Source # | |
| Traversable Changeable Source # | |
| Eq a => Eq (Changeable a) Source # | |
| Data a => Data (Changeable a) Source # | |
| Read a => Read (Changeable a) Source # | |
| Show a => Show (Changeable a) Source # | |
| Generic (Changeable a) Source # | |
| type Rep (Changeable a) Source # | |
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.
Whether a device should be locked or unlocked.
Switching Playback States
data PlaybackState Source #
Whether to allow an AudioDevice to play sound or remain paused.
Constructors
| Pause | Pause the  | 
| Play | Resume the  | 
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  | 
| Paused | The  | 
| Stopped | The  | 
Instances
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.
Constructors
Instances
| Eq (AudioFormat sampleType) Source # | |
| Ord (AudioFormat sampleType) Source # | |
| Show (AudioFormat sampleType) Source # | |
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
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.
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.