mikmod-0.2.0.1: MikMod bindings

LicenseLGPL3
Safe HaskellNone
LanguageHaskell2010

Sound.MikMod

Contents

Description

MikMod bindings for Haskell

Synopsis

Overview

MikMod is a C library for playing music modules and sound samples.

The user controls MikMod by manipulating a handful of global variables, calling API functions, and manipulating fields of the Module and Sample structure. These low-level bindings are basically convenience wrappers for the above operations.

Module objects represent not only music but the playback state of a song. In this sense you can think of Modules as being like cassette tapes. For example if a playing module is paused or stopped, and another module begins playing, then resuming the original module will start from the position it was stopped at. You manipulate modules only via the type ModuleHandle.

Sample objects represent single sounds. Modules use samples to make music, but you can use samples independently for sound effects. Samples are similar to Modules in that they are only accessed via the type SampleHandle.

Music and sound effects both play samples on voices. There can be at most one sample playing on a voice at a time. Voices can be individually adjusted to change the characteristics of the samples that play on them. Voices are exposed by MikMod as indexes. These indexes are wrapped in the Voice newtype.

Modifying values of global variables and structure fields is allowed during playback and in most cases will have immediate effect.

MikMod allows loading modules and samples from the file system or from an arbitrary source via the MReader structure.

API functions that may fail come in two flavors: one that throws an exception and one that returns an Either.

The MikMod error callback mechanism and the MWriter are not supported yet.

Beware of using playerLoad while a song is playing. It has the side effect of adjusting the number of music voices (see mikmodSetNumVoices)!

Quickstart

import Control.Concurrent (threadDelay)
import Control.Monad.Loops (whileM_)
import Sound.MikMod

main = do
  mikmodRegisterAllDrivers
  mikmodRegisterAllLoaders
  mikmodInit ""
  mod <- playerLoad "rock on.mod" 128 NotCurious
  playerStart mod
  whileM_ playerActive $ do
    mikmodUpdate -- might be unnecessary on your system
    threadDelay 10000
  playerFree mod
  mikmodExit

Make sure to link your program to MikMod with -lmikmod. GHCI can be used to experiment by using ghci -lmikmod.

Example of playing sound effects.

import Control.Concurrent (threadDelay)
import Control.Monad.Loops (whileM_)
import Data.Functor ((<$>))
import Sound.MikMod

main = do
  mikmodRegisterAllDrivers
  mikmodRegisterAllLoaders
  mikmodInit ""
  mikmodSetNumVoices (-1) 4
  mikmodEnableOutput
  samp <- sampleLoad "wilhelm.wav"
  Just voice <- samplePlay samp 0
  whileM_ (not <$> voiceStopped voice) $ do
    mikmodUpdate -- might be unnecessary on your system
    threadDelay 10000
  sampleFree samp
  mikmodExit

Or using convenience wrappers for the initialization sequence,

import Control.Concurrent (threadDelay)
import Control.Monad.Loops (whileM_)
import Data.Functor ((<$>))
import Sound.MikMod

main = runMikMod 4 $ do
  samp <- sampleLoad "wilhelm.wav"
  Just voice <- samplePlay samp 0
  whileM_ (not <$> voiceStopped voice) $ do
    mikmodUpdate
    threadDelay 10000
  sampleFree samp

Globals

mikmodSetMusicVolume :: Int -> IO () Source #

Set the global music volume. The argument must be in the range 0 to 128 (There are 129 volume levels).

mikmodSetPanSep :: Int -> IO () Source #

Set the global stereo separation. The argument must be in the range 0 to 128 where 0 means mono sound and 128 means full separation. The default pan sep is 128.

mikmodSetReverb :: Int -> IO () Source #

Set the global reverb. The argument must be in the range 0 to 15 where 0 means no reverb and 15 means extreme reverb. The default reverb is zero.

mikmodSetSndFXVolume :: Int -> IO () Source #

Set the global sound effects volume. The argument must be in the range 0 to 128.

mikmodSetVolume :: Int -> IO () Source #

Set the global overall sound volume. The argument must be in the range 0 to 128.

mikmodSetDeviceIndex :: Int -> IO () Source #

Change the selected output driver by specifying a 1-based index into the global list of drivers. Setting this to zero, the default, means autodetect. To see the list use mikmodInfoDriver.

mikmodGetDeviceIndex :: IO Int Source #

The selected output driver from the global 1-based list of drivers.

mikmodGetDriver :: IO (Maybe MDriverInfo) Source #

Get an info report of the sound driver currently in use, if any. MikMod does not expose any functionality via MDriver field manipulation.

mikmodSetMixFreq :: Int -> IO () Source #

Set the mix frequency measured in Hertz. Higher values mean more sound quality and more CPU usage. Common values are 8000, 11025, 22100, and 44100. The default is 44100.

mikmodModifyDriverModeFlags :: ([DriverModeFlag] -> [DriverModeFlag]) -> IO () Source #

Modify the "mode flags". These flags affect sound output in various ways. For a full explanation of each one see the MikMod docs. Changing DModeInterp, DModeReverse, or DModeSurround will affect playing immediately. The other flags will require a reset. The default flags are set to [DModeStereo, DModeSurround, DMode16Bits, DModeSoftMusic, DModeSoftSndFX].

mikmodSetDriverModeFlags :: [DriverModeFlag] -> IO () Source #

See mikmodModifyDriverModeFlags to avoid clobbering flags you aren't trying to clear.

Core Operations

runMikMod :: Int -> IO a -> IO a Source #

Run an action between mikmodSetup and mikmodExit. It does not handle freeing of Modules or Samples.

mikmodSetup :: Int -> IO () Source #

Registers all drivers and loaders, initializes MikMod, sets a number of sample voices and enables output.

mikmodGetVersion :: IO (Int, Int, Int) Source #

Get the MikMod version as (major, minor, revision).

mikmodGetError :: IO MikModError Source #

Query the current MikMod global errno and get the MikModError expressed there, if any. This value is only valid if checked immediately after an error occurs. If you are interested in MikModErrors use the "Safe" versions of the API methods which return an Either MikModError.

mikmodRegisterAllDrivers :: IO () Source #

Register all drivers. Use this before initializing MikMod with mikmodInit.

mikmodRegisterAllLoaders :: IO () Source #

Register all loaders. Use this before loading any modules.

mikmodInit :: String -> IO () Source #

Initialize the MikMod system using an initialization string. An empty string is acceptable (see MikMod docs for more info). If initialization fails it will throw a MikModError.

Don't try this until you register a driver which is supported by your system. See mikmodRegisterAllDrivers.

See also the convenience functions mikmodSetup and runMikMod.

mikmodInitSafe :: String -> IO (Either MikModError ()) Source #

Same as mikmodInit but doesn't throw exceptions.

mikmodActive :: IO Bool Source #

Returns True if and only if sound output is enabled.

mikmodInfoDriver :: IO (Maybe String) Source #

Get a formatted string describing the available drivers, if any.

mikmodInfoLoader :: IO (Maybe String) Source #

Get a formatted string describing the available loaders, if any.

mikmodSetNumVoices Source #

Arguments

:: Int

Number of music voices or -1

-> Int

Number of sample voices or -1

-> IO () 

Set the number of music voices and sample voices to be used for playback. If either parameter is -1, the currently set value will be retained.

This is executed by playerLoad as a side effect of loading a module to set the number of music voices.

If this operation fails it will throw a MikModError.

mikmodSetNumVoicesSafe :: Int -> Int -> IO (Either MikModError ()) Source #

Same as mikmodSetNumVoices but doesn't throw exceptions.

mikmodReset :: String -> IO () Source #

Reset the driver using the new global variable settings. If the driver has not been initialized, it will be now. Throws a MikModError in case of failure.

mikmodResetSafe :: String -> IO (Either MikModError ()) Source #

Same as mikmodReset but doesn't throw exceptions.

mikmodDisableOutput :: IO () Source #

Disable output.

mikmodEnableOutput :: IO () Source #

Enable output. Playing modules will enable output automatically. However playing samples does not. Therefore use mikmodEnableOutput if you intend to play sound effects with no music. The convenience function mikmodSetup enables output among other things.

mikmodUpdate :: IO () Source #

Update the sound. If you don't call this often enough, then sound might drop out. If you call this too often, the audio driver may eat CPU in a busy loop. Higher quality audio requires calling mikmodUpdate more often (see mikmodSetMixFreq). And finally, on some drivers this is a no-op because there is an audio callback.

Known:

  • On OSX there is an audio callback and polling mikmodUpdate is unnecessary.
  • On Linux mikmodUpdate triggers ALSA's non-blocking IO API and is necessary.

mikmodExit :: IO () Source #

Shutdown the MikMod system.

Module Player Operations

data CuriousFlag Source #

When loading a module, Curious will cause the loader to attempt to load hidden tracks past the end of the song.

Constructors

Curious 
NotCurious 

playerLoad :: FilePath -> Int -> CuriousFlag -> IO ModuleHandle Source #

Load a module from a file.

The second argument is the maximum number of channels to allow. Basic 4 channel mods only need 4 music voices. But some impulse tracker modules use a large number of extra channels for new note actions (NNAs). Only the amount needed will be allocated so using a large value here like 64 doesn't hurt.

This operation has side effects. When the module is loaded the number of music voices will be adjusted (see mikmodSetNumVoices) to accommodate the song. If a song is already playing that needs more voices than the song being loaded, you will hear a reduction in music quality! If want to load many ModuleHandles then use mikmodSetNumVoices afterward to set the number of music voices to some upper bound for the group.

If something goes wrong while loading the module it will throw a MikModError.

playerLoadSafe :: FilePath -> Int -> CuriousFlag -> IO (Either MikModError ModuleHandle) Source #

Same as playerLoad but doesn't throw exceptions.

playerLoadGeneric :: MReader -> Int -> CuriousFlag -> IO ModuleHandle Source #

Same as playerLoad but loads the module data from an MReader.

playerLoadTitle :: FilePath -> IO (Maybe String) Source #

Load only the title from a module file. Returns Nothing if there is no title. If something goes wrong it will throw a MikModError.

playerStart :: ModuleHandle -> IO () Source #

Begin playing a module. If another module is already playing it will be stopped.

playerStop :: IO () Source #

Stop the player.

playerPaused :: IO Bool Source #

Returns True if and only if the player is paused.

playerTogglePause :: IO () Source #

Pause the player if it isn't paused. Otherwise unpause it.

playerActive :: IO Bool Source #

Returns True if and only if a song is playing.

playerFree :: ModuleHandle -> IO () Source #

Free a module and all its contents. If the module was playing then it will be stopped. Discard the ModuleHandle after using this operation.

playerGetChannelVoice :: Int -> IO (Maybe Voice) Source #

Returns the voice corresponding to a module channel.

playerGetModule :: IO (Maybe ModuleHandle) Source #

Get the currently playing module, if any.

data MuteOperation Source #

Inclusive or exclusive selection of channels for muting.

playerMuteChannel :: Int -> IO () Source #

Mute a channel.

playerMuteChannels :: MuteOperation -> Int -> Int -> IO () Source #

Mute a range of channels. MuteOperation determines if the range is inclusive or exclusive.

playerUnmuteChannel :: Int -> IO () Source #

Unmute the given channel.

playerUnmuteChannels :: MuteOperation -> Int -> Int -> IO () Source #

Toggle the muting of a range of channels. MuteOperation determines if the range is inclusive or exclusive.

playerToggleMuteChannel :: Int -> IO () Source #

Toggle the muting of the specified channel.

playerToggleMuteChannels :: MuteOperation -> Int -> Int -> IO () Source #

Toggle the muting of a range of channels. MuteOperation determines if the range is inclusive or exclusive.

playerMuted :: Int -> IO Bool Source #

Return True if and only if a channel is muted.

playerNextPosition :: IO () Source #

Skip to the next position in the current module.

playerPrevPosition :: IO () Source #

Go back to the previous position in the current module.

playerSetPosition :: Int -> IO () Source #

Set the position of the current module.

playerSetSpeed :: Int -> IO () Source #

Set the speed of the current module to a value in the range 1 to 32.

playerSetTempo :: Int -> IO () Source #

Set the tempo of the current module to a value in the range 32 to 255.

Module Operations

type ModuleHandle = Ptr Module Source #

Handle to a Module object which contains the music data and current playback state of a song.

getModuleInfo :: ModuleHandle -> IO ModuleInfo Source #

Get a report of the static aspects of a module.

getModuleRealChannels :: ModuleHandle -> IO Int Source #

During playback, the number of active channels (not counting NNA channels).

getModuleTotalChannels :: ModuleHandle -> IO Int Source #

During playback, the total number of channels (including NNA channels).

getModuleSongTime :: ModuleHandle -> IO Integer Source #

Elapsed song time in units of 1/1024 seconds. That's not milliseconds.

getModuleSongPosition :: ModuleHandle -> IO Int Source #

Current song position.

getModulePatternPosition :: ModuleHandle -> IO Int Source #

Current position in the pattern being played.

setModuleInitSpeed :: ModuleHandle -> Int -> IO () Source #

Set the initial speed of the module. Must be in range 1 - 32.

setModuleInitTempo :: ModuleHandle -> Int -> IO () Source #

Set the initial tempo of the module. Must be in range 32 - 255.

setModulePanning Source #

Arguments

:: ModuleHandle 
-> Int

Channel to set panning on.

-> Int

Pan position from 0 (far left) to 255 (far right).

-> IO () 

Set the pan position of a channel in a module.

getModulePanning :: ModuleHandle -> Int -> IO Int Source #

Query the pan position of a particular channel.

setModuleChannelVolume Source #

Arguments

:: ModuleHandle 
-> Int

Channel to set volume on.

-> Int

Volume level from 0 to 128.

-> IO () 

Set the volume of a channel in a module.

getModuleChannelVolume :: ModuleHandle -> Int -> IO Int Source #

Query the volume of a particular channel.

setModuleBPM :: ModuleHandle -> Int -> IO () Source #

Set the tempo of the module. See playerSetTempo.

setModuleSongSpeed :: ModuleHandle -> Int -> IO () Source #

Set the speed of the module. See playerSetSpeed.

setModuleExtSpeed :: ModuleHandle -> Bool -> IO () Source #

Set the Protracker extended speed effect flag. True means process the effect. Default is True.

setModulePanFlag :: ModuleHandle -> Bool -> IO () Source #

Set the pan flag. True means process pan effects. Default is True.

setModuleWrap :: ModuleHandle -> Bool -> IO () Source #

Set the wrap flag. True means repeat from restart position at end of song. Default is False, song ends.

setModuleRepeatPosition :: ModuleHandle -> Int -> IO () Source #

Set the restart position.

setModuleLoop :: ModuleHandle -> Bool -> IO () Source #

Set the loop flag. False means only process forward loops or same-pattern backward loops. Default is True, process all loops.

setModuleFadeout :: ModuleHandle -> Bool -> IO () Source #

Set the fadeout flag of the module. True means fade out. Default is False.

setModuleRelativeSpeed :: ModuleHandle -> Int -> IO () Source #

This value is added to the module tempo to define actual playback speed. Default is zero.

getModuleSamples :: ModuleHandle -> IO [SampleHandle] Source #

Get handles to the samples contained in a module. I don't think it would be wise to call sampleFree on these samples.

Sample Operations

sampleLoad :: FilePath -> IO SampleHandle Source #

Load a sample from a mono, uncompressed RIFF WAV file. If something goes wrong while loading the sample it will throw a MikModError.

sampleLoadSafe :: FilePath -> IO (Either MikModError SampleHandle) Source #

Same as sampleLoad but doesn't throw exceptions.

sampleLoadGeneric :: MReader -> IO SampleHandle Source #

Same as sampleLoad but read sample data from an MReader.

samplePlay :: SampleHandle -> Int -> IO (Maybe Voice) Source #

Plays a sound effects sample. Picks a voice from the number of voices allocated for use as sound effects. Returns the voice that the sound is being played on. The oldest playing sample will be interrupted if necessary, unless all playing samples are "critical", in which case the sound will not play.

The second argument is the position, in samples, to start playing from.

samplePlayCritical :: SampleHandle -> Int -> IO (Maybe Voice) Source #

Same behavior as samplePlay except that the voice the sound is played on (if any) is given the "critical" status. Note that this will still not result in any critical samples being interrupted.

sampleFree :: SampleHandle -> IO () Source #

Free a sample. Do not sampleFree samples aquired via getModuleSamples. Those are freed with playerFree. Discard the SampleHandle after using this operation.

getSampleInfo :: SampleHandle -> IO SampleInfo Source #

Get a report of the current state of a sample.

data Pan Source #

Pan settings.

Constructors

Pan Int 
PanSurround 

Instances

Eq Pan Source # 

Methods

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

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

Show Pan Source # 

Methods

showsPrec :: Int -> Pan -> ShowS #

show :: Pan -> String #

showList :: [Pan] -> ShowS #

panLeft :: Pan Source #

Far left pan. panLeft = Pan 0.

panRight :: Pan Source #

Far right pan. panRight = Pan 255.

setSamplePanning :: SampleHandle -> Pan -> IO () Source #

Set the panning value of the sample. Valid values range from panLeft (0) to panRight (255), or PanSurround.

setSampleSpeed :: SampleHandle -> Int -> IO () Source #

Set the sample playing frequency in Hertz.

setSampleVolume :: SampleHandle -> Int -> IO () Source #

Set sample volume to a range 0 to 64 (65 levels).

modifySampleFlags :: SampleHandle -> ([SampleFlag] -> [SampleFlag]) -> IO () Source #

Modify the sample flags. Useful for setting the loop, reverse, and bi-directional playback characteristics of the sample.

setSampleFlags :: SampleHandle -> [SampleFlag] -> IO () Source #

See modifySampleFlags to avoid clobbering flags you aren't trying to clear, such as the sample format flags.

getSampleInFlags :: SampleHandle -> IO [SampleFlag] Source #

Query the "on disk" flags of the sample if you're curious about the original format.

getSampleLength :: SampleHandle -> IO Int Source #

Query the length of the sample... in samples.

setSampleLoopStart :: SampleHandle -> Int -> IO () Source #

Set the loop starting position in samples.

setSampleLoopEnd :: SampleHandle -> Int -> IO () Source #

Set the loop end position in samples.

Voice Operations

newtype Voice Source #

MikMod distinguishes module channels from voices. Sound effects and music both work by playing samples on voices. At most one sample can play on a voice at a time. Operations on the voice level take a voice number which you can get using playerGetChannelVoice and samplePlay.

Constructors

Voice 

Fields

Instances

Eq Voice Source # 

Methods

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

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

Ord Voice Source # 

Methods

compare :: Voice -> Voice -> Ordering #

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

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

(>) :: Voice -> Voice -> Bool #

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

max :: Voice -> Voice -> Voice #

min :: Voice -> Voice -> Voice #

Show Voice Source # 

Methods

showsPrec :: Int -> Voice -> ShowS #

show :: Voice -> String #

showList :: [Voice] -> ShowS #

voicePlay :: Voice -> SampleHandle -> Int -> IO () Source #

Play a sample on the specified voice starting from the specified position in samples. The playing sample will have the same "critical status" as the previous sample played on this voice.

voiceStop :: Voice -> IO () Source #

Stop a voice from playing.

voiceStopped :: Voice -> IO Bool Source #

Returns True if and only if the specified voice is not playing.

voiceSetVolume :: Voice -> Int -> IO () Source #

Set a voice's volume to a value in the range 0 to 256. There are 257 volume levels.

voiceSetFrequency :: Voice -> Int -> IO () Source #

Set a voice's frequency in Hertz.

voiceSetPanning :: Voice -> Int -> IO () Source #

Set a voice's pan position. 0 is far left. 127 is center. 255 is far right.

voiceGetPosition :: Voice -> IO Int Source #

Query the position (in samples) of the sample playing on this voice. If no sample is playing it will return zero. On some drivers this operation does not work and will return -1.

voiceRealVolume :: Voice -> IO Int Source #

Compute the "actual playing volume" of the voice. The result will be in the range 0 - 65535. On some drivers this operation does not work and will return zero.

MReaders

data MReader Source #

Collection of IO operations that MikMod can use to load data from an arbitrary source, such as a memory buffer or zip file.

Constructors

MReader 

Fields

  • readerSeek :: Int -> SeekMode -> IO Outcome

    Move the read position. Return Ok for success or Fail for failure.

  • readerTell :: IO Int

    Report the current read position.

  • readerRead :: Int -> IO (Maybe ByteString)

    Return a ByteString of length (at most) n and advance the read position. Return an empty ByteString if already at EOF. Return Nothing in case of an error.

  • readerGet :: IO (Maybe Word8)

    Return one byte and advance the read position. If an error occurs or we are at the end-of-stream, then return Nothing.

  • readerEof :: IO IsEOF

    Return EOF if we are at the end of the stream. Otherwise return NotEOF.

data Outcome Source #

Used for the very undescriptive possible outcomes of a readerSeek.

Constructors

Ok 
Fail 

data IsEOF Source #

The result of a readerEof call.

Constructors

EOF 
NotEOF 

Instances

Eq IsEOF Source # 

Methods

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

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

Show IsEOF Source # 

Methods

showsPrec :: Int -> IsEOF -> ShowS #

show :: IsEOF -> String #

showList :: [IsEOF] -> ShowS #

byteStringReader :: ByteString -> IORef Int -> MReader Source #

Make an MReader from a ByteString and a mutable variable for the read position.

handleReader :: Handle -> MReader Source #

Wrap a Handle so it works like an MReader.

Errors

data MikModError Source #

MikMod reports errors as either critical or not. A critical error means the system state was reset because it could not continue in the face of the error.

data MikModErrno Source #

The possible things to be found in MikMod_errno

Constructors

MMErrNoError 
MMErrOpeningFile 
MMErrOutOfMemory 
MMErrDynamicLinking 
MMErrSampleTooBig 
MMErrOutOfHandles 
MMErrUnknownWaveType 
MMErrLoadingPattern 
MMErrLoadingTrack 
MMErrLoadingHeader 
MMErrLoadingSampleinfo 
MMErrNotAModule 
MMErrNotAStream 
MMErrMedSynthsamples 
MMErrItpackInvalidData 
MMErrDetectingDevice 
MMErrInvalidDevice 
MMErrInitializingMixer 
MMErrOpeningAudio 
MMErr8bitOnly 
MMErr16bitOnly 
MMErrStereoOnly 
MMErrUlaw 
MMErrNonBlock 
MMErrAfAudioPort 
MMErrAixConfigInit 
MMErrAixConfigControl 
MMErrAixConfigStart 
MMErrGusSettings 
MMErrGusReset 
MMErrGusTimer 
MMErrHpSetsamplesize 
MMErrHpSetspeed 
MMErrHpChannels 
MMErrHpAudioOutput 
MMErrHpAudioDesc 
MMErrHpBuffersize 
MMErrOssSetfragment 
MMErrOssSetsamplesize 
MMErrOssSetstereo 
MMErrOssSetspeed 
MMErrSgiSpeed 
MMErrSgi16bit 
MMErrSgi8bit 
MMErrSgiStereo 
MMErrSgiMono 
MMErrSunInit 
MMErrOs2Mixsetup 
MMErrOs2Semaphore 
MMErrOs2Timer 
MMErrOs2Thread 
MMErrDsPriority 
MMErrDsBuffer 
MMErrDsFormat 
MMErrDsNotify 
MMErrDsEvent 
MMErrDsThread 
MMErrDsUpdate 
MMErrWinmmHandle 
MMErrWinmmAllocated 
MMErrWinmmDeviceid 
MMErrWinmmFormat 
MMErrWinmmUnknown 
MMErrMacSpeed 
MMErrMacStart 
MMErrOsxUnknownDevice 
MMErrOsxBadProperty 
MMErrOsxUnsupportedFormat 
MMErrOsxSetStereo 
MMErrOsxBufferAlloc 
MMErrOsxAddIoProc 
MMErrOsxDeviceStart 
MMErrOsxPthread 
MMErrDoswssStartdma 
MMErrDossbStartdma 
MMErrNoFloat32 
MMErrOpenalCreatectx 
MMErrOpenalCtxcurrent 
MMErrOpenalGenbuffers 
MMErrOpenalGensources 
MMErrOpenalSource 
MMErrOpenalQueuebuffers 
MMErrOpenalUnqueuebuffers 
MMErrOpenalBufferdata 
MMErrOpenalGetsource 
MMErrOpenalSourceplay 
MMErrOpenalSourcestop 
MMErrAlsaNoconfig 
MMErrAlsaSetparams 
MMErrAlsaSetformat 
MMErrAlsaSetrate 
MMErrAlsaSetchannels 
MMErrAlsaBuffersize 
MMErrAlsaPcmStart 
MMErrAlsaPcmWrite 
MMErrAlsaPcmRecover 
MMErrMax 
MMErrUnknown CInt 

Esoterica

mikmodInitThreads :: IO Bool Source #

If your libmikmod has pthread support, returns True. Otherwise this may initialize internal mutexes to support multi-threaded access anyway. A result of True indicates this was successful. False indicates no support for multi-threaded access is available. It is safe to call this multiple times. Only the first call has any effect.

Short story: Before attempting to use MikMod from multiple threads execute this and check that the result is True.

This only has an effect on Win32, OS/2, and EMX.

withMikMod :: IO a -> IO a Source #

Execute the action after calling MikMod_Lock. Calls MikMod_Unlock afterwards even if an error occurred. If mikmodInitThreads returns True then it means all calls to libmikmod will be protected by internal mutexes. Therefore using MikMod functions inside a withMikMod will deadlock. Allowing clients to manually lock MikMod is probably only useful when manipulating shared data across the API boundary.