{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Applicative.Database where
import Control.Applicative
import qualified Network.MPD.Commands.Arg as Arg
import Network.MPD.Commands.Arg hiding (Command)
import Network.MPD.Commands.Parse
import Network.MPD.Commands.Query
import Network.MPD.Util
import Network.MPD.Commands.Types
import Network.MPD.Applicative.Internal
import Network.MPD.Applicative.Util
count :: Query -> Command Count
count q = Command (liftParser parseCount) ["count" <@> q]
find :: Query -> Command [Song]
find q = Command p ["find" <@> q]
where
p :: Parser [Song]
p = liftParser takeSongs
findAdd :: Query -> Command ()
findAdd q = Command emptyResponse ["findadd" <@> q]
list :: Metadata -> Maybe Artist -> Command [Value]
list m q = Command p c
where
p = map Value . takeValues <$> getResponse
c = case m of
Album -> ["list Album" <@> q]
_ -> ["list" <@> m]
listAll :: Path -> Command [Path]
listAll path = Command p ["listall" <@> path]
where
p :: Parser [Path]
p = map (Path . snd) . filter ((== "file") . fst)
. toAssocList <$> getResponse
lsInfo' :: Arg.Command -> Path -> Command [LsResult]
lsInfo' cmd path = Command p [cmd <@> path]
where
p :: Parser [LsResult]
p = liftParser takeEntries
listAllInfo :: Path -> Command [LsResult]
listAllInfo = lsInfo' "listallinfo"
lsInfo :: Path -> Command [LsResult]
lsInfo = lsInfo' "lsinfo"
readComments :: Path -> Command [(String, String)]
readComments uri = Command p ["readcomments" <@> uri]
where p = map decodePair . toAssocList <$> getResponse
search :: Query -> Command [Song]
search q = Command p ["search" <@> q]
where
p :: Parser [Song]
p = liftParser takeSongs
searchAdd :: Query -> Command ()
searchAdd q = Command emptyResponse ["searchadd" <@> q]
searchAddPl :: PlaylistName -> Query -> Command ()
searchAddPl pl q = Command emptyResponse ["searchaddpl" <@> pl <++> q]
update :: Maybe Path -> Command Integer
update = update_ "update"
rescan :: Maybe Path -> Command Integer
rescan = update_ "rescan"
update_ :: Arg.Command -> Maybe Path -> Command Integer
update_ cmd mPath = Command p [cmd <@> mPath]
where
p :: Parser Integer
p = do
r <- getResponse
case toAssocList r of
[("updating_db", id_)] -> maybe (unexpected r)
return
(parseNum id_)
_ -> unexpected r