{-# 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
listPlaylist :: PlaylistName -> Command [Path]
listPlaylist :: PlaylistName -> Command [Path]
listPlaylist PlaylistName
plName = Parser [Path] -> [String] -> Command [Path]
forall a. Parser a -> [String] -> Command a
Command Parser [Path]
p [Command
"listplaylist" Command -> PlaylistName -> String
forall a. MPDArg a => Command -> a -> String
<@> PlaylistName
plName]
where
p :: Parser [Path]
p = (ByteString -> Path) -> [ByteString] -> [Path]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> Path
Path ([ByteString] -> [Path])
-> ([ByteString] -> [ByteString]) -> [ByteString] -> [Path]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> [ByteString]
takeValues ([ByteString] -> [Path]) -> Parser [ByteString] -> Parser [Path]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [ByteString]
getResponse
listPlaylistInfo :: PlaylistName -> Command [Song]
listPlaylistInfo :: PlaylistName -> Command [Song]
listPlaylistInfo PlaylistName
plName =
Parser [Song] -> [String] -> Command [Song]
forall a. Parser a -> [String] -> Command a
Command (([ByteString] -> Either String [Song]) -> Parser [Song]
forall a. ([ByteString] -> Either String a) -> Parser a
liftParser [ByteString] -> Either String [Song]
takeSongs) [Command
"listplaylistinfo" Command -> PlaylistName -> String
forall a. MPDArg a => Command -> a -> String
<@> PlaylistName
plName]
listPlaylists :: Command [PlaylistName]
listPlaylists :: Command [PlaylistName]
listPlaylists = Parser [PlaylistName] -> [String] -> Command [PlaylistName]
forall a. Parser a -> [String] -> Command a
Command Parser [PlaylistName]
p [String
"listplaylists"]
where
p :: Parser [PlaylistName]
p = (ByteString -> PlaylistName) -> [ByteString] -> [PlaylistName]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> PlaylistName
PlaylistName ([ByteString] -> [PlaylistName])
-> ([ByteString] -> [ByteString]) -> [ByteString] -> [PlaylistName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> [(ByteString, ByteString)] -> [ByteString]
forall {a} {a}. [a] -> [(a, a)] -> [a]
go [] ([(ByteString, ByteString)] -> [ByteString])
-> ([ByteString] -> [(ByteString, ByteString)])
-> [ByteString]
-> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> [(ByteString, ByteString)]
toAssocList ([ByteString] -> [PlaylistName])
-> Parser [ByteString] -> Parser [PlaylistName]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [ByteString]
getResponse
go :: [a] -> [(a, a)] -> [a]
go [a]
acc [] = [a]
acc
go [a]
acc ((a
_, a
b):(a, a)
_:[(a, a)]
xs) = [a] -> [(a, a)] -> [a]
go (a
b a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
acc) [(a, a)]
xs
go [a]
_ [(a, a)]
_ = String -> [a]
forall a. HasCallStack => String -> a
error String
"listPlaylists: bug"
load :: PlaylistName -> Command ()
load :: PlaylistName -> Command ()
load PlaylistName
plName = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"load" Command -> PlaylistName -> String
forall a. MPDArg a => Command -> a -> String
<@> PlaylistName
plName]
playlistAdd :: PlaylistName -> Path -> Command ()
playlistAdd :: PlaylistName -> Path -> Command ()
playlistAdd PlaylistName
plName Path
path =
Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"playlistadd" Command -> Args -> String
forall a. MPDArg a => Command -> a -> String
<@> PlaylistName
plName PlaylistName -> Path -> Args
forall a b. (MPDArg a, MPDArg b) => a -> b -> Args
<++> Path
path]
playlistClear :: PlaylistName -> Command ()
playlistClear :: PlaylistName -> Command ()
playlistClear PlaylistName
plName = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"playlistclear" Command -> PlaylistName -> String
forall a. MPDArg a => Command -> a -> String
<@> PlaylistName
plName]
playlistDelete :: PlaylistName -> Position -> Command ()
playlistDelete :: PlaylistName -> Position -> Command ()
playlistDelete PlaylistName
name Position
pos =
Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"playlistdelete" Command -> Args -> String
forall a. MPDArg a => Command -> a -> String
<@> PlaylistName
name PlaylistName -> Position -> Args
forall a b. (MPDArg a, MPDArg b) => a -> b -> Args
<++> Position
pos]
playlistMove :: PlaylistName -> Id -> Position -> Command ()
playlistMove :: PlaylistName -> Id -> Position -> Command ()
playlistMove PlaylistName
name Id
from Position
to =
Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"playlistmove" Command -> Args -> String
forall a. MPDArg a => Command -> a -> String
<@> PlaylistName
name PlaylistName -> Id -> Args
forall a b. (MPDArg a, MPDArg b) => a -> b -> Args
<++> Id
from Args -> Position -> Args
forall a b. (MPDArg a, MPDArg b) => a -> b -> Args
<++> Position
to]
rename :: PlaylistName -> PlaylistName -> Command ()
rename :: PlaylistName -> PlaylistName -> Command ()
rename PlaylistName
plName PlaylistName
new = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"rename" Command -> Args -> String
forall a. MPDArg a => Command -> a -> String
<@> PlaylistName
plName PlaylistName -> PlaylistName -> Args
forall a b. (MPDArg a, MPDArg b) => a -> b -> Args
<++> PlaylistName
new]
rm :: PlaylistName -> Command ()
rm :: PlaylistName -> Command ()
rm PlaylistName
plName = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"rm" Command -> PlaylistName -> String
forall a. MPDArg a => Command -> a -> String
<@> PlaylistName
plName]
save :: PlaylistName -> Command ()
save :: PlaylistName -> Command ()
save PlaylistName
plName = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"save" Command -> PlaylistName -> String
forall a. MPDArg a => Command -> a -> String
<@> PlaylistName
plName]