{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Applicative.CurrentPlaylist
( add
, addId
, clear
, delete
, deleteRange
, deleteId
, move
, moveId
, moveRange
, playlistFind
, playlistInfo
, playlistInfoRange
, playlistId
, playlistSearch
, plChanges
, plChangesPosId
, prio
, prioId
, shuffle
, swap
, swapId
, addTagId
, clearTagId
, rangeId
) where
import Network.MPD.Commands.Arg hiding (Command)
import qualified Network.MPD.Commands.Arg as Arg
import Network.MPD.Util
import Network.MPD.Commands.Query
import Network.MPD.Commands.Parse
import Network.MPD.Commands.Types
import Network.MPD.Applicative.Internal
import Network.MPD.Applicative.Util
add :: Path -> Command ()
add path = Command emptyResponse ["add" <@> path]
addId :: Path -> Maybe Position -> Command Id
addId path pos = Command p c
where
c = ["addid" <@> path <++> pos]
p = do
r <- getResponse
case toAssocList r of
[("Id", n)] -> maybe (unexpected r) (return . Id) (parseNum n)
_ -> unexpected r
clear :: Command ()
clear = Command emptyResponse ["clear"]
delete :: Position -> Command ()
delete pos = Command emptyResponse ["delete" <@> pos]
deleteRange :: (Position, Position) -> Command ()
deleteRange range = Command emptyResponse ["delete" <@> range]
deleteId :: Id -> Command ()
deleteId i = Command emptyResponse ["deleteid" <@> i]
move :: Position -> Position -> Command ()
move pos to = Command emptyResponse ["move" <@> pos <++> to]
moveRange :: (Position, Position) -> Position -> Command ()
moveRange range to = Command emptyResponse ["move" <@> range <++> to]
moveId :: Id -> Position -> Command ()
moveId i to = Command emptyResponse ["moveid" <@> i <++> to]
playlist' :: MPDArg a => Arg.Command -> a -> Command [Song]
playlist' cmd q = Command (liftParser takeSongs) [cmd <@> q]
playlistFind :: Query -> Command [Song]
playlistFind = playlist' "playlistfind"
playlistInfo :: Maybe Position -> Command [Song]
playlistInfo = playlist' "playlistinfo"
playlistInfoRange :: Maybe (Position, Position) -> Command [Song]
playlistInfoRange = playlist' "playlistinfo"
playlistId :: Maybe Id -> Command [Song]
playlistId = playlist' "playlistid"
playlistSearch :: Query -> Command [Song]
playlistSearch = playlist' "playlistsearch"
plChanges :: Integer -> Command [Song]
plChanges = playlist' "plchanges"
plChangesPosId :: Integer -> Command [(Position, Id)]
plChangesPosId ver = Command p ["plchangesposid" <@> ver]
where
p :: Parser [(Position, Id)]
p = liftParser $ mapM f . splitGroups ["cpos"] . toAssocList
f xs | [("cpos", x), ("Id", y)] <- xs
, Just (x', y') <- pair parseNum (x, y)
= Right (x', Id y')
| otherwise = Left ""
prio :: Priority -> (Position, Position) -> Command ()
prio p range = Command emptyResponse ["prio" <@> p <++> range]
prioId :: Priority -> Id -> Command ()
prioId p ids = Command emptyResponse ["prioid" <@> p <++> ids]
shuffle :: Maybe (Position, Position) -> Command ()
shuffle mbRange = Command emptyResponse ["shuffle" <@> mbRange]
swap :: Position -> Position -> Command ()
swap pos1 pos2 = Command emptyResponse ["swap" <@> pos1 <++> pos2]
swapId :: Id -> Id -> Command ()
swapId id1 id2 = Command emptyResponse ["swapid" <@> id1 <++> id2]
addTagId :: Id -> Metadata -> Value -> Command ()
addTagId id' tag val = Command emptyResponse ["addtagid" <@> id' <++> tag <++> val]
clearTagId :: Id -> Metadata -> Command ()
clearTagId id' tags = Command emptyResponse ["cleartagid" <@> id' <++> tags]
rangeId :: Id -> (Maybe Double, Maybe Double) -> Command ()
rangeId id' (mbStart, mbEnd) = Command emptyResponse ["rangeid " ++ show id' ++ " " ++ arg ]
where arg = maybe "" show mbStart ++ ":" ++ maybe "" show mbEnd