mikmod-0.1.0.1: bindings to libmikmod

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.

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 100000
  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 100000
  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 100000
  sampleFree samp

Globals

mikmodGetMusicVolume :: IO Int Source

Query the global music volume. It has range 0 to 128 (there are 129 possible volume levels). The default music volume is 128.

mikmodSetMusicVolume :: Int -> IO () Source

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

mikmodGetPanSep :: IO Int Source

Query the global stereo separation. It has range 0 to 128 where 0 means mono sound and 128 means full separation. The default pan sep is 128.

mikmodSetPanSep :: Int -> IO () Source

Set the global stereo separation. The argument must be in the range 0 to 128.

mikmodGetReverb :: IO Int Source

Query the global reverb. It has range 0 to 15 where 0 means no reverb and 15 means extreme reverb. The default reverb is zero.

mikmodSetReverb :: Int -> IO () Source

Set the global reverb. The argument must be in the range 0 to 15.

mikmodGetSndFXVolume :: IO Int Source

Query the global sound effects volume. It has range 0 to 128. The default sound effects volume is 128.

mikmodSetSndFXVolume :: Int -> IO () Source

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

mikmodGetVolume :: IO Int Source

Query the global overall sound volume. It has range 0 to 128. The default overall sound volume is 128.

mikmodSetVolume :: Int -> IO () Source

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

mikmodGetDeviceIndex :: IO Int Source

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

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.

mikmodGetDriver :: IO (Maybe MDriverInfo) Source

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

mikmodGetMixFreq :: IO Int Source

Query the mix frequency setting measured in Hertz. Higher values mean more sound quality and more CPU usage. The default is 44100.

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.

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

Set 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].

Core Operations

mikmodSetup :: Int -> IO () Source

Registers all drivers and loaders, initializes MikMod, sets a number of sound effect 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 or samples.

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.

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

Same as mikmodInit but doesn't throw exceptions.

mikmodActive :: IO Bool Source

Check if a module is currently playing.

mikmodInfoDriver :: IO (Maybe String) Source

Get a formatted string describing the current driver, if any.

mikmodInfoLoader :: IO (Maybe String) Source

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

mikmodSetNumVoices :: Int -> Int -> IO () Source

Set the number of music voices and sample voices to be used for playback. If this operation fails for some reason it will throw a MikModError.

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

Same as mikmodSetNumVoices but doesn't throw exceptions.

mikmodReset :: String -> IO () Source

Reinitialize the MikMod system. This might be necessary after tweaking one of MikMods global parameters. If reinitialization fails it will throw a MikModError.

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

Same as mikmodReset but doesn't throw exceptions.

mikmodDisableOutput :: IO () Source

Disable output.

mikmodEnableOutput :: IO () Source

Enable output. This happens automatically when playing a module. But according to the examples, mikmodEnableOutput is required before sound effects will work by themselves.

mikmodUpdate :: IO () Source

On some drivers mikmodUpdate must called periodically to fill an audio out buffer, or sound wont play. In those environments you must call it more often for higher quality audio (see mikmodSetMixFreq).

Many audio backends have luckily taken this out of the programmer's hands and so mikmodUpdate may be unnecessary.

mikmodExit :: IO () Source

Shutdown the MikMod system.

mikmodInitThreads :: IO Bool Source

Check if MikMod is thread safe.

withMikMod :: IO a -> IO a Source

Execute the action after calling MikMod_Lock. Calls MikMod_Unlock afterwards even if an error occurred. See the MikMod docs to determine if this is necessary.

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. 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 the MReader.

playerLoadGenericSafe :: MReader -> Int -> CuriousFlag -> IO (Either MikModError ModuleHandle) Source

Same as playerLoadGeneric but doesn't throw exceptions.

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

Load only the title from a module file. Returns Nothing in case there is no title or an error occurred!

playerStart :: ModuleHandle -> IO () Source

Begin playing the given module.

playerStop :: IO () Source

Stop the player.

playerPaused :: IO Bool Source

Check if the current module is paused.

playerTogglePause :: IO () Source

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

playerActive :: IO Bool Source

Check if the player is active.

playerFree :: ModuleHandle -> IO () Source

Free a module and stop it if it is playing. You must discard the ModuleHandle after this operation.

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

This function determines the voice corresponding to the specified module channel.

playerGetModule :: IO (Maybe ModuleHandle) Source

Get the currently playing module, if any.

data MuteOperation Source

Operations that manipulate muting of multiple channels use one of two interpretations of the specified channge range. MuteExclusive means mute / unmute / toggle muting of all channels outside the specified range.

playerMuteChannel :: Int -> IO () Source

Mute the given 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. If MuteInclusive is used this will include all channels in the given range. MuteExclusive is the opposite of MuteInclusive.

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

Check if a channel is muted.

playerNextPosition :: IO () Source

Skip to the next position in the module.

playerPrevPosition :: IO () Source

Go back to the previous position in the module.

playerSetPosition :: Int -> IO () Source

Set the position of the current module.

playerSetSpeed :: Int -> IO () Source

Set the speed of the current module, 1 to 32.

playerSetTempo :: Int -> IO () Source

Set the tempo of the current module, 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.

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 same 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 a MReader.

sampleLoadGenericSafe :: MReader -> IO (Either MikModError SampleHandle) Source

Same as sampleLoadGeneric but doesn't throw exceptions.

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

Play the given sample from the specified starting position (in samples). If there aren't enough voices available to do this, it will replace the oldest non-critical sample currently playing.

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

This is like samplePlay but the sample will not be interrupted by other samples played later (unless all voices are being used by critical samples and yet another critical sample is played).

sampleFree :: SampleHandle -> IO () Source

Free a sample. You must discard the SampleHandle after 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

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).

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

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

getSampleInFlags :: SampleHandle -> IO [SampleFlag] Source

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

getSampleLength :: SampleHandle -> IO Int Source

Query the length of the sample... in samples. The byte-size of a (big) sample is related to the size of a (small) sample in bytes, either 8bit or 16bit.

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 mikmodGetChannelVoice.

Constructors

Voice 

Fields

marshalVoice :: SBYTE
 

Instances

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

Play a sample on the specified voice starting from the specified position. 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

Check if a voice is currently not playing.

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

Set a voice's volume, 0 - 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 Int

Move the read position. Return 0 for success and -1 for failure.

readerTell :: IO Int

Report the current read position.

readerRead :: Ptr Word8 -> Int -> IO Bool

Write a number of bytes to the destination and advance the read position. Return True if an error occurred or False otherwise. EOF is not an error.

readerGet :: IO Int

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

readerEof :: IO Bool

Return True if we are at the end of the stream. Otherwise return False.

newByteStringReader :: ByteString -> IO MReader Source

Create an MReader from a ByteString.

newHandleReader :: Handle -> MReader Source

Wrap a Handle so it works like an MReader.

eof :: Int Source

To be returned by a readerGet if called at end-of-stream.

Errors

data MikModError Source

A 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.