{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Applicative.PlaybackOptions
( consume
, crossfade
, random
, repeat
, setVolume
, single
, replayGainMode
, replayGainStatus
, mixrampDb
, mixrampDelay
) where
import Network.MPD.Applicative.Internal
import Network.MPD.Applicative.Util
import Network.MPD.Commands.Arg hiding (Command)
import Network.MPD.Commands.Types
import Network.MPD.Util (toAssocList)
import Control.Applicative
import Prelude hiding (repeat)
consume :: Bool -> Command ()
consume f = Command emptyResponse ["consume" <@> f]
crossfade :: Seconds -> Command ()
crossfade secs = Command emptyResponse ["crossfade" <@> secs]
random :: Bool -> Command ()
random f = Command emptyResponse ["random" <@> f]
repeat :: Bool -> Command ()
repeat f = Command emptyResponse ["repeat" <@> f]
setVolume :: Volume -> Command ()
setVolume vol = Command emptyResponse ["setvol" <@> vol]
single :: Bool -> Command ()
single f = Command emptyResponse ["single" <@> f]
replayGainMode :: ReplayGainMode -> Command ()
replayGainMode f = Command emptyResponse ["replay_gain_mode" <@> f]
replayGainStatus :: Command [(String, String)]
replayGainStatus = Command p ["replay_gain_status"]
where
p = map decodePair . toAssocList <$> getResponse
mixrampDb :: Decibels -> Command ()
mixrampDb db = Command emptyResponse ["mixrampdb" <@> db]
mixrampDelay :: Seconds -> Command ()
mixrampDelay sec = Command emptyResponse ["mixrampdelay" <@> sec]