{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Applicative.StoredPlaylists
( listPlaylist
, listPlaylistInfo
, listPlaylists
, load
, playlistAdd
, playlistClear
, playlistDelete
, playlistMove
, rename
, rm
, save
) where
import Network.MPD.Applicative.Internal
import Network.MPD.Applicative.Util
import Network.MPD.Commands.Arg hiding (Command)
import Network.MPD.Commands.Types
import Network.MPD.Util
import Control.Applicative
listPlaylist :: PlaylistName -> Command [Path]
listPlaylist plName = Command p ["listplaylist" <@> plName]
where
p = map Path . takeValues <$> getResponse
listPlaylistInfo :: PlaylistName -> Command [Song]
listPlaylistInfo plName =
Command (liftParser takeSongs) ["listplaylistinfo" <@> plName]
listPlaylists :: Command [PlaylistName]
listPlaylists = Command p ["listplaylists"]
where
p = map PlaylistName . go [] . toAssocList <$> getResponse
go acc [] = acc
go acc ((_, b):_:xs) = go (b : acc) xs
go _ _ = error "listPlaylists: bug"
load :: PlaylistName -> Command ()
load plName = Command emptyResponse ["load" <@> plName]
playlistAdd :: PlaylistName -> Path -> Command ()
playlistAdd plName path =
Command emptyResponse ["playlistadd" <@> plName <++> path]
playlistClear :: PlaylistName -> Command ()
playlistClear plName = Command emptyResponse ["playlistclear" <@> plName]
playlistDelete :: PlaylistName -> Position -> Command ()
playlistDelete name pos =
Command emptyResponse ["playlistdelete" <@> name <++> pos]
playlistMove :: PlaylistName -> Id -> Position -> Command ()
playlistMove name from to =
Command emptyResponse ["playlistmove" <@> name <++> from <++> to]
rename :: PlaylistName -> PlaylistName -> Command ()
rename plName new = Command emptyResponse ["rename" <@> plName <++> new]
rm :: PlaylistName -> Command ()
rm plName = Command emptyResponse ["rm" <@> plName]
save :: PlaylistName -> Command ()
save plName = Command emptyResponse ["save" <@> plName]