{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Applicative.Reflection
( commands
, notCommands
, tagTypes
, urlHandlers
, decoders
, config
) where
import Network.MPD.Util
import Network.MPD.Applicative.Internal
import Network.MPD.Applicative.Util
import Control.Applicative
import Prelude hiding (repeat, read)
import qualified Data.ByteString.UTF8 as UTF8
commands :: Command [String]
commands = Command p ["commands"]
where
p = map UTF8.toString . takeValues <$> getResponse
notCommands :: Command [String]
notCommands = Command p ["notcommands"]
where
p = map UTF8.toString . takeValues <$> getResponse
tagTypes :: Command [String]
tagTypes = Command p ["tagtypes"]
where
p = map UTF8.toString . takeValues <$> getResponse
urlHandlers :: Command [String]
urlHandlers = Command p ["urlhandlers"]
where
p = map UTF8.toString . takeValues <$> getResponse
decoders :: Command [(String, [(String, String)])]
decoders = Command p ["decoders"]
where
p = takeDecoders . toAssocList <$> getResponse
takeDecoders [] = []
takeDecoders ((_, m):xs) =
let (info, rest) = break ((==) "plugin" . fst) xs
in (UTF8.toString m, map decodePair info) : takeDecoders rest
config :: Command [(String, String)]
config = Command p ["config"]
where
p = map (\(k, v) -> (UTF8.toString k, UTF8.toString v)) . toAssocList <$> getResponse