{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Commands.Output
( disableOutput
, enableOutput
, toggleOutput
, outputs
) where
import qualified Network.MPD.Applicative.Internal as A
import qualified Network.MPD.Applicative.Output as A
import Network.MPD.Core
import Network.MPD.Commands.Types
disableOutput :: MonadMPD m => Int -> m ()
disableOutput :: Int -> m ()
disableOutput = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Int -> Command ()) -> Int -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Command ()
A.disableOutput
enableOutput :: MonadMPD m => Int -> m ()
enableOutput :: Int -> m ()
enableOutput = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Int -> Command ()) -> Int -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Command ()
A.enableOutput
toggleOutput :: MonadMPD m => Int -> m ()
toggleOutput :: Int -> m ()
toggleOutput = Command () -> m ()
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand (Command () -> m ()) -> (Int -> Command ()) -> Int -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Command ()
A.toggleOutput
outputs :: MonadMPD m => m [Device]
outputs :: m [Device]
outputs = Command [Device] -> m [Device]
forall (m :: * -> *) a. MonadMPD m => Command a -> m a
A.runCommand Command [Device]
A.outputs