{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Applicative.Stickers
( stickerGet
, stickerSet
, stickerDelete
, stickerList
, stickerFind
) 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
import qualified Data.ByteString.UTF8 as UTF8
stickerGet :: ObjectType -> String -> String -> Command [String]
stickerGet typ uri name = Command p c
where
p :: Parser [String]
p = map UTF8.toString . takeValues <$> getResponse
c = ["sticker get" <@> typ <++> uri <++> name]
stickerSet :: ObjectType -> String -> String -> String -> Command ()
stickerSet typ uri name value = Command emptyResponse c
where
c = ["sticker set" <@> typ <++> uri <++> name <++> value]
stickerDelete :: ObjectType -> String -> String -> Command ()
stickerDelete typ uri name = Command emptyResponse c
where
c = ["sticker delete" <@> typ <++> uri <++> name]
stickerList :: ObjectType -> String -> Command [(String, String)]
stickerList typ uri = Command p c
where
p = map decodePair . toAssocList <$> getResponse
c = ["sticker list" <@> typ <++> uri]
stickerFind :: ObjectType -> String -> String -> Command [(String, String)]
stickerFind typ uri name = Command p c
where
p = map decodePair . toAssocList <$> getResponse
c = ["sticker find" <@> typ <++> uri <++> name]