{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Commands.PlaybackOptions
( consume
, crossfade
, random
, repeat
, setVolume
, single
, replayGainMode
, replayGainStatus
) where
import qualified Network.MPD.Applicative.Internal as A
import qualified Network.MPD.Applicative.PlaybackOptions as A
import Network.MPD.Commands.Types
import Network.MPD.Core
import Prelude hiding (repeat)
consume :: MonadMPD m => Bool -> m ()
consume :: forall (m :: * -> *). MonadMPD m => Bool -> m ()
consume = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Bool -> Command ()) -> Bool -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Command ()
A.consume
crossfade :: MonadMPD m => Seconds -> m ()
crossfade :: forall (m :: * -> *). MonadMPD m => Seconds -> m ()
crossfade = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Seconds -> Command ()) -> Seconds -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seconds -> Command ()
A.crossfade
random :: MonadMPD m => Bool -> m ()
random :: forall (m :: * -> *). MonadMPD m => Bool -> m ()
random = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Bool -> Command ()) -> Bool -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Command ()
A.random
repeat :: MonadMPD m => Bool -> m ()
repeat :: forall (m :: * -> *). MonadMPD m => Bool -> m ()
repeat = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Bool -> Command ()) -> Bool -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Command ()
A.repeat
setVolume :: MonadMPD m => Volume -> m ()
setVolume :: forall (m :: * -> *). MonadMPD m => Volume -> m ()
setVolume = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Volume -> Command ()) -> Volume -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Volume -> Command ()
A.setVolume
single :: MonadMPD m => Bool -> m ()
single :: forall (m :: * -> *). MonadMPD m => Bool -> m ()
single = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Bool -> Command ()) -> Bool -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Command ()
A.single
replayGainMode :: MonadMPD m => ReplayGainMode -> m ()
replayGainMode :: forall (m :: * -> *). MonadMPD m => ReplayGainMode -> m ()
replayGainMode = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (ReplayGainMode -> Command ()) -> ReplayGainMode -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReplayGainMode -> Command ()
A.replayGainMode
replayGainStatus :: MonadMPD m => m [(String, String)]
replayGainStatus :: forall (m :: * -> *). MonadMPD m => m [(String, String)]
replayGainStatus = Command [(String, String)] -> m [(String, String)]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command [(String, String)]
A.replayGainStatus