module Sound.ALSA.Mixer
(
Control(..)
, Mixer()
, Channel(..)
, PerChannel(..)
, Volume(..)
, Switch()
, CUInt
, CLong
, controls
, withMixer
, getControlByName
, common
, playback
, capture
, channels
, allChannels
, joined
, perChannel
, getChannel
, setChannel
) where
import Control.Monad ( forM, liftM, when )
import Data.Maybe ( catMaybes )
import Foreign.C.Error ( Errno(..) )
import Foreign.C.Types
import Sound.ALSA.Exception ( catchErrno )
import Sound.ALSA.Mixer.Internal
data Control = Control { index :: CUInt
, name :: String
, switch :: Either Switch (Maybe Switch, Maybe Switch)
, volume :: Either Volume (Maybe Volume, Maybe Volume)
}
data PerChannel e = Joined { getJoined :: IO e
, setJoined :: e -> IO ()
, joinedChannels :: [Channel]
}
| PerChannel { getPerChannel :: IO [(Channel, e)]
, setPerChannel :: [(Channel, e)] -> IO ()
, perChannels :: [Channel]
}
joined :: PerChannel e -> Bool
joined j@(Joined _ _ _) = True
joined _ = False
perChannel :: PerChannel e -> Bool
perChannel p@(PerChannel _ _ _) = True
perChannel _ = False
channels :: PerChannel e -> [Channel]
channels p | joined p = joinedChannels p
| otherwise = perChannels p
type Switch = PerChannel Bool
data Volume = Volume { getRange :: IO (CLong, CLong)
, setRange :: (CLong, CLong) -> IO ()
, getRangeDb :: IO (CLong, CLong)
, value :: PerChannel CLong
, dB :: PerChannel CLong
}
getChannel :: Channel -> PerChannel x -> IO (Maybe x)
getChannel c p | joined p = let r | c `elem` channels p =
liftM Just $ getJoined p
| otherwise = return Nothing
in r
| otherwise = liftM (lookup c) $ getPerChannel p
setChannel :: Channel -> PerChannel x -> x -> IO ()
setChannel c p v | joined p = when (c `elem` channels p) $ setJoined p v
| otherwise = setPerChannel p [(c, v)]
playback :: Either a (Maybe a, Maybe a) -> Maybe a
playback (Left _) = Nothing
playback (Right (x, _)) = x
capture :: Either a (Maybe a, Maybe a) -> Maybe a
capture (Left _) = Nothing
capture (Right (_, x)) = x
common :: Either a (Maybe a, Maybe a) -> Maybe a
common (Left x) = Just x
common (Right _) = Nothing
mkSwitch :: SimpleElement -> IO (Either Switch (Maybe Switch, Maybe Switch))
mkSwitch se = do
hasPlayChan <- mapM (hasPlaybackChannel se) allChannels
hasCaptChan <- mapM (hasCaptureChannel se) allChannels
let pChans = map fst $ filter snd $ zip allChannels hasPlayChan
cChans = map fst $ filter snd $ zip allChannels hasCaptChan
hasComSw <- hasCommonSwitch se
hasPlaySw <- hasPlaybackSwitch se
hasPlaySwJ <- hasPlaybackSwitchJoined se
hasCaptSw <- hasCaptureSwitch se
hasCaptSwJ <- hasCaptureSwitchJoined se
return $ if hasComSw
then Left $ if hasPlaySwJ
then comJoinedSwitch pChans
else comPerChannelSwitch pChans
else let playSw | not hasPlaySw = Nothing
| otherwise = Just
$ if hasPlaySwJ
then playJoinedSwitch pChans
else playPerChannelSwitch pChans
captSw | not hasCaptSw = Nothing
| otherwise = Just
$ if hasCaptSwJ
then captJoinedSwitch cChans
else captPerChannelSwitch cChans
in Right (playSw, captSw)
where joined fGet fSet chans =
Joined { getJoined = fGet se (head chans)
, setJoined = fSet se (head chans)
, joinedChannels = chans
}
perChannel fGet fSet chans =
PerChannel { getPerChannel = liftM (zip chans)
$ mapM (fGet se) chans
, setPerChannel = mapM_ (uncurry (fSet se))
, perChannels = chans
}
comJoinedSwitch = joined getPlaybackSwitch setPlaybackSwitch
comPerChannelSwitch = perChannel getPlaybackSwitch setPlaybackSwitch
playJoinedSwitch = comJoinedSwitch
playPerChannelSwitch = comPerChannelSwitch
captJoinedSwitch = joined getCaptureSwitch setCaptureSwitch
captPerChannelSwitch = perChannel getCaptureSwitch setCaptureSwitch
mkVolume :: SimpleElement -> IO (Either Volume (Maybe Volume, Maybe Volume))
mkVolume se = do
hasPlayChan <- mapM (hasPlaybackChannel se) allChannels
hasCaptChan <- mapM (hasCaptureChannel se) allChannels
let pChans = map fst $ filter snd $ zip allChannels hasPlayChan
cChans = map fst $ filter snd $ zip allChannels hasCaptChan
hasComV <- hasCommonVolume se
hasPlayV <- hasPlaybackVolume se
hasPlayVJ <- hasPlaybackVolumeJoined se
hasCaptV <- hasCaptureVolume se
hasCaptVJ <- hasCaptureVolumeJoined se
return $
if hasComV
then let (v, d) | hasPlayVJ = ( comJoinedVol pChans
, comJoinedDb pChans
)
| otherwise = ( comPerChannelVol pChans
, comPerChannelDb pChans
)
in Left $ playVolume { value = v, dB = d }
else let playVol | not hasPlayV = Nothing
| otherwise =
let (v, d) | hasPlayVJ =
( playJoinedVol pChans
, playJoinedDb pChans
)
| otherwise =
( playPerChannelVol pChans
, playPerChannelDb pChans
)
in Just playVolume { value = v, dB = d }
captVol | not hasCaptV = Nothing
| otherwise =
let (v, d) | hasCaptVJ =
( captJoinedVol cChans
, captJoinedDb cChans
)
| otherwise =
( captPerChannelVol cChans
, captPerChannelDb cChans
)
in Just $ captVolume { value = v, dB = d }
in Right (playVol, captVol)
where j fGet fSet chans =
Joined { getJoined = fGet se (head chans)
, setJoined = fSet se (head chans)
, joinedChannels = chans
}
pc fGet fSet chans =
PerChannel { getPerChannel = liftM (zip chans)
$ mapM (fGet se) chans
, setPerChannel = mapM_ (uncurry (fSet se))
, perChannels = chans
}
playVolume = Volume { getRange = getPlaybackVolumeRange se
, setRange = setPlaybackVolumeRange se
, getRangeDb = getPlaybackDbRange se
, value = undefined
, dB = undefined
}
captVolume = Volume { getRange = getCaptureVolumeRange se
, setRange = setCaptureVolumeRange se
, getRangeDb = getCaptureDbRange se
, value = undefined
, dB = undefined
}
comJoinedVol = j getPlaybackVolume setPlaybackVolume
comJoinedDb = j getPlaybackDb setPlaybackDb
comPerChannelVol = pc getPlaybackVolume setPlaybackVolume
comPerChannelDb = pc getPlaybackDb setPlaybackDb
playJoinedVol = comJoinedVol
playPerChannelVol = comPerChannelVol
playJoinedDb = comJoinedDb
playPerChannelDb = comPerChannelDb
captJoinedVol = j getCaptureVolume setCaptureVolume
captPerChannelVol = pc getCaptureVolume setCaptureVolume
captJoinedDb = j getCaptureDb setCaptureDb
captPerChannelDb = pc getCaptureDb setCaptureDb
controls :: Mixer -> IO [Control]
controls mix = do
es <- elements mix
forM es $ \(idN, se) -> do
n <- getName idN
i <- getIndex idN
sw <- mkSwitch se
v <- mkVolume se
return $! Control { name = n
, index = i
, switch = sw
, volume = v
}
getControlByName :: Mixer
-> String
-> IO (Maybe Control)
getControlByName mix controlName = do
cs <- controls mix
return $ lookup controlName $ zip (map name cs) cs