{-# LANGUAGE OverloadedStrings #-}

{- |
Module      : Network.MPD.Commands.Stickers
Copyright   : (c) Ben Sinclair 2005-2009, Joachim Fasting 2012
License     : MIT (see LICENSE)

Maintainer  : joachifm@fastmail.fm
Stability   : stable
Portability : unportable

Stickers.
-}

module Network.MPD.Commands.Stickers
    ( stickerGet
    , stickerSet
    , stickerDelete
    , stickerList
    , stickerFind
    ) where

import qualified Network.MPD.Applicative.Internal as A
import qualified Network.MPD.Applicative.Stickers as A
import           Network.MPD.Commands.Types
import           Network.MPD.Core

-- | Reads a sticker value for the specified object.
stickerGet :: MonadMPD m => ObjectType
           -> String -- ^ Object URI
           -> String -- ^ Sticker name
           -> m [String]
stickerGet :: ObjectType -> String -> String -> m [String]
stickerGet ObjectType
typ String
uri = Command [String] -> m [String]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command [String] -> m [String])
-> (String -> Command [String]) -> String -> m [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectType -> String -> String -> Command [String]
A.stickerGet ObjectType
typ String
uri

-- | Adds a sticker value to the specified object.
stickerSet :: MonadMPD m => ObjectType
           -> String -- ^ Object URI
           -> String -- ^ Sticker name
           -> String -- ^ Sticker value
           -> m ()
stickerSet :: ObjectType -> String -> String -> String -> m ()
stickerSet ObjectType
typ String
uri String
name = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (String -> Command ()) -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectType -> String -> String -> String -> Command ()
A.stickerSet ObjectType
typ String
uri String
name

-- | Delete a sticker value from the specified object.
stickerDelete :: MonadMPD m => ObjectType
              -> String -- ^ Object URI
              -> String -- ^ Sticker name
              -> m ()
stickerDelete :: ObjectType -> String -> String -> m ()
stickerDelete ObjectType
typ String
uri = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (String -> Command ()) -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectType -> String -> String -> Command ()
A.stickerDelete ObjectType
typ String
uri

-- | Lists the stickers for the specified object.
stickerList :: MonadMPD m => ObjectType
            -> String -- ^ Object URI
            -> m [(String, String)] -- ^ Sticker name\/sticker value
stickerList :: ObjectType -> String -> m [(String, String)]
stickerList ObjectType
typ = Command [(String, String)] -> m [(String, String)]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command [(String, String)] -> m [(String, String)])
-> (String -> Command [(String, String)])
-> String
-> m [(String, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectType -> String -> Command [(String, String)]
A.stickerList ObjectType
typ

-- | Searches the sticker database for stickers with the specified name, below
-- the specified path.
stickerFind :: MonadMPD m => ObjectType
            -> String -- ^ Path
            -> String -- ^ Sticker name
            -> m [(String, String)] -- ^ URI\/sticker value
stickerFind :: ObjectType -> String -> String -> m [(String, String)]
stickerFind ObjectType
typ String
uri = Command [(String, String)] -> m [(String, String)]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command [(String, String)] -> m [(String, String)])
-> (String -> Command [(String, String)])
-> String
-> m [(String, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectType -> String -> String -> Command [(String, String)]
A.stickerFind ObjectType
typ String
uri