{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Commands.Extensions where
import Network.MPD.Core
import Network.MPD.Commands
import qualified Network.MPD.Applicative.Internal as A
import qualified Network.MPD.Applicative.CurrentPlaylist as A
import qualified Network.MPD.Applicative.StoredPlaylists as A
import Control.Monad (liftM)
import Data.Traversable (for)
import Data.Foldable (for_)
import Data.Semigroup ((<>))
updateId :: MonadMPD m => Maybe Path -> m Integer
updateId = update
{-# DEPRECATED updateId "use `update` instead" #-}
toggle :: MonadMPD m => m ()
toggle = status >>= \st -> case stState st of Playing -> pause True
_ -> play Nothing
addMany :: MonadMPD m => PlaylistName -> [Path] -> m ()
addMany plname xs = A.runCommand (for_ xs cmd)
where cmd | plname == "" = A.add
| otherwise = A.playlistAdd plname
addIdMany :: MonadMPD m => Path -> Maybe Position -> m [Id]
addIdMany x (Just p) = do
fs <- listAll x
let fs' = map (\(a, b) -> (a, Just b)) $ zip fs [p ..]
A.runCommand $ for fs' (uncurry A.addId)
addIdMany x Nothing = do
fs <- listAll x
A.runCommand $ for fs (`A.addId` Nothing)
addList :: MonadMPD m => Path -> m [Path]
addList x = add x >> listAll x
{-# DEPRECATED addList "will be removed in a future version" #-}
playlistAddList :: MonadMPD m => PlaylistName -> Path -> m [Path]
playlistAddList plname path = playlistAdd plname path >> listAll path
{-# DEPRECATED playlistAddList "will be removed in a future version" #-}
listArtists :: MonadMPD m => m [Artist]
listArtists = list Artist Nothing
listAlbums :: MonadMPD m => Maybe Artist -> m [Album]
listAlbums = list Album
listAlbum :: MonadMPD m => Artist -> Album -> m [Song]
listAlbum artist album = find (Artist =? artist <> Album =? album)
getPlaylist :: MonadMPD m => m [Song]
getPlaylist = playlistInfo Nothing
volume :: MonadMPD m => Int -> m ()
volume n = do
cur <- stVolume `liftM` status
case cur of
Nothing -> return ()
Just v -> setVolume (adjust v)
where
adjust x = round $ (fromIntegral n / (100 :: Double)) * x' + x'
where x' = fromIntegral x