{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Applicative.PlaybackControl
( next
, pause
, toggle
, 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 ()
next = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [String
"next"]
pause :: Bool -> Command ()
pause :: Bool -> Command ()
pause Bool
f = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"pause" Command -> Bool -> String
forall a. MPDArg a => Command -> a -> String
<@> Bool
f]
toggle :: Command ()
toggle :: Command ()
toggle = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [String
"pause"]
play :: Maybe Position -> Command ()
play :: Maybe Position -> Command ()
play Maybe Position
mbPos = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [String]
c
where
c :: [String]
c = String -> [String]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$ String -> (Position -> String) -> Maybe Position -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"play" (Command
"play" Command -> Position -> String
forall a. MPDArg a => Command -> a -> String
<@>) Maybe Position
mbPos
playId :: Id -> Command ()
playId :: Id -> Command ()
playId Id
id' = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"playid" Command -> Id -> String
forall a. MPDArg a => Command -> a -> String
<@> Id
id']
previous :: Command ()
previous :: Command ()
previous = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [String
"previous"]
seek :: Position -> FractionalSeconds -> Command ()
seek :: Position -> FractionalSeconds -> Command ()
seek Position
pos FractionalSeconds
time = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"seek" Command -> Args -> String
forall a. MPDArg a => Command -> a -> String
<@> Position
pos Position -> FractionalSeconds -> Args
forall a b. (MPDArg a, MPDArg b) => a -> b -> Args
<++> FractionalSeconds
time]
seekId :: Id -> FractionalSeconds -> Command ()
seekId :: Id -> FractionalSeconds -> Command ()
seekId Id
id' FractionalSeconds
time = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"seekid" Command -> Args -> String
forall a. MPDArg a => Command -> a -> String
<@> Id
id' Id -> FractionalSeconds -> Args
forall a b. (MPDArg a, MPDArg b) => a -> b -> Args
<++> FractionalSeconds
time]
seekCur :: Bool -> FractionalSeconds -> Command ()
seekCur :: Bool -> FractionalSeconds -> Command ()
seekCur Bool
bool FractionalSeconds
time
| Bool
bool = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"seekcur" Command -> FractionalSeconds -> String
forall a. MPDArg a => Command -> a -> String
<@> FractionalSeconds
time]
| Bool
otherwise = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"seekcur" Command -> Sign FractionalSeconds -> String
forall a. MPDArg a => Command -> a -> String
<@> (FractionalSeconds -> Sign FractionalSeconds
forall a. a -> Sign a
Sign FractionalSeconds
time)]
stop :: Command ()
stop :: Command ()
stop = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [String
"stop"]