{-# LANGUAGE OverloadedStrings #-}

{- |
Module      : Network.MPD.Commands.PlaybackControl
Copyright   : (c) Ben Sinclair 2005-2009, Joachim Fasting 2012
License     : MIT (see LICENSE)

Maintainer  : joachifm@fastmail.fm
Stability   : stable
Portability : unportable

Controlling playback.
-}

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

-- | Play the next song.
next :: MonadMPD m => m ()
next :: m ()
next = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command ()
A.next

-- | Pauses playback on True, resumes on False.
pause :: MonadMPD m => Bool -> m ()
pause :: 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

-- | Toggles play\/pause. Plays if stopped.
--
-- @since 0.10.0.0
toggle :: MonadMPD m => m ()
toggle :: m ()
toggle = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command ()
A.toggle

-- | Begin\/continue playing.
play :: MonadMPD m => Maybe Position -> m ()
play :: 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

-- | Play a file with given id.
playId :: MonadMPD m => Id -> m ()
playId :: 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

-- | Play the previous song.
previous :: MonadMPD m => m ()
previous :: m ()
previous = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command ()
A.previous

-- | Seek to some point in a song.
seek :: MonadMPD m => Position -> FractionalSeconds -> m ()
seek :: 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

-- | Seek to some point in a song (id version)
seekId :: MonadMPD m => Id -> FractionalSeconds -> m ()
seekId :: 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'

-- | Seek to some point in the current song. Absolute time for True in
-- the frist argument, relative time for False.
--
-- @since 0.9.2.0
seekCur :: MonadMPD m => Bool -> FractionalSeconds -> m ()
seekCur :: 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 playing.
stop :: MonadMPD m => m ()
stop :: m ()
stop = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command ()
A.stop