sdl2-mixer-1.2.0.0: Haskell bindings to SDL2_mixer
LicenseBSD3
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

SDL.Mixer

Description

Bindings to the SDL2_mixer library.

Synopsis

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.

data Audio Source #

An audio configuration. Use this with withAudio.

Constructors

Audio 

Fields

Instances

Instances details
Eq Audio Source # 
Instance details

Defined in SDL.Mixer

Methods

(==) :: Audio -> Audio -> Bool #

(/=) :: Audio -> Audio -> Bool #

Read Audio Source # 
Instance details

Defined in SDL.Mixer

Show Audio Source # 
Instance details

Defined in SDL.Mixer

Methods

showsPrec :: Int -> Audio -> ShowS #

show :: Audio -> String #

showList :: [Audio] -> ShowS #

Default Audio Source # 
Instance details

Defined in SDL.Mixer

Methods

def :: Audio #

data Format Source #

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.

Instances

Instances details
Bounded Format Source # 
Instance details

Defined in SDL.Mixer

Eq Format Source # 
Instance details

Defined in SDL.Mixer

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

Ord Format Source # 
Instance details

Defined in SDL.Mixer

Read Format Source # 
Instance details

Defined in SDL.Mixer

Show Format Source # 
Instance details

Defined in SDL.Mixer

data Output Source #

The number of sound channels in output.

Constructors

Mono 
Stereo 

Instances

Instances details
Bounded Output Source # 
Instance details

Defined in SDL.Mixer

Eq Output Source # 
Instance details

Defined in SDL.Mixer

Methods

(==) :: Output -> Output -> Bool #

(/=) :: Output -> Output -> Bool #

Ord Output Source # 
Instance details

Defined in SDL.Mixer

Read Output Source # 
Instance details

Defined in SDL.Mixer

Show Output Source # 
Instance details

Defined in SDL.Mixer

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.

type ChunkSize = Int Source #

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 #

Get the audio format in use by the opened audio device.

This may or may not match the Audio you asked for when calling withAudio.

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

Use load or decode to get both Chunk and Music values.

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.

Minimal complete definition

decode, free

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.

Instances

Instances details
Loadable Music Source # 
Instance details

Defined in SDL.Mixer

Methods

decode :: MonadIO m => ByteString -> m Music Source #

load :: MonadIO m => FilePath -> m Music Source #

free :: MonadIO m => Music -> m () Source #

Loadable Chunk Source # 
Instance details

Defined in SDL.Mixer

Methods

decode :: MonadIO m => ByteString -> m Chunk Source #

load :: MonadIO m => FilePath -> m Chunk Source #

free :: MonadIO m => Chunk -> m () Source #

newtype Chunk Source #

A loaded audio chunk.

Constructors

Chunk (Ptr Chunk) 

Instances

Instances details
Eq Chunk Source # 
Instance details

Defined in SDL.Mixer

Methods

(==) :: Chunk -> Chunk -> Bool #

(/=) :: Chunk -> Chunk -> Bool #

Show Chunk Source # 
Instance details

Defined in SDL.Mixer

Methods

showsPrec :: Int -> Chunk -> ShowS #

show :: Chunk -> String #

showList :: [Chunk] -> ShowS #

HasVolume Chunk Source # 
Instance details

Defined in SDL.Mixer

Methods

getVolume :: MonadIO m => Chunk -> m Volume Source #

setVolume :: MonadIO m => Volume -> Chunk -> m () Source #

Loadable Chunk Source # 
Instance details

Defined in SDL.Mixer

Methods

decode :: MonadIO m => ByteString -> m Chunk Source #

load :: MonadIO m => FilePath -> m Chunk Source #

free :: MonadIO m => Chunk -> m () Source #

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.

newtype Music Source #

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.

Constructors

Music (Ptr Music) 

Instances

Instances details
Eq Music Source # 
Instance details

Defined in SDL.Mixer

Methods

(==) :: Music -> Music -> Bool #

(/=) :: Music -> Music -> Bool #

Show Music Source # 
Instance details

Defined in SDL.Mixer

Methods

showsPrec :: Int -> Music -> ShowS #

show :: Music -> String #

showList :: [Music] -> ShowS #

Loadable Music Source # 
Instance details

Defined in SDL.Mixer

Methods

decode :: MonadIO m => ByteString -> m Music Source #

load :: MonadIO m => FilePath -> m Music Source #

free :: MonadIO m => Music -> m () Source #

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

Chunks are played on Channels, which can be combined into Groups.

Playing chunks

data Channel Source #

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.

The starting Volume of each Channel is the maximum: 128.

Instances

Instances details
Enum Channel Source # 
Instance details

Defined in SDL.Mixer

Eq Channel Source # 
Instance details

Defined in SDL.Mixer

Methods

(==) :: Channel -> Channel -> Bool #

(/=) :: Channel -> Channel -> Bool #

Integral Channel Source # 
Instance details

Defined in SDL.Mixer

Num Channel Source # 
Instance details

Defined in SDL.Mixer

Ord Channel Source # 
Instance details

Defined in SDL.Mixer

Real Channel Source # 
Instance details

Defined in SDL.Mixer

Show Channel Source # 
Instance details

Defined in SDL.Mixer

HasVolume Channel Source # 
Instance details

Defined in SDL.Mixer

Methods

getVolume :: MonadIO m => Channel -> m Volume Source #

setVolume :: MonadIO m => Volume -> Channel -> m () Source #

pattern AllChannels :: Channel Source #

Use this value when you wish to perform an operation on all Channels.

For more information, see each of the functions accepting a Channel.

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.

getChannels :: MonadIO m => m Int Source #

Gets the number of Channels currently in use.

play :: MonadIO m => Chunk -> m () Source #

Play a Chunk once, using the first available Channel.

playForever :: MonadIO m => Chunk -> m () Source #

Same as play, but keeps playing the Chunk forever.

data Times Source #

How many times should a certain Chunk be played?

Instances

Instances details
Enum Times Source # 
Instance details

Defined in SDL.Mixer

Eq Times Source # 
Instance details

Defined in SDL.Mixer

Methods

(==) :: Times -> Times -> Bool #

(/=) :: Times -> Times -> Bool #

Integral Times Source # 
Instance details

Defined in SDL.Mixer

Num Times Source # 
Instance details

Defined in SDL.Mixer

Ord Times Source # 
Instance details

Defined in SDL.Mixer

Methods

compare :: Times -> Times -> Ordering #

(<) :: Times -> Times -> Bool #

(<=) :: Times -> Times -> Bool #

(>) :: Times -> Times -> Bool #

(>=) :: Times -> Times -> Bool #

max :: Times -> Times -> Times #

min :: Times -> Times -> Times #

Real Times Source # 
Instance details

Defined in SDL.Mixer

Methods

toRational :: Times -> Rational #

pattern Once :: Times Source #

A shorthand for playing once.

pattern Forever :: Times Source #

A shorthand for looping a Chunk forever.

playOn :: MonadIO m => Channel -> Times -> Chunk -> m Channel Source #

Same as play, but plays the Chunk using a given Channel a certain number of Times.

If AllChannels is used, then plays the Chunk using the first available Channel instead.

Returns the Channel that was used.

type Milliseconds = Int Source #

A time in milliseconds.

type Limit = Milliseconds Source #

An upper limit of time, in milliseconds.

pattern NoLimit :: Limit Source #

A lack of an upper limit.

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.

fadeIn :: MonadIO m => Milliseconds -> Chunk -> m () Source #

Same as play, but fades in the Chunk by making the Channel Volume start at 0 and rise to a full 128 over the course of a given number of Milliseconds.

The Chunk may end playing before the fade-in is complete, if it doesn't last as long as the given fade-in time.

fadeInOn :: MonadIO m => Channel -> Times -> Milliseconds -> Chunk -> m Channel Source #

Same as fadeIn, but allows you to specify the Channel to play on and how many Times to play it, similar to playOn.

If AllChannels is used, will play the Chunk on the first available Channel.

Returns the Channel that was used.

fadeInLimit :: MonadIO m => Limit -> Channel -> Times -> Milliseconds -> Chunk -> m Channel Source #

Same as fadeInOn, but imposes an upper Limit to how long the Chunk can play, similar to playLimit.

This is the most generic fade-in function variant.

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.

data Group Source #

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.

Instances

Instances details
Enum Group Source # 
Instance details

Defined in SDL.Mixer

Eq Group Source # 
Instance details

Defined in SDL.Mixer

Methods

(==) :: Group -> Group -> Bool #

(/=) :: Group -> Group -> Bool #

Integral Group Source # 
Instance details

Defined in SDL.Mixer

Num Group Source # 
Instance details

Defined in SDL.Mixer

Ord Group Source # 
Instance details

Defined in SDL.Mixer

Methods

compare :: Group -> Group -> Ordering #

(<) :: Group -> Group -> Bool #

(<=) :: Group -> Group -> Bool #

(>) :: Group -> Group -> Bool #

(>=) :: Group -> Group -> Bool #

max :: Group -> Group -> Group #

min :: Group -> Group -> Group #

Real Group Source # 
Instance details

Defined in SDL.Mixer

Methods

toRational :: Group -> Rational #

pattern DefaultGroup :: Group Source #

The default Group all Channels are in the moment they are created.

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.

getOldest :: MonadIO m => Group -> m (Maybe Channel) Source #

Gets the oldest actively playing Channel within a given Group.

Returns Nothing when the Group is empty or no Channels within it are playing.

getNewest :: MonadIO m => Group -> m (Maybe Channel) Source #

Gets the newest actively playing Channel within a given Group.

Returns Nothing when the Group is empty or no Channels within it are playing.

Controlling playback

pause :: MonadIO m => Channel -> m () Source #

Pauses the given Channel, if it is actively playing.

If AllChannels is used, will pause all actively playing Channels instead.

Note that paused Channels may still be halted.

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

type Volume = Int Source #

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.

Instances

Instances details
HasVolume Channel Source # 
Instance details

Defined in SDL.Mixer

Methods

getVolume :: MonadIO m => Channel -> m Volume Source #

setVolume :: MonadIO m => Volume -> Channel -> m () Source #

HasVolume Chunk Source # 
Instance details

Defined in SDL.Mixer

Methods

getVolume :: MonadIO m => Chunk -> m Volume Source #

setVolume :: MonadIO m => Volume -> Chunk -> m () Source #

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.

playingCount :: MonadIO m => m Int Source #

Returns how many Channels are 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.

pausedCount :: MonadIO m => m Int Source #

Returns how many Channels are currently paused.

playedLast :: MonadIO m => Channel -> m (Maybe Chunk) Source #

Gets the most recent Chunk played on a Channel, if any.

Using AllChannels is not valid here, and will return Nothing.

Note that the returned Chunk might be invalid if it was already freed.

data Fading Source #

Describes whether a Channel is fading in, out, or not at all.

Instances

Instances details
Eq Fading Source # 
Instance details

Defined in SDL.Mixer

Methods

(==) :: Fading -> Fading -> Bool #

(/=) :: Fading -> Fading -> Bool #

Ord Fading Source # 
Instance details

Defined in SDL.Mixer

Read Fading Source # 
Instance details

Defined in SDL.Mixer

Show Fading Source # 
Instance details

Defined in SDL.Mixer

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

playMusic :: MonadIO m => Times -> Music -> m () Source #

Plays a given Music a certain number of Times.

The previously playing Music will be halted, unless it is fading out in which case a blocking wait occurs until it fades out completely.

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 #

Pauses Music playback, if it is actively playing.

You may still haltMusic paused Music.

haltMusic :: MonadIO m => m () Source #

Halts Music playback.

resumeMusic :: MonadIO m => m () Source #

Resumes Music playback.

This works on both paused and halted Music.

If Music is currently actively playing, this has no effect.

rewindMusic :: MonadIO m => m () Source #

Rewinds the Music to the beginning.

When playing new Music, it starts at the beginning by default.

This function only works with MOD, OGG, MP3 and NATIVEMIDI streams.

setMusicPosition :: MonadIO m => Position -> m () Source #

Set the Position for currently playing Music.

Note: this only works for OGG and MP3 Music.

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 #

Sets the Volume for Music.

Note that this won't work if any Music is currently fading.

getMusicVolume :: MonadIO m => m Volume Source #

Gets the current Volume setting for Music.

Querying for status

playingMusic :: MonadIO m => m Bool Source #

Returns whether a Music is currently playing or not.

Note that this returns True even if the Music is currently paused.

pausedMusic :: MonadIO m => m Bool Source #

Returns whether a Music is currently paused or not.

Note that this returns False if the Music is currently halted.

fadingMusic :: MonadIO m => m Fading Source #

Returns the Music's Fading status.

data MusicType Source #

A Music's type.

Constructors

CMD 
WAV 
MOD 
MID 
OGG 
MP3 
FLAC 

Instances

Instances details
Bounded MusicType Source # 
Instance details

Defined in SDL.Mixer

Eq MusicType Source # 
Instance details

Defined in SDL.Mixer

Ord MusicType Source # 
Instance details

Defined in SDL.Mixer

Read MusicType Source # 
Instance details

Defined in SDL.Mixer

Show MusicType Source # 
Instance details

Defined in SDL.Mixer

musicType :: Music -> Maybe MusicType Source #

Gets the MusicType of a given Music.

playingMusicType :: MonadIO m => m (Maybe MusicType) Source #

Gets the MusicType of currently playing Music, if any.

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 #

Sets a callback that gets invoked each time a Music finishes playing.

Note: don't call other Mixer functions within this callback.

Effects

type Effect = Channel -> IOVector Word8 -> IO () Source #

A post-processing effect as a function operating on a mutable stream.

Note that, at the moment, this is a stream of bytes. Depending on the Audio Format you're using, you're probably going to want to treat is as a stream of 16-bit values instead.

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.

effect :: MonadIO m => Channel -> EffectFinished -> Effect -> m (m ()) Source #

Adds a post-processing Effect to a certain Channel.

A Channel's Effects are called in the order they were added.

Returns an action that, when executed, removes this Effect. Note: do execute this returned action more than once.

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.

data InitFlag Source #

Used with initialize to designate loading support for a particular sample/music format.

Constructors

InitFLAC 
InitMOD 
InitMP3 
InitOGG 

Instances

Instances details
Bounded InitFlag Source # 
Instance details

Defined in SDL.Mixer

Eq InitFlag Source # 
Instance details

Defined in SDL.Mixer

Ord InitFlag Source # 
Instance details

Defined in SDL.Mixer

Read InitFlag Source # 
Instance details

Defined in SDL.Mixer

Show InitFlag Source # 
Instance details

Defined in SDL.Mixer

quit :: MonadIO m => m () Source #

Cleans up any loaded libraries, freeing memory.

version :: (Integral a, MonadIO m) => m (a, a, a) Source #

Gets the major, minor, patch versions of the linked SDL2_mixer library.