{-# LANGUAGE OverloadedStrings #-}

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

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

Stored playlists.
-}

module Network.MPD.Commands.StoredPlaylists
    ( listPlaylist
    , listPlaylistInfo
    , listPlaylists
    , load
    , playlistAdd
    , playlistClear
    , playlistDelete
    , playlistMove
    , rename
    , rm
    , save
    ) where

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

-- | Retrieve a list of files in a given playlist.
listPlaylist :: MonadMPD m => PlaylistName -> m [Path]
listPlaylist :: PlaylistName -> m [Path]
listPlaylist = Command [Path] -> m [Path]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command [Path] -> m [Path])
-> (PlaylistName -> Command [Path]) -> PlaylistName -> m [Path]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlaylistName -> Command [Path]
A.listPlaylist

-- | Retrieve metadata for files in a given playlist.
listPlaylistInfo :: MonadMPD m => PlaylistName -> m [Song]
listPlaylistInfo :: PlaylistName -> m [Song]
listPlaylistInfo = Command [Song] -> m [Song]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command [Song] -> m [Song])
-> (PlaylistName -> Command [Song]) -> PlaylistName -> m [Song]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlaylistName -> Command [Song]
A.listPlaylistInfo

-- | Retreive a list of stored playlists.
listPlaylists :: MonadMPD m => m [PlaylistName]
listPlaylists :: m [PlaylistName]
listPlaylists = Command [PlaylistName] -> m [PlaylistName]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command [PlaylistName]
A.listPlaylists

-- | Load an existing playlist.
load :: MonadMPD m => PlaylistName -> m ()
load :: PlaylistName -> m ()
load = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (PlaylistName -> Command ()) -> PlaylistName -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlaylistName -> Command ()
A.load

-- | Add a song (or a whole directory) to a stored playlist.
-- Will create a new playlist if the one specified does not already exist.
playlistAdd :: MonadMPD m => PlaylistName -> Path -> m ()
playlistAdd :: PlaylistName -> Path -> m ()
playlistAdd PlaylistName
plname = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Path -> Command ()) -> Path -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlaylistName -> Path -> Command ()
A.playlistAdd PlaylistName
plname

-- | Clear a playlist. If the specified playlist does not exist, it will be
-- created.
playlistClear :: MonadMPD m => PlaylistName -> m ()
playlistClear :: PlaylistName -> m ()
playlistClear = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (PlaylistName -> Command ()) -> PlaylistName -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlaylistName -> Command ()
A.playlistClear

-- | Remove a song from a playlist.
playlistDelete :: MonadMPD m => PlaylistName -> Position -> m ()
playlistDelete :: PlaylistName -> Position -> m ()
playlistDelete PlaylistName
name = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (Position -> Command ()) -> Position -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlaylistName -> Position -> Command ()
A.playlistDelete PlaylistName
name

-- | Move a song to a given position in the playlist specified.
playlistMove :: MonadMPD m => PlaylistName -> Id -> Position -> m ()
playlistMove :: PlaylistName -> Id -> Position -> m ()
playlistMove PlaylistName
name Id
from = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (Position -> Command ()) -> Position -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlaylistName -> Id -> Position -> Command ()
A.playlistMove PlaylistName
name Id
from

-- | Rename an existing playlist.
rename :: MonadMPD m
       => PlaylistName -- ^ Original playlist
       -> PlaylistName -- ^ New playlist name
       -> m ()
rename :: PlaylistName -> PlaylistName -> m ()
rename PlaylistName
plname = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (PlaylistName -> Command ()) -> PlaylistName -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlaylistName -> PlaylistName -> Command ()
A.rename PlaylistName
plname

-- | Delete existing playlist.
rm :: MonadMPD m => PlaylistName -> m ()
rm :: PlaylistName -> m ()
rm = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (PlaylistName -> Command ()) -> PlaylistName -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlaylistName -> Command ()
A.rm

-- | Save the current playlist.
save :: MonadMPD m => PlaylistName -> m ()
save :: PlaylistName -> m ()
save = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ())
-> (PlaylistName -> Command ()) -> PlaylistName -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlaylistName -> Command ()
A.save