{-# LANGUAGE OverloadedStrings #-}
module Network.MPD.Applicative.Output
( disableOutput
, enableOutput
, toggleOutput
, outputs
) where
import Network.MPD.Applicative.Internal
import Network.MPD.Commands.Arg hiding (Command)
import Network.MPD.Commands.Parse
import Network.MPD.Commands.Types
disableOutput :: Int -> Command ()
disableOutput :: Int -> Command ()
disableOutput Int
n = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"disableoutput" Command -> Int -> String
forall a. MPDArg a => Command -> a -> String
<@> Int
n]
enableOutput :: Int -> Command ()
enableOutput :: Int -> Command ()
enableOutput Int
n = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"enableoutput" Command -> Int -> String
forall a. MPDArg a => Command -> a -> String
<@> Int
n]
toggleOutput :: Int -> Command ()
toggleOutput :: Int -> Command ()
toggleOutput Int
n = Parser () -> [String] -> Command ()
forall a. Parser a -> [String] -> Command a
Command Parser ()
emptyResponse [Command
"toggleoutput" Command -> Int -> String
forall a. MPDArg a => Command -> a -> String
<@> Int
n]
outputs :: Command [Device]
outputs :: Command [Device]
outputs = Parser [Device] -> [String] -> Command [Device]
forall a. Parser a -> [String] -> Command a
Command (([ByteString] -> Either String [Device]) -> Parser [Device]
forall a. ([ByteString] -> Either String a) -> Parser a
liftParser [ByteString] -> Either String [Device]
parseOutputs) [String
"outputs"]