{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Applicative.PlaybackControl
( next
, pause
, play
, playId
, previous
, seek
, seekId
, seekCur
, stop
) where
import Network.MPD.Applicative.Internal
import Network.MPD.Commands.Arg hiding (Command)
import Network.MPD.Commands.Types
next :: Command ()
next = Command emptyResponse ["next"]
pause :: Bool -> Command ()
pause f = Command emptyResponse ["pause" <@> f]
play :: Maybe Position -> Command ()
play mbPos = Command emptyResponse c
where
c = return $ maybe "play" ("play" <@>) mbPos
playId :: Id -> Command ()
playId id' = Command emptyResponse ["playid" <@> id']
previous :: Command ()
previous = Command emptyResponse ["previous"]
seek :: Position -> FractionalSeconds -> Command ()
seek pos time = Command emptyResponse ["seek" <@> pos <++> time]
seekId :: Id -> FractionalSeconds -> Command ()
seekId id' time = Command emptyResponse ["seekid" <@> id' <++> time]
seekCur :: Bool -> FractionalSeconds -> Command ()
seekCur bool time
| bool = Command emptyResponse ["seekcur" <@> time]
| otherwise = Command emptyResponse ["seekcur" <@> (Sign time)]
stop :: Command ()
stop = Command emptyResponse ["stop"]