Copyright | (c) Joachim Fasting Simon Hengel 2012 |
---|---|
License | MIT |
Maintainer | Joachim Fasting <joachifm@fastmail.fm> |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
An MPD client library. MPD is a daemon for playing music that is controlled over a network socket.
To use the library, do:
{-# LANGUAGE OverloadedStrings #-} import qualified Network.MPD as MPD
Synopsis
- class (Monad m, MonadError MPDError m) => MonadMPD m
- data MPD a
- data MPDError
- data ACKType
- type Response = Either MPDError
- type Host = String
- type Port = Integer
- type Password = String
- withMPD :: MPD a -> IO (Response a)
- withMPD_ :: Maybe String -> Maybe String -> MPD a -> IO (Response a)
- withMPDEx :: Host -> Port -> Password -> MPD a -> IO (Response a)
- data Query
- (=?) :: Metadata -> Value -> Query
- (/=?) :: Metadata -> Value -> Query
- (%?) :: Metadata -> Value -> Query
- (~?) :: Metadata -> Value -> Query
- (/~?) :: Metadata -> Value -> Query
- qNot :: Query -> Query
- qModSince :: UTCTime -> Query
- qFile :: Path -> Query
- qBase :: Path -> Query
- anything :: Query
- class ToString a where
- type Artist = Value
- type Album = Value
- type Title = Value
- newtype PlaylistName = PlaylistName ByteString
- data Path
- data Metadata
- = Artist
- | ArtistSort
- | Album
- | AlbumSort
- | AlbumArtist
- | AlbumArtistSort
- | Title
- | Track
- | Name
- | Genre
- | Date
- | OriginalDate
- | Composer
- | Performer
- | Conductor
- | Work
- | Grouping
- | Comment
- | Disc
- | Label
- | MUSICBRAINZ_ARTISTID
- | MUSICBRAINZ_ALBUMID
- | MUSICBRAINZ_ALBUMARTISTID
- | MUSICBRAINZ_TRACKID
- | MUSICBRAINZ_RELEASETRACKID
- | MUSICBRAINZ_WORKID
- data Value
- data ObjectType = SongObj
- type Seconds = Integer
- type FractionalSeconds = Double
- type Decibels = Integer
- data PlaybackState
- data Subsystem
- data ReplayGainMode
- data Count = Count {}
- data LsResult
- data Device = Device {
- dOutputID :: Int
- dOutputName :: String
- dOutputEnabled :: Bool
- data Song = Song {}
- newtype Priority = Priority Int
- type Position = Int
- data Range
- data Volume
- newtype Id = Id Int
- sgGetTag :: Metadata -> Song -> Maybe [Value]
- sgAddTag :: Metadata -> Value -> Song -> Song
- data Stats = Stats {}
- data Status = Status {
- stState :: PlaybackState
- stVolume :: Maybe Volume
- stRepeat :: Bool
- stRandom :: Bool
- stPlaylistVersion :: Integer
- stPlaylistLength :: Integer
- stSongPos :: Maybe Position
- stSongID :: Maybe Id
- stNextSongPos :: Maybe Position
- stNextSongID :: Maybe Id
- stTime :: Maybe (FractionalSeconds, FractionalSeconds)
- stBitrate :: Maybe Int
- stXFadeWidth :: Seconds
- stMixRampdB :: Double
- stMixRampDelay :: Double
- stAudio :: (Int, Int, Int)
- stUpdatingDb :: Maybe Integer
- stSingle :: Bool
- stConsume :: Bool
- stError :: Maybe String
- stPartition :: String
- def :: Default a => a
- clearError :: MonadMPD m => m ()
- currentSong :: MonadMPD m => m (Maybe Song)
- idle :: MonadMPD m => [Subsystem] -> m [Subsystem]
- noidle :: MonadMPD m => m ()
- stats :: MonadMPD m => m Stats
- status :: MonadMPD m => m Status
- consume :: MonadMPD m => Bool -> m ()
- crossfade :: MonadMPD m => Seconds -> m ()
- random :: MonadMPD m => Bool -> m ()
- repeat :: MonadMPD m => Bool -> m ()
- setVolume :: MonadMPD m => Volume -> m ()
- single :: MonadMPD m => Bool -> m ()
- replayGainMode :: MonadMPD m => ReplayGainMode -> m ()
- replayGainStatus :: MonadMPD m => m [(String, String)]
- next :: MonadMPD m => m ()
- pause :: MonadMPD m => Bool -> m ()
- toggle :: MonadMPD m => m ()
- play :: MonadMPD m => Maybe Position -> m ()
- playId :: MonadMPD m => Id -> m ()
- previous :: MonadMPD m => m ()
- seek :: MonadMPD m => Position -> FractionalSeconds -> m ()
- seekId :: MonadMPD m => Id -> FractionalSeconds -> m ()
- seekCur :: MonadMPD m => Bool -> FractionalSeconds -> m ()
- stop :: MonadMPD m => m ()
- addId :: MonadMPD m => Path -> Maybe Position -> m Id
- add :: MonadMPD m => Path -> m ()
- clear :: MonadMPD m => m ()
- delete :: MonadMPD m => Position -> m ()
- deleteRange :: MonadMPD m => Range -> m ()
- deleteId :: MonadMPD m => Id -> m ()
- move :: MonadMPD m => Position -> Position -> m ()
- moveRange :: MonadMPD m => Range -> Position -> m ()
- moveId :: MonadMPD m => Id -> Position -> m ()
- playlist :: MonadMPD m => m [(Position, Path)]
- playlistFind :: MonadMPD m => Query -> m [Song]
- playlistInfo :: MonadMPD m => Maybe Position -> m [Song]
- playlistInfoRange :: MonadMPD m => Maybe Range -> m [Song]
- playlistId :: MonadMPD m => Maybe Id -> m [Song]
- playlistSearch :: MonadMPD m => Query -> m [Song]
- plChanges :: MonadMPD m => Integer -> m [Song]
- plChangesPosId :: MonadMPD m => Integer -> m [(Position, Id)]
- prio :: MonadMPD m => Priority -> Range -> m ()
- prioId :: MonadMPD m => Priority -> Id -> m ()
- shuffle :: MonadMPD m => Maybe Range -> m ()
- swap :: MonadMPD m => Position -> Position -> m ()
- swapId :: MonadMPD m => Id -> Id -> m ()
- addTagId :: MonadMPD m => Id -> Metadata -> Value -> m ()
- clearTagId :: MonadMPD m => Id -> Metadata -> m ()
- rangeId :: MonadMPD m => Id -> (Maybe Double, Maybe Double) -> m ()
- listPlaylist :: MonadMPD m => PlaylistName -> m [Path]
- listPlaylistInfo :: MonadMPD m => PlaylistName -> m [Song]
- listPlaylists :: MonadMPD m => m [PlaylistName]
- load :: MonadMPD m => PlaylistName -> m ()
- playlistAdd :: MonadMPD m => PlaylistName -> Path -> m ()
- playlistClear :: MonadMPD m => PlaylistName -> m ()
- playlistDelete :: MonadMPD m => PlaylistName -> Position -> m ()
- playlistMove :: MonadMPD m => PlaylistName -> Id -> Position -> m ()
- rename :: MonadMPD m => PlaylistName -> PlaylistName -> m ()
- rm :: MonadMPD m => PlaylistName -> m ()
- save :: MonadMPD m => PlaylistName -> m ()
- count :: MonadMPD m => Query -> m Count
- find :: MonadMPD m => Query -> m [Song]
- findAdd :: MonadMPD m => Query -> m ()
- list :: MonadMPD m => Metadata -> Query -> m [Value]
- listAll :: MonadMPD m => Path -> m [Path]
- listAllInfo :: MonadMPD m => Path -> m [LsResult]
- lsInfo :: MonadMPD m => Path -> m [LsResult]
- readComments :: MonadMPD m => Path -> m [(String, String)]
- search :: MonadMPD m => Query -> m [Song]
- searchAdd :: MonadMPD m => Query -> m ()
- searchAddPl :: MonadMPD m => PlaylistName -> Query -> m ()
- update :: MonadMPD m => Maybe Path -> m Integer
- rescan :: MonadMPD m => Maybe Path -> m Integer
- stickerGet :: MonadMPD m => ObjectType -> String -> String -> m [String]
- stickerSet :: MonadMPD m => ObjectType -> String -> String -> String -> m ()
- stickerDelete :: MonadMPD m => ObjectType -> String -> String -> m ()
- stickerList :: MonadMPD m => ObjectType -> String -> m [(String, String)]
- stickerFind :: MonadMPD m => ObjectType -> String -> String -> m [(String, String)]
- password :: MonadMPD m => String -> m ()
- ping :: MonadMPD m => m ()
- disableOutput :: MonadMPD m => Int -> m ()
- enableOutput :: MonadMPD m => Int -> m ()
- toggleOutput :: MonadMPD m => Int -> m ()
- outputs :: MonadMPD m => m [Device]
- commands :: MonadMPD m => m [String]
- notCommands :: MonadMPD m => m [String]
- tagTypes :: MonadMPD m => m [String]
- urlHandlers :: MonadMPD m => m [String]
- decoders :: MonadMPD m => m [(String, [(String, String)])]
- config :: MonadMPD m => m [(String, String)]
- type ChannelName = String
- type MessageText = String
- subscribe :: MonadMPD m => ChannelName -> m ()
- unsubscribe :: MonadMPD m => ChannelName -> m ()
- channels :: MonadMPD m => m [ChannelName]
- readMessages :: MonadMPD m => m [(ChannelName, MessageText)]
- sendMessage :: MonadMPD m => ChannelName -> MessageText -> m ()
- mount :: MonadMPD m => String -> String -> m ()
- unmount :: MonadMPD m => String -> m ()
- listMounts :: MonadMPD m => m [(String, String)]
- listNeighbors :: MonadMPD m => m [(String, String)]
Basic data types
class (Monad m, MonadError MPDError m) => MonadMPD m Source #
A typeclass to allow for multiple implementations of a connection to an MPD server.
The main implementation of an MPD client. It actually connects to a server and interacts with it.
To use the error throwing/catching capabilities:
import Control.Monad.Except (throwError, catchError)
To run IO actions within the MPD monad:
import Control.Monad.Trans (liftIO)
The MPDError type is used to signal errors, both from the MPD and otherwise.
NoMPD | MPD not responding |
ConnectionError IOException | An error occurred while talking to MPD. |
Unexpected String | MPD returned an unexpected response. This is a bug, either in the library or in MPD itself. |
Custom String | Used for misc. errors |
ACK ACKType String | ACK type and a message from the server |
Instances
Exception MPDError Source # | |
Defined in Network.MPD.Core.Error toException :: MPDError -> SomeException # fromException :: SomeException -> Maybe MPDError # displayException :: MPDError -> String # | |
Show MPDError Source # | |
Eq MPDError Source # | |
MonadError MPDError MPD Source # | |
Defined in Network.MPD.Core throwError :: MPDError -> MPD a # |
Represents various MPD errors (aka. ACKs).
InvalidArgument | Invalid argument passed (ACK 2) |
InvalidPassword | Invalid password supplied (ACK 3) |
Auth | Authentication required (ACK 4) |
UnknownCommand | Unknown command (ACK 5) |
FileNotFound | File or directory not found ACK 50) |
PlaylistMax | Playlist at maximum size (ACK 51) |
System | A system error (ACK 52) |
PlaylistLoad | Playlist loading failed (ACK 53) |
Busy | Update already running (ACK 54) |
NotPlaying | An operation requiring playback got interrupted (ACK 55) |
FileExists | File already exists (ACK 56) |
UnknownACK | An unknown ACK (aka. bug) |
Connections
withMPD :: MPD a -> IO (Response a) Source #
A wrapper for withMPDEx
that uses localhost:6600 as the default
host:port, or whatever is found in the environment variables MPD_HOST and
MPD_PORT. If MPD_HOST is of the form "password@host" the password
will be supplied as well.
Examples:
withMPD $ play Nothing withMPD $ add_ "tool" >> play Nothing >> currentSong
withMPDEx :: Host -> Port -> Password -> MPD a -> IO (Response a) Source #
The most configurable API for running an MPD action.
An interface for creating MPD queries.
For example, to match any song where the value of artist is "Foo", we use:
Artist =? "Foo"
We can also compose queries, thus narrowing the search. For example, to match any song where the value of artist is "Foo" and the value of album is "Bar", we use:
Artist =? "Foo" <> Album =? "Bar"
(/=?) :: Metadata -> Value -> Query Source #
Create a query matching a tag with anything but a value.
Since MPD 0.21.
Since: 0.9.3.0
(%?) :: Metadata -> Value -> Query Source #
Create a query for a tag containing a value.
Since MPD 0.21.
Since: 0.9.3.0
(~?) :: Metadata -> Value -> Query Source #
Create a query matching a tag with regexp.
Since MPD 0.21.
Since: 0.9.3.0
(/~?) :: Metadata -> Value -> Query Source #
Create a query matching a tag with anything but a regexp.
Since MPD 0.21.
Since: 0.9.3.0
qModSince :: UTCTime -> Query Source #
Create a query for songs modified since a date.
Since MPD 0.21.
Since: 0.9.3.0
qFile :: Path -> Query Source #
Create a query for the full song URI relative to the music directory.
Since MPD 0.21.
Since: 0.9.3.0
qBase :: Path -> Query Source #
Limit the query to the given directory, relative to the music directory.
Since MPD 0.21.
Since: 0.9.3.0
class ToString a where Source #
A type class for values that can be converted to String
s.
toString :: a -> String Source #
Convert given value to String
.
Convert given value to Text
.
toUtf8 :: a -> ByteString Source #
Convert given value to a UTF-8 encoded ByteString
.
Instances
ToString Path Source # | |
ToString PlaylistName Source # | |
Defined in Network.MPD.Commands.Types toString :: PlaylistName -> String Source # toText :: PlaylistName -> Text Source # toUtf8 :: PlaylistName -> ByteString Source # | |
ToString Value Source # | |
newtype PlaylistName Source #
Used for commands which require a playlist name. If empty, the current playlist is used.
Instances
Used for commands which require a path within the database. If empty, the root path is used.
Available metadata types/scope modifiers, used for searching the database for entries with certain metadata values.
Artist | |
ArtistSort | |
Album | |
AlbumSort | Since: 0.10.0.0 |
AlbumArtist | |
AlbumArtistSort | |
Title | |
Track | |
Name | |
Genre | |
Date | |
OriginalDate | Since: 0.10.0.0 |
Composer | |
Performer | |
Conductor | Since: 0.10.0.0 |
Work | Since: 0.10.0.0 |
Grouping | Since: 0.10.0.0 |
Comment | |
Disc | |
Label | Since: 0.10.0.0 |
MUSICBRAINZ_ARTISTID | |
MUSICBRAINZ_ALBUMID | |
MUSICBRAINZ_ALBUMARTISTID | |
MUSICBRAINZ_TRACKID | |
MUSICBRAINZ_RELEASETRACKID | |
MUSICBRAINZ_WORKID | Since: 0.10.0.0 |
Instances
Bounded Metadata Source # | |
Enum Metadata Source # | |
Defined in Network.MPD.Commands.Types | |
Show Metadata Source # | |
Eq Metadata Source # | |
Ord Metadata Source # | |
Defined in Network.MPD.Commands.Types |
A metadata value.
data ObjectType Source #
Object types.
Instances
Show ObjectType Source # | |
Defined in Network.MPD.Commands.Types showsPrec :: Int -> ObjectType -> ShowS # show :: ObjectType -> String # showList :: [ObjectType] -> ShowS # | |
Eq ObjectType Source # | |
Defined in Network.MPD.Commands.Types (==) :: ObjectType -> ObjectType -> Bool # (/=) :: ObjectType -> ObjectType -> Bool # |
type FractionalSeconds = Double Source #
data PlaybackState Source #
Represents the different playback states.
Instances
Represents the various MPD subsystems.
DatabaseS | The song database |
UpdateS | Database updates |
StoredPlaylistS | Stored playlists |
PlaylistS | The current playlist |
PlayerS | The player |
MixerS | The volume mixer |
OutputS | Audio outputs |
OptionsS | Playback options |
PartitionS | Partition changes Since: 0.10.0.0 |
StickerS | Sticker database |
SubscriptionS | Subscription |
MessageS | Message on subscribed channel |
NeighborS | finding or losing a neighbor Since: 0.10.0.0 |
MountS | Mount list changes Since: 0.10.0.0 |
Instances
Bounded Subsystem Source # | |
Enum Subsystem Source # | |
Defined in Network.MPD.Commands.Types succ :: Subsystem -> Subsystem # pred :: Subsystem -> Subsystem # fromEnum :: Subsystem -> Int # enumFrom :: Subsystem -> [Subsystem] # enumFromThen :: Subsystem -> Subsystem -> [Subsystem] # enumFromTo :: Subsystem -> Subsystem -> [Subsystem] # enumFromThenTo :: Subsystem -> Subsystem -> Subsystem -> [Subsystem] # | |
Show Subsystem Source # | |
Eq Subsystem Source # | |
Ord Subsystem Source # | |
Defined in Network.MPD.Commands.Types |
data ReplayGainMode Source #
Off | Disable replay gain |
TrackMode | Per track mode |
AlbumMode | Per album mode |
AutoMode | Auto mode Since: 0.10.0.0 |
Instances
Represents the result of running count
.
Result of the lsInfo operation
LsDirectory Path | Directory |
LsSong Song | Song |
LsPlaylist PlaylistName | Playlist |
Instances
Represents an output device.
Device | |
|
Represents a single song item.
Instances
A range of songs.
Volume values.
Values of this type are always in the range 0-100.
Arithmetic on volumes has the property that:
current + new = 100 if current + new > 100
current - new = 0 if current - new < 0
but current / 0
still yields a division by zero exception.
Instances
Bounded Volume Source # | |
Enum Volume Source # | |
Defined in Network.MPD.Commands.Types | |
Num Volume Source # | |
Integral Volume Source # | |
Defined in Network.MPD.Commands.Types | |
Real Volume Source # | |
Defined in Network.MPD.Commands.Types toRational :: Volume -> Rational # | |
Show Volume Source # | |
Eq Volume Source # | |
Ord Volume Source # | |
Container for database statistics.
Stats | |
|
Container for MPD status.
Status | |
|
clearError :: MonadMPD m => m () Source #
Clear the current error message in status.
idle :: MonadMPD m => [Subsystem] -> m [Subsystem] Source #
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
.
replayGainMode :: MonadMPD m => ReplayGainMode -> m () Source #
Set the replay gain mode.
seekId :: MonadMPD m => Id -> FractionalSeconds -> m () Source #
Seek to some point in a song (id version)
seekCur :: MonadMPD m => Bool -> FractionalSeconds -> m () Source #
Seek to some point in the current song. Absolute time for True in the frist argument, relative time for False.
Since: 0.9.2.0
add :: MonadMPD m => Path -> m () Source #
Add a song (or a whole directory) to the current playlist.
deleteRange :: MonadMPD m => Range -> m () Source #
Remove a range of songs from the current playlist.
Since: 0.10.0.0
move :: MonadMPD m => Position -> Position -> m () Source #
Move a song to a given position in the current playlist.
moveRange :: MonadMPD m => Range -> Position -> m () Source #
Move a range of songs to a given position in the current playlist.
Since: 0.10.0.0
moveId :: MonadMPD m => Id -> Position -> m () Source #
Move a song from (songid) to (playlist index) in the playlist. If to is negative, it is relative to the current song in the playlist (if there is one).
playlist :: MonadMPD m => m [(Position, Path)] Source #
Warning: this is deprecated; please use playlistInfo
instead.
Retrieve file paths and positions of songs in the current playlist.
Note that this command is only included for completeness sake; it's
deprecated and likely to disappear at any time, please use playlistInfo
instead.
playlistFind :: MonadMPD m => Query -> m [Song] Source #
Search for songs in the current playlist with strict matching.
playlistInfo :: MonadMPD m => Maybe Position -> m [Song] Source #
Retrieve metadata for songs in the current playlist.
playlistInfoRange :: MonadMPD m => Maybe Range -> m [Song] Source #
Like playlistInfo
but can restrict to a range of songs.
Since: 0.10.0.0
playlistId :: MonadMPD m => Maybe Id -> m [Song] Source #
Displays a list of songs in the playlist. If id is specified, only its info is returned.
playlistSearch :: MonadMPD m => Query -> m [Song] Source #
Search case-insensitively with partial matches for songs in the current playlist.
plChanges :: MonadMPD m => Integer -> m [Song] Source #
Retrieve a list of changed songs currently in the playlist since a given playlist version.
plChangesPosId :: MonadMPD m => Integer -> m [(Position, Id)] Source #
Like plChanges
but only returns positions and ids.
prio :: MonadMPD m => Priority -> Range -> m () Source #
Set the priority of the specified songs.
Since: 0.10.0.0
shuffle :: MonadMPD m => Maybe Range -> m () Source #
Shuffle the current playlist. Optionally restrict to a range of songs.
Since: 0.10.0.0
rangeId :: MonadMPD m => Id -> (Maybe Double, Maybe Double) -> m () Source #
Specify portion of song that shall be played. Both ends of the range are optional; omitting both plays everything.
listPlaylist :: MonadMPD m => PlaylistName -> m [Path] Source #
Retrieve a list of files in a given playlist.
listPlaylistInfo :: MonadMPD m => PlaylistName -> m [Song] Source #
Retrieve metadata for files in a given playlist.
listPlaylists :: MonadMPD m => m [PlaylistName] Source #
Retreive a list of stored playlists.
load :: MonadMPD m => PlaylistName -> m () Source #
Load an existing playlist.
playlistAdd :: MonadMPD m => PlaylistName -> Path -> m () Source #
Add a song (or a whole directory) to a stored playlist. Will create a new playlist if the one specified does not already exist.
playlistClear :: MonadMPD m => PlaylistName -> m () Source #
Clear a playlist. If the specified playlist does not exist, it will be created.
playlistDelete :: MonadMPD m => PlaylistName -> Position -> m () Source #
Remove a song from a playlist.
playlistMove :: MonadMPD m => PlaylistName -> Id -> Position -> m () Source #
Move a song to a given position in the playlist specified.
:: MonadMPD m | |
=> PlaylistName | Original playlist |
-> PlaylistName | New playlist name |
-> m () |
Rename an existing playlist.
rm :: MonadMPD m => PlaylistName -> m () Source #
Delete existing playlist.
save :: MonadMPD m => PlaylistName -> m () Source #
Save the current playlist.
find :: MonadMPD m => Query -> m [Song] Source #
Search the database for entries exactly matching a query.
List all tags of the specified type of songs that that satisfy the query.
Since: 0.10.0.0
listAll :: MonadMPD m => Path -> m [Path] Source #
List the songs (without metadata) in a database directory recursively.
lsInfo :: MonadMPD m => Path -> m [LsResult] Source #
Non-recursively list the contents of a database directory.
search :: MonadMPD m => Query -> m [Song] Source #
Search the database using case insensitive matching.
searchAdd :: MonadMPD m => Query -> m () Source #
Like search
but adds the results to the current playlist.
Since: 0.10.0.0
searchAddPl :: MonadMPD m => PlaylistName -> Query -> m () Source #
Like searchAdd
but adds results to the named playlist.
Since: 0.10.0.0
update :: MonadMPD m => Maybe Path -> m Integer Source #
Update the server's database.
If no path is given, the whole library will be scanned. Unreadable or non-existent paths are silently ignored.
The update job id is returned.
rescan :: MonadMPD m => Maybe Path -> m Integer Source #
Like update
but also rescans unmodified files.
:: MonadMPD m | |
=> ObjectType | |
-> String | Object URI |
-> String | Sticker name |
-> m [String] |
Reads a sticker value for the specified object.
:: MonadMPD m | |
=> ObjectType | |
-> String | Object URI |
-> String | Sticker name |
-> String | Sticker value |
-> m () |
Adds a sticker value to the specified object.
:: MonadMPD m | |
=> ObjectType | |
-> String | Object URI |
-> String | Sticker name |
-> m () |
Delete a sticker value from the specified object.
:: MonadMPD m | |
=> ObjectType | |
-> String | Object URI |
-> m [(String, String)] | Sticker name/sticker value |
Lists the stickers for the specified object.
:: MonadMPD m | |
=> ObjectType | |
-> String | Path |
-> String | Sticker name |
-> m [(String, String)] | URI/sticker value |
Searches the sticker database for stickers with the specified name, below the specified path.
password :: MonadMPD m => String -> m () Source #
Send password to server to authenticate session. Password is sent as plain text.
disableOutput :: MonadMPD m => Int -> m () Source #
Turn off an output device.
enableOutput :: MonadMPD m => Int -> m () Source #
Turn on an output device.
toggleOutput :: MonadMPD m => Int -> m () Source #
Toggle output device.
notCommands :: MonadMPD m => m [String] Source #
Retrieve a list of unavailable (due to access restrictions) commands.
urlHandlers :: MonadMPD m => m [String] Source #
Retrieve a list of supported urlhandlers.
decoders :: MonadMPD m => m [(String, [(String, String)])] Source #
Retreive a list of decoder plugins with associated suffix and mime types.
Types
type ChannelName = String Source #
type MessageText = String Source #
Subscribing to channels
subscribe :: MonadMPD m => ChannelName -> m () Source #
unsubscribe :: MonadMPD m => ChannelName -> m () Source #
channels :: MonadMPD m => m [ChannelName] Source #
Communicating with other clients
readMessages :: MonadMPD m => m [(ChannelName, MessageText)] Source #
sendMessage :: MonadMPD m => ChannelName -> MessageText -> m () Source #