{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Commands.PlaybackControl
( next
, pause
, toggle
, play
, playId
, previous
, seek
, seekId
, seekCur
, stop
) where
import qualified Network.MPD.Applicative.Internal as A
import qualified Network.MPD.Applicative.PlaybackControl as A
import Network.MPD.Commands.Types
import Network.MPD.Core
next :: MonadMPD m => m ()
next :: forall (m :: * -> *). MonadMPD m => m ()
next = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command ()
A.next
pause :: MonadMPD m => Bool -> m ()
pause :: forall (m :: * -> *). MonadMPD m => Bool -> m ()
pause = 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.pause
toggle :: MonadMPD m => m ()
toggle :: forall (m :: * -> *). MonadMPD m => m ()
toggle = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command ()
A.toggle
play :: MonadMPD m => Maybe Position -> m ()
play :: forall (m :: * -> *). MonadMPD m => Maybe Position -> m ()
play = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (Maybe Position -> Command ()) -> Maybe Position -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Position -> Command ()
A.play
playId :: MonadMPD m => Id -> m ()
playId :: forall (m :: * -> *). MonadMPD m => Id -> m ()
playId = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Id -> Command ()) -> Id -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id -> Command ()
A.playId
previous :: MonadMPD m => m ()
previous :: forall (m :: * -> *). MonadMPD m => m ()
previous = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command ()
A.previous
seek :: MonadMPD m => Position -> FractionalSeconds -> m ()
seek :: forall (m :: * -> *).
MonadMPD m =>
Position -> FractionalSeconds -> m ()
seek Position
pos = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (FractionalSeconds -> Command ()) -> FractionalSeconds -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Position -> FractionalSeconds -> Command ()
A.seek Position
pos
seekId :: MonadMPD m => Id -> FractionalSeconds -> m ()
seekId :: forall (m :: * -> *). MonadMPD m => Id -> FractionalSeconds -> m ()
seekId Id
id' = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (FractionalSeconds -> Command ()) -> FractionalSeconds -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id -> FractionalSeconds -> Command ()
A.seekId Id
id'
seekCur :: MonadMPD m => Bool -> FractionalSeconds -> m ()
seekCur :: forall (m :: * -> *).
MonadMPD m =>
Bool -> FractionalSeconds -> m ()
seekCur Bool
bool = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (FractionalSeconds -> Command ()) -> FractionalSeconds -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> FractionalSeconds -> Command ()
A.seekCur Bool
bool
stop :: MonadMPD m => m ()
stop :: forall (m :: * -> *). MonadMPD m => m ()
stop = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command ()
A.stop