| License | BSD3 |
|---|---|
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
SDL.Mixer
Contents
Description
Bindings to the SDL2_mixer library.
Synopsis
- withAudio :: (MonadBaseControl IO m, MonadIO m) => Audio -> ChunkSize -> m a -> m a
- data Audio = Audio {}
- data Format
- data Output
- defaultAudio :: Audio
- type ChunkSize = Int
- queryAudio :: MonadIO m => m Audio
- openAudio :: MonadIO m => Audio -> ChunkSize -> m ()
- closeAudio :: MonadIO m => m ()
- class Loadable a where
- newtype Chunk = Chunk (Ptr Chunk)
- chunkDecoders :: MonadIO m => m [String]
- newtype Music = Music (Ptr Music)
- musicDecoders :: MonadIO m => m [String]
- data Channel
- pattern AllChannels :: Channel
- setChannels :: MonadIO m => Int -> m ()
- getChannels :: MonadIO m => m Int
- play :: MonadIO m => Chunk -> m ()
- playForever :: MonadIO m => Chunk -> m ()
- data Times
- pattern Once :: Times
- pattern Forever :: Times
- playOn :: MonadIO m => Channel -> Times -> Chunk -> m Channel
- type Milliseconds = Int
- type Limit = Milliseconds
- pattern NoLimit :: Limit
- playLimit :: MonadIO m => Limit -> Channel -> Times -> Chunk -> m Channel
- fadeIn :: MonadIO m => Milliseconds -> Chunk -> m ()
- fadeInOn :: MonadIO m => Channel -> Times -> Milliseconds -> Chunk -> m Channel
- fadeInLimit :: MonadIO m => Limit -> Channel -> Times -> Milliseconds -> Chunk -> m Channel
- reserveChannels :: MonadIO m => Int -> m Int
- data Group
- pattern DefaultGroup :: Group
- group :: MonadIO m => Group -> Channel -> m Bool
- groupSpan :: MonadIO m => Group -> Channel -> Channel -> m Int
- groupCount :: MonadIO m => Group -> m Int
- getAvailable :: MonadIO m => Group -> m (Maybe Channel)
- getOldest :: MonadIO m => Group -> m (Maybe Channel)
- getNewest :: MonadIO m => Group -> m (Maybe Channel)
- pause :: MonadIO m => Channel -> m ()
- resume :: MonadIO m => Channel -> m ()
- halt :: MonadIO m => Channel -> m ()
- haltAfter :: MonadIO m => Milliseconds -> Channel -> m ()
- haltGroup :: MonadIO m => Group -> m ()
- type Volume = Int
- class HasVolume a where
- playing :: MonadIO m => Channel -> m Bool
- playingCount :: MonadIO m => m Int
- paused :: MonadIO m => Channel -> m Bool
- pausedCount :: MonadIO m => m Int
- playedLast :: MonadIO m => Channel -> m (Maybe Chunk)
- data Fading
- fading :: MonadIO m => Channel -> m Fading
- fadeOut :: MonadIO m => Milliseconds -> Channel -> m ()
- fadeOutGroup :: MonadIO m => Milliseconds -> Group -> m ()
- whenChannelFinished :: MonadIO m => (Channel -> IO ()) -> m ()
- playMusic :: MonadIO m => Times -> Music -> m ()
- type Position = Milliseconds
- fadeInMusic :: MonadIO m => Milliseconds -> Times -> Music -> m ()
- fadeInMusicAt :: MonadIO m => Position -> Milliseconds -> Times -> Music -> m ()
- fadeInMusicAtMOD :: MonadIO m => Int -> Milliseconds -> Times -> Music -> m ()
- pauseMusic :: MonadIO m => m ()
- haltMusic :: MonadIO m => m ()
- resumeMusic :: MonadIO m => m ()
- rewindMusic :: MonadIO m => m ()
- setMusicPosition :: MonadIO m => Position -> m ()
- setMusicPositionMOD :: MonadIO m => Int -> m ()
- setMusicVolume :: MonadIO m => Volume -> m ()
- getMusicVolume :: MonadIO m => m Volume
- playingMusic :: MonadIO m => m Bool
- pausedMusic :: MonadIO m => m Bool
- fadingMusic :: MonadIO m => m Fading
- data MusicType
- musicType :: Music -> Maybe MusicType
- playingMusicType :: MonadIO m => m (Maybe MusicType)
- fadeOutMusic :: MonadIO m => Milliseconds -> m Bool
- whenMusicFinished :: MonadIO m => IO () -> m ()
- type Effect = Channel -> IOVector Word8 -> IO ()
- type EffectFinished = Channel -> IO ()
- pattern PostProcessing :: Channel
- effect :: MonadIO m => Channel -> EffectFinished -> Effect -> m (m ())
- effectPan :: MonadIO m => Channel -> Volume -> Volume -> m (m ())
- effectDistance :: MonadIO m => Channel -> Word8 -> m (m ())
- effectPosition :: MonadIO m => Channel -> Int16 -> Word8 -> m (m ())
- effectReverseStereo :: MonadIO m => Channel -> Bool -> m (m ())
- initialize :: (Foldable f, MonadIO m) => f InitFlag -> m ()
- data InitFlag
- quit :: MonadIO m => m ()
- version :: (Integral a, MonadIO m) => m (a, a, a)
Audio setup
In order to use the rest of the library, you need to
supply withAudio or openAudio with an Audio configuration.
withAudio :: (MonadBaseControl IO m, MonadIO m) => Audio -> ChunkSize -> m a -> m a Source #
Initializes the SDL2_mixer API.
This should be the first function you call after initializing SDL itself
with InitAudio.
Automatically cleans up the API when the inner computation finishes.
An audio configuration. Use this with withAudio.
Constructors
| Audio | |
Fields
| |
A sample format.
Constructors
| FormatU8 | Unsigned 8-bit samples. |
| FormatS8 | Signed 8-bit samples. |
| FormatU16_LSB | Unsigned 16-bit samples, in little-endian byte order. |
| FormatS16_LSB | Signed 16-bit samples, in little-endian byte order. |
| FormatU16_MSB | Unsigned 16-bit samples, in big-endian byte order. |
| FormatS16_MSB | signed 16-bit samples, in big-endian byte order. |
| FormatU16_Sys | Unsigned 16-bit samples, in system byte order. |
| FormatS16_Sys | Signed 16-bit samples, in system byte order. |
The number of sound channels in output.
defaultAudio :: Audio Source #
A default Audio configuration.
Same as def.
Uses 22050 as the audioFrequency, FormatS16_Sys as the audioFormat and
Stereo as the audioOutput.
The size of each mixed sample.
The smaller this is, the more often callbacks will be invoked. If this is made too small on a slow system, the sounds may skip. If made too large, sound effects could lag.
queryAudio :: MonadIO m => m Audio Source #
Alternative
openAudio :: MonadIO m => Audio -> ChunkSize -> m () Source #
An alternative to withAudio, also initializes the SDL2_mixer API.
However, openAudio does not take care of automatically calling
closeAudio after a computation ends, so you have to take care to do so
manually.
closeAudio :: MonadIO m => m () Source #
Shut down and clean up the SDL2_mixer API.
After calling this, all audio stops.
You don't have to call this if you're using withAudio.
Loading audio data
class Loadable a where Source #
A class of all values that can be loaded from some source. You can load
both Chunks and Music this way.
Note that you must call withAudio before using these, since they have to
know the audio configuration to properly convert the data for playback.
Methods
decode :: MonadIO m => ByteString -> m a Source #
Load the value from a ByteString.
load :: MonadIO m => FilePath -> m a Source #
Same as decode, but loads from a file instead.
free :: MonadIO m => a -> m () Source #
Frees the value's memory. It should no longer be used.
Note that you shouldn't free those values that are currently playing.
A loaded audio chunk.
chunkDecoders :: MonadIO m => m [String] Source #
Returns the names of all chunk decoders currently available.
These depend on the availability of shared libraries for each of the
formats. The list may contain any of the following, and possibly others:
WAVE, AIFF, VOC, OFF, FLAC, MP3.
A loaded music file.
Music is played on a separate channel different from the normal mixing
Channels.
To manipulate Music outside of post-processing callbacks, use the music
variant functions listed below.
musicDecoders :: MonadIO m => m [String] Source #
Returns the names of all music decoders currently available.
These depend on the availability of shared libraries for each of the
formats. The list may contain any of the following, and possibly others:
WAVE, MODPLUG, MIKMOD, TIMIDITY, FLUIDSYNTH, NATIVEMIDI, OGG,
FLAC, MP3.
Chunks
Playing chunks
A mixing channel.
Use the Integral instance to define these: the first channel is 0, the
second 1 and so on.
The default number of Channels available at startup is 8, so note that you
cannot usemore than these starting 8 if you haven't created more with
setChannels.
Instances
| Enum Channel Source # | |
| Eq Channel Source # | |
| Integral Channel Source # | |
Defined in SDL.Mixer | |
| Num Channel Source # | |
| Ord Channel Source # | |
| Real Channel Source # | |
Defined in SDL.Mixer Methods toRational :: Channel -> Rational # | |
| Show Channel Source # | |
| HasVolume Channel Source # | |
pattern AllChannels :: Channel Source #
setChannels :: MonadIO m => Int -> m () Source #
Prepares a given number of Channels for use.
There are 8 such Channels already prepared for use after withAudio is
called.
You may call this multiple times, even with sounds playing. If setting a
lesser number of Channels than are currently in use, the higher Channels
will be stopped, their finish callbacks invoked, and their memory freed.
Passing in 0 or less will therefore stop and free all mixing channels.
Any Music playing is not affected by this function.
playForever :: MonadIO m => Chunk -> m () Source #
How many times should a certain Chunk be played?
type Milliseconds = Int Source #
A time in milliseconds.
type Limit = Milliseconds Source #
An upper limit of time, in milliseconds.
playLimit :: MonadIO m => Limit -> Channel -> Times -> Chunk -> m Channel Source #
Same as playOn, but imposes an upper limit in Milliseconds to how long
the Chunk can play.
The playing may still stop before the limit is reached.
This is the most generic play function variant.
fadeInLimit :: MonadIO m => Limit -> Channel -> Times -> Milliseconds -> Chunk -> m Channel Source #
Grouping channels
reserveChannels :: MonadIO m => Int -> m Int Source #
Reserve a given number of Channels, starting from Channel 0.
A reserved Channel is considered not to be available for playing samples
when using any play or fadeIn function variant with AllChannels. In
other words, whenever you let Mixer pick the first available Channel
itself, these reserved Channels will not be considered.
A group of Channels.
Grouping Channels together allows you to perform some operations on all of
them at once.
By default, all Channels are members of the DefaultGroup.
pattern DefaultGroup :: Group Source #
group :: MonadIO m => Group -> Channel -> m Bool Source #
Assigns a given Channel to a certain Group.
If DefaultGroup is used, assigns the Channel the the default starting
Group (essentially ungrouping them).
If AllChannels is used, assigns all Channels to the given Group.
Returns whether the Channel was successfully grouped or not. Failure is
poosible if the Channel does not exist, for instance.
groupSpan :: MonadIO m => Group -> Channel -> Channel -> m Int Source #
Same as groupChannel, but groups all Channels between the first and
last given, inclusive.
If DefaultGroup is used, assigns the entire Channel span to the default
starting Group (essentially ungrouping them).
Using AllChannels is invalid.
Returns the number of Channels successfully grouped. This number may be
less than the number of Channels given, for instance if some of them do
not exist.
groupCount :: MonadIO m => Group -> m Int Source #
Returns the number of Channels within a Group.
If DefaultGroup is used, will return the number of all Channels, since
all of them are within the default Group.
getAvailable :: MonadIO m => Group -> m (Maybe Channel) Source #
Gets the first inactive (not playing) Channel within a given Group,
if any.
Using DefaultGroup will give you the first inactive Channel out of all
that exist.
Controlling playback
resume :: MonadIO m => Channel -> m () Source #
Resumes playing a Channel, or all Channels if AllChannels is used.
halt :: MonadIO m => Channel -> m () Source #
Halts playback on a Channel, or all Channels if AllChannels is used.
haltAfter :: MonadIO m => Milliseconds -> Channel -> m () Source #
Same as halt, but only does so after a certain number of Milliseconds.
If AllChannels is used, it will halt all the Channels after the given
time instead.
haltGroup :: MonadIO m => Group -> m () Source #
Same as halt, but halts an entire Group instead.
Note that using DefaultGroup here is the same as calling halt
AllChannels.
Setting the volume
A volume, where 0 is silent and 128 loudest.
Volumes lesser than 0 or greater than 128 function as if they are 0 and
128, respectively.
class HasVolume a where Source #
A class of all values that have a Volume.
Methods
getVolume :: MonadIO m => a -> m Volume Source #
Gets the value's currently set Volume.
If the value is a Channel and AllChannels is used, gets the average
Volume of all Channels.
setVolume :: MonadIO m => Volume -> a -> m () Source #
Sets a value's Volume.
If the value is a Chunk, the volume setting only takes effect when the
Chunk is used on a Channel, being mixed into the output.
In case of being used on a Channel, the volume setting takes effect
during the final mix, along with the Chunk volume. For instance, setting
the Volume of a certain Channel to 64 will halve the volume of all
Chunks played on that Channel. If AllChannels is used, sets all
Channels to the given Volume instead.
Querying for status
playing :: MonadIO m => Channel -> m Bool Source #
Returns whether the given Channel is playing or not.
If AllChannels is used, this returns whether any of the channels is
currently playing.
paused :: MonadIO m => Channel -> m Bool Source #
Returns whether the given Channel is paused or not.
If AllChannels is used, this returns whether any of the channels is
currently paused.
Describes whether a Channel is fading in, out, or not at all.
fading :: MonadIO m => Channel -> m Fading Source #
Returns a Channel's Fading status.
Note that using AllChannels here is not valid, and will simply return the
Fading status of the first Channel instead.
Fading out
fadeOut :: MonadIO m => Milliseconds -> Channel -> m () Source #
Gradually fade out a given playing Channel during the next
Milliseconds, even if it is paused.
If AllChannels is used, fades out all the playing Channels instead.
fadeOutGroup :: MonadIO m => Milliseconds -> Group -> m () Source #
Same as fadeOut, but fades out an entire Group instead.
Using DefaultGroup here is the same as calling fadeOut with
AllChannels.
Reacting to finish
whenChannelFinished :: MonadIO m => (Channel -> IO ()) -> m () Source #
Sets a callback that gets invoked each time a Channel finishes playing.
A Channel finishes playing both when playback ends normally and when it is
halted (also possibly via setChannels).
Note: don't call other Mixer functions within this callback.
Music
Chunks and Music differ by the way they are played. While multiple
Chunks can be played on different desired Channels at the same time,
there can only be one Music playing at the same time.
Therefore, the functions used for Music are separate.
Playing music
type Position = Milliseconds Source #
A position in milliseconds within a piece of Music.
fadeInMusic :: MonadIO m => Milliseconds -> Times -> Music -> m () Source #
Plays a given Music a number of Times, but fading it in during a
certain number of Milliseconds.
The fading only occurs during the first time the Music is played.
fadeInMusicAt :: MonadIO m => Position -> Milliseconds -> Times -> Music -> m () Source #
Same as fadeInMusic, but with a custom starting Music's Position.
Note that this only works on Music that setMusicPosition works on.
fadeInMusicAtMOD :: MonadIO m => Int -> Milliseconds -> Times -> Music -> m () Source #
Same as fadeInMusicAt, but works with MOD Music.
Instead of milliseconds, specify the position with a pattern number.
Controlling playback
pauseMusic :: MonadIO m => m () Source #
resumeMusic :: MonadIO m => m () Source #
rewindMusic :: MonadIO m => m () Source #
setMusicPosition :: MonadIO m => Position -> m () Source #
setMusicPositionMOD :: MonadIO m => Int -> m () Source #
Similar to setMusicPosition, but works only with MOD Music.
Pass in the pattern number.
Setting the volume
setMusicVolume :: MonadIO m => Volume -> m () Source #
Querying for status
playingMusic :: MonadIO m => m Bool Source #
pausedMusic :: MonadIO m => m Bool Source #
A Music's type.
Instances
| Bounded MusicType Source # | |
| Eq MusicType Source # | |
| Ord MusicType Source # | |
| Read MusicType Source # | |
| Show MusicType Source # | |
Fading out
fadeOutMusic :: MonadIO m => Milliseconds -> m Bool Source #
Gradually fade out the Music over a given number of Milliseconds.
The Music is set to fade out only when it is playing and not fading
already.
Returns whether the Music was successfully set to fade out.
Reacting to finish
whenMusicFinished :: MonadIO m => IO () -> m () Source #
Effects
type EffectFinished = Channel -> IO () Source #
A function called when a processor is finished being used.
This allows you to clean up any state you might have had.
pattern PostProcessing :: Channel Source #
A way to refer to the special Channel used for post-processing effects.
You can only use this value with effect and the other in-built effect
functions such as effectPan and effectDistance.
In-built effects
effectPan :: MonadIO m => Channel -> Volume -> Volume -> m (m ()) Source #
Applies an in-built effect implementing panning.
Sets the left-channel and right-channel Volume to the given values.
This only works when Audio's Output is Stereo, which is the default.
Returns an action that, when executed, removes this effect. That action
simply calls effectPan with Volumes 128 and 128.
effectDistance :: MonadIO m => Channel -> Word8 -> m (m ()) Source #
Applies a different volume based on the distance (as Word8) specified.
The volume is loudest at distance 0, quietest at distance 255.
Returns an action that, when executed, removes this effect. That action
simply calls effectDistance with a distance of 0.
effectPosition :: MonadIO m => Channel -> Int16 -> Word8 -> m (m ()) Source #
Simulates a simple 3D audio effect.
Accepts the angle in degrees (as Int16) in relation to the source of the
sound (0 is directly in front, 90 directly to the right, and so on) and a
distance (as Word8) from the source of the sound (where 255 is very far
away, and 0 extremely close).
Returns an action that, when executed, removes this effect. That action
simply calls effectPosition with both angle and distance set to 0.
effectReverseStereo :: MonadIO m => Channel -> Bool -> m (m ()) Source #
Swaps the left and right channel sound.
If given True, will swap the sound channels.
Returns an action that, when executed, removes this effect. That action
simply calls effectReverseStereo with False.
Other
initialize :: (Foldable f, MonadIO m) => f InitFlag -> m () Source #
Initialize the library by loading support for a certain set of sample/music formats.
Note that calling this is not strictly necessary: support for a certain
format will be loaded automatically when attempting to load data in that
format. Using initialize allows you to decide when to load support.
You may call this function multiple times.