{-# LANGUAGE FlexibleInstances, TypeSynonymInstances, GeneralizedNewtypeDeriving #-}
module Network.MPD.Commands.Arg (Command, Args(..), MPDArg(..), (<++>), (<@>)) where
import Network.MPD.Util (showBool)
import Data.ByteString (ByteString)
import qualified Data.ByteString.UTF8 as UTF8
import Data.String
newtype Args = Args [String]
deriving Show
class Show a => MPDArg a where
prep :: a -> Args
prep = Args . return . show
infixl 3 <++>
(<++>) :: (MPDArg a, MPDArg b) => a -> b -> Args
x <++> y = Args $ xs ++ ys
where Args xs = prep x
Args ys = prep y
newtype Command = Command String
deriving IsString
infix 2 <@>
(<@>) :: (MPDArg a) => Command -> a -> String
Command x <@> y = unwords $ x : filter (not . null) y'
where Args y' = prep y
instance MPDArg Args where prep = id
instance MPDArg String where
prep x = Args ['"' : addSlashes x ++ "\""]
instance MPDArg ByteString where
prep = prep . UTF8.toString
instance (MPDArg a) => MPDArg (Maybe a) where
prep Nothing = Args []
prep (Just x) = prep x
instance (MPDArg a, MPDArg b) => MPDArg (a, b) where
prep (x, y) = Args [show x ++ ":" ++ show y]
instance MPDArg Int
instance MPDArg Integer
instance MPDArg Bool where prep = Args . return . showBool
instance MPDArg Double
addSlashes :: String -> String
addSlashes = concatMap escapeSpecial
where specials = "\\\""
escapeSpecial x
| x `elem` specials = ['\\', x]
| otherwise = [x]