alsa-mixer-0.3.0.1: Bindings to the ALSA simple mixer API.
Copyright(c) Thomas Tuegel 2011
LicenseBSD
MaintainerThomas Tuegel <ttuegel@gmail.com>
Stabilityexperimental
Portabilitynon-portable (Linux only)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.ALSA.Mixer

Description

This library provides bindings to the Advanced Linux Sound Architecture (ALSA) library API. The portability of this library is limited to systems with ALSA (i.e., Linux systems). The functions in this library throw errors of type T on failure.

Synopsis

Types

data Control Source #

Control represents one of the controls belonging to an ALSA mixer element. Each control has a number of playback and capture channels. The control may also have a switch and/or a volume capability associated with it. The capability can be common to both playback and capture, or there can be separate capabilities for each.

data PerChannel e Source #

PerChannel represents a capability that with either a separate value for each channel or with a common value for all channels.

Constructors

Joined 

Fields

PerChannel 

Fields

data Volume Source #

Volume represents a volume capability. There may be a separate value per channel, but each capability has only one range.

Constructors

Volume 

Fields

type Switch = PerChannel Bool Source #

Switch represents a switch capability for controls and channels that can be muted and unmuted.

data CUInt #

Haskell type representing the C unsigned int type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Storable CUInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CUInt -> Int #

alignment :: CUInt -> Int #

peekElemOff :: Ptr CUInt -> Int -> IO CUInt #

pokeElemOff :: Ptr CUInt -> Int -> CUInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CUInt #

pokeByteOff :: Ptr b -> Int -> CUInt -> IO () #

peek :: Ptr CUInt -> IO CUInt #

poke :: Ptr CUInt -> CUInt -> IO () #

Bits CUInt 
Instance details

Defined in Foreign.C.Types

FiniteBits CUInt 
Instance details

Defined in Foreign.C.Types

Bounded CUInt 
Instance details

Defined in Foreign.C.Types

Enum CUInt 
Instance details

Defined in Foreign.C.Types

Ix CUInt 
Instance details

Defined in Foreign.C.Types

Num CUInt 
Instance details

Defined in Foreign.C.Types

Read CUInt 
Instance details

Defined in Foreign.C.Types

Integral CUInt 
Instance details

Defined in Foreign.C.Types

Real CUInt 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CUInt -> Rational #

Show CUInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CUInt -> ShowS #

show :: CUInt -> String #

showList :: [CUInt] -> ShowS #

Eq CUInt 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Ord CUInt 
Instance details

Defined in Foreign.C.Types

Methods

compare :: CUInt -> CUInt -> Ordering #

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

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

(>) :: CUInt -> CUInt -> Bool #

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

max :: CUInt -> CUInt -> CUInt #

min :: CUInt -> CUInt -> CUInt #

data CLong #

Haskell type representing the C long type. (The concrete types of Foreign.C.Types are platform-specific.)

Instances

Instances details
Storable CLong 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CLong -> Int #

alignment :: CLong -> Int #

peekElemOff :: Ptr CLong -> Int -> IO CLong #

pokeElemOff :: Ptr CLong -> Int -> CLong -> IO () #

peekByteOff :: Ptr b -> Int -> IO CLong #

pokeByteOff :: Ptr b -> Int -> CLong -> IO () #

peek :: Ptr CLong -> IO CLong #

poke :: Ptr CLong -> CLong -> IO () #

Bits CLong 
Instance details

Defined in Foreign.C.Types

FiniteBits CLong 
Instance details

Defined in Foreign.C.Types

Bounded CLong 
Instance details

Defined in Foreign.C.Types

Enum CLong 
Instance details

Defined in Foreign.C.Types

Ix CLong 
Instance details

Defined in Foreign.C.Types

Num CLong 
Instance details

Defined in Foreign.C.Types

Read CLong 
Instance details

Defined in Foreign.C.Types

Integral CLong 
Instance details

Defined in Foreign.C.Types

Real CLong 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CLong -> Rational #

Show CLong 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CLong -> ShowS #

show :: CLong -> String #

showList :: [CLong] -> ShowS #

Eq CLong 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Ord CLong 
Instance details

Defined in Foreign.C.Types

Methods

compare :: CLong -> CLong -> Ordering #

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

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

(>) :: CLong -> CLong -> Bool #

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

max :: CLong -> CLong -> CLong #

min :: CLong -> CLong -> CLong #

Functions

Mixers

controls :: Mixer -> IO [Control] Source #

All the Control objects associated with a particular Mixer.

withMixer :: String -> (Mixer -> IO a) -> IO a Source #

Perform an IO action with the named mixer. An exception of type T will be thrown if the named mixer cannot be found. A mixer named "default" should always exist.

Controls

getControlByName Source #

Arguments

:: Mixer

Mixer

-> String

Control name

-> IO (Maybe Control) 

Get the named Control, if it exists, from the named Mixer.

common :: Either a (Maybe a, Maybe a) -> Maybe a Source #

For a given capability, which may be for either playback or capture, or common to both, return the common capability if it exists.

playback :: Either a (Maybe a, Maybe a) -> Maybe a Source #

For a given capability, which may be for either playback or capture, or common to both, return the playback capability if it exists.

capture :: Either a (Maybe a, Maybe a) -> Maybe a Source #

For a given capability, which may be for either playback or capture, or common to both, return the capture capability if it exists.

PerChannels

channels :: PerChannel e -> [Channel] Source #

All channels supported by a PerChannel object.

joined :: PerChannel e -> Bool Source #

True if the PerChannel object has a common value for all channels.

perChannel :: PerChannel e -> Bool Source #

True if the PerChannel object has a separate value for each channel.

getChannel :: Channel -> PerChannel x -> IO (Maybe x) Source #

Get the value associated with a particular channel, if that channel exists.

setChannel :: Channel -> PerChannel x -> x -> IO () Source #

Set the value associated with a particular channel, if that channel exists.

Examples

Getting and setting the volume of a Control

This example demonstrates the method of accessing the volume of a Control. The example function reads the volume and increases it by the value supplied.

  changeVolumeBy :: CLong -> IO ()
  changeVolumeBy i =
      withMixer "default" $ \mixer ->
        do Just control <- getControlByName mixer "Master"
           let Just playbackVolume = playback $ volume control
           (min, max) <- getRange playbackVolume
           Just vol <- getChannel FrontLeft $ value $ playbackVolume
           when ((i > 0 && vol < max) || (i < 0 && vol > min))
             $ setChannel FrontLeft (value $ playbackVolume) $ vol + i

Getting and setting the switch of a Control

This example demonstrates the method of accessing the switch of a Control. The example function reads the value of the switch and toggles it.

  toggleMute :: IO ()
  toggleMute =
      withMixer "default" $ \mixer ->
        do Just control <- getControlByName mixer "Master"
           let Just playbackSwitch = playback $ switch control
           Just sw <- getChannel FrontLeft playbackSwitch
           setChannel FrontLeft playbackSwitch $ not sw