{-# LANGUAGE OverloadedStrings #-}

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

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

Querying MPD's status.
-}

module Network.MPD.Commands.Status
    ( clearError
    , currentSong
    , idle
    , noidle
    , stats
    , status
    ) where

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

-- | Clear the current error message in status.
clearError :: MonadMPD m => m ()
clearError :: m ()
clearError = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command ()
A.clearError

-- | Get the currently playing song.
currentSong :: MonadMPD m => m (Maybe Song)
currentSong :: m (Maybe Song)
currentSong = Command (Maybe Song) -> m (Maybe Song)
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command (Maybe Song)
A.currentSong

-- | Wait until there is a noteworthy change in one or more of MPD's
-- susbystems.
--
-- The first argument is a list of subsystems that should be considered.  An
-- empty list specifies that all subsystems should be considered.
--
-- A list of subsystems that have noteworthy changes is returned.
--
-- Note that running this command will block until either 'idle' returns or is
-- cancelled by 'noidle'.
idle :: MonadMPD m => [Subsystem] -> m [Subsystem]
idle :: [Subsystem] -> m [Subsystem]
idle = Command [Subsystem] -> m [Subsystem]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command [Subsystem] -> m [Subsystem])
-> ([Subsystem] -> Command [Subsystem])
-> [Subsystem]
-> m [Subsystem]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Subsystem] -> Command [Subsystem]
A.idle

-- | Cancel 'idle'.
noidle :: MonadMPD m => m ()
noidle :: m ()
noidle = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command ()
A.noidle

-- | Get server statistics.
stats :: MonadMPD m => m Stats
stats :: m Stats
stats = Command Stats -> m Stats
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command Stats
A.stats

-- | Get the server's status.
status :: MonadMPD m => m Status
status :: m Status
status = Command Status -> m Status
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command Status
A.status