libmpd-0.10.0.0: An MPD client library.
Copyright(c) Joachim Fasting Simon Hengel 2012
LicenseMIT
MaintainerJoachim Fasting <joachifm@fastmail.fm>
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell2010

Network.MPD

Description

An MPD client library. MPD is a daemon for playing music that is controlled over a network socket.

To use the library, do:

import qualified Network.MPD as MPD
Synopsis

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.

Minimal complete definition

open, close, send, getPassword, setPassword, getVersion

Instances

Instances details
MonadMPD MPD Source # 
Instance details

Defined in Network.MPD.Core

data MPD a Source #

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)

Instances

Instances details
Monad MPD Source # 
Instance details

Defined in Network.MPD.Core

Methods

(>>=) :: MPD a -> (a -> MPD b) -> MPD b #

(>>) :: MPD a -> MPD b -> MPD b #

return :: a -> MPD a #

Functor MPD Source # 
Instance details

Defined in Network.MPD.Core

Methods

fmap :: (a -> b) -> MPD a -> MPD b #

(<$) :: a -> MPD b -> MPD a #

Applicative MPD Source # 
Instance details

Defined in Network.MPD.Core

Methods

pure :: a -> MPD a #

(<*>) :: MPD (a -> b) -> MPD a -> MPD b #

liftA2 :: (a -> b -> c) -> MPD a -> MPD b -> MPD c #

(*>) :: MPD a -> MPD b -> MPD b #

(<*) :: MPD a -> MPD b -> MPD a #

MonadIO MPD Source # 
Instance details

Defined in Network.MPD.Core

Methods

liftIO :: IO a -> MPD a #

MonadMPD MPD Source # 
Instance details

Defined in Network.MPD.Core

MonadError MPDError MPD Source # 
Instance details

Defined in Network.MPD.Core

Methods

throwError :: MPDError -> MPD a #

catchError :: MPD a -> (MPDError -> MPD a) -> MPD a #

data MPDError Source #

The MPDError type is used to signal errors, both from the MPD and otherwise.

Constructors

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

Instances details
Eq MPDError Source # 
Instance details

Defined in Network.MPD.Core.Error

Show MPDError Source # 
Instance details

Defined in Network.MPD.Core.Error

Exception MPDError Source # 
Instance details

Defined in Network.MPD.Core.Error

MonadError MPDError MPD Source # 
Instance details

Defined in Network.MPD.Core

Methods

throwError :: MPDError -> MPD a #

catchError :: MPD a -> (MPDError -> MPD a) -> MPD a #

data ACKType Source #

Represents various MPD errors (aka. ACKs).

Constructors

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)

Instances

Instances details
Eq ACKType Source # 
Instance details

Defined in Network.MPD.Core.Error

Methods

(==) :: ACKType -> ACKType -> Bool #

(/=) :: ACKType -> ACKType -> Bool #

type Response = Either MPDError Source #

A response is either an MPDError or some result.

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

withMPD_ Source #

Arguments

:: Maybe String

optional override for MPD_HOST

-> Maybe String

optional override for MPD_PORT

-> MPD a 
-> IO (Response a) 

Same as withMPD, but takes optional arguments that override MPD_HOST and MPD_PORT.

This is e.g. useful for clients that optionally take --port and --host as command line arguments, and fall back to withMPD's defaults if those arguments are not given.

withMPDEx :: Host -> Port -> Password -> MPD a -> IO (Response a) Source #

The most configurable API for running an MPD action.

data Query Source #

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"

Instances

Instances details
Show Query Source # 
Instance details

Defined in Network.MPD.Commands.Query

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Semigroup Query Source # 
Instance details

Defined in Network.MPD.Commands.Query

Methods

(<>) :: Query -> Query -> Query #

sconcat :: NonEmpty Query -> Query #

stimes :: Integral b => b -> Query -> Query #

Monoid Query Source # 
Instance details

Defined in Network.MPD.Commands.Query

Methods

mempty :: Query #

mappend :: Query -> Query -> Query #

mconcat :: [Query] -> Query #

(=?) :: Metadata -> Value -> Query Source #

Create a query matching a tag with a value.

(/=?) :: 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

qNot :: Query -> Query Source #

Negate a Query.

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

anything :: Query Source #

An empty query. Matches anything.

class ToString a where Source #

A type class for values that can be converted to Strings.

Methods

toString :: a -> String Source #

Convert given value to String.

toText :: a -> Text Source #

Convert given value to Text.

toUtf8 :: a -> ByteString Source #

Convert given value to a UTF-8 encoded ByteString.

data Path Source #

Used for commands which require a path within the database. If empty, the root path is used.

Instances

Instances details
Eq Path Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Ord Path Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

compare :: Path -> Path -> Ordering #

(<) :: Path -> Path -> Bool #

(<=) :: Path -> Path -> Bool #

(>) :: Path -> Path -> Bool #

(>=) :: Path -> Path -> Bool #

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

Show Path Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

IsString Path Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

fromString :: String -> Path #

ToString Path Source # 
Instance details

Defined in Network.MPD.Commands.Types

data Metadata Source #

Available metadata types/scope modifiers, used for searching the database for entries with certain metadata values.

data Value Source #

A metadata value.

Instances

Instances details
Eq Value Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Ord Value Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

compare :: Value -> Value -> Ordering #

(<) :: Value -> Value -> Bool #

(<=) :: Value -> Value -> Bool #

(>) :: Value -> Value -> Bool #

(>=) :: Value -> Value -> Bool #

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

Show Value Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

fromString :: String -> Value #

ToString Value Source # 
Instance details

Defined in Network.MPD.Commands.Types

data ObjectType Source #

Object types.

Constructors

SongObj 

Instances

Instances details
Eq ObjectType Source # 
Instance details

Defined in Network.MPD.Commands.Types

Show ObjectType Source # 
Instance details

Defined in Network.MPD.Commands.Types

data PlaybackState Source #

Represents the different playback states.

Constructors

Playing 
Stopped 
Paused 

Instances

Instances details
Bounded PlaybackState Source # 
Instance details

Defined in Network.MPD.Commands.Types

Enum PlaybackState Source # 
Instance details

Defined in Network.MPD.Commands.Types

Eq PlaybackState Source # 
Instance details

Defined in Network.MPD.Commands.Types

Ord PlaybackState Source # 
Instance details

Defined in Network.MPD.Commands.Types

Show PlaybackState Source # 
Instance details

Defined in Network.MPD.Commands.Types

data Subsystem Source #

Represents the various MPD subsystems.

Constructors

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

data ReplayGainMode Source #

Constructors

Off

Disable replay gain

TrackMode

Per track mode

AlbumMode

Per album mode

AutoMode

Auto mode

Since: 0.10.0.0

Instances

Instances details
Bounded ReplayGainMode Source # 
Instance details

Defined in Network.MPD.Commands.Types

Enum ReplayGainMode Source # 
Instance details

Defined in Network.MPD.Commands.Types

Eq ReplayGainMode Source # 
Instance details

Defined in Network.MPD.Commands.Types

Ord ReplayGainMode Source # 
Instance details

Defined in Network.MPD.Commands.Types

Show ReplayGainMode Source # 
Instance details

Defined in Network.MPD.Commands.Types

data Count Source #

Represents the result of running count.

Constructors

Count 

Fields

Instances

Instances details
Eq Count Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

(==) :: Count -> Count -> Bool #

(/=) :: Count -> Count -> Bool #

Show Count Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

showsPrec :: Int -> Count -> ShowS #

show :: Count -> String #

showList :: [Count] -> ShowS #

Default Count Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

def :: Count #

data LsResult Source #

Result of the lsInfo operation

Constructors

LsDirectory Path

Directory

LsSong Song

Song

LsPlaylist PlaylistName

Playlist

Instances

Instances details
Eq LsResult Source # 
Instance details

Defined in Network.MPD.Commands.Types

Show LsResult Source # 
Instance details

Defined in Network.MPD.Commands.Types

data Device Source #

Represents an output device.

Constructors

Device 

Fields

Instances

Instances details
Eq Device Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

(==) :: Device -> Device -> Bool #

(/=) :: Device -> Device -> Bool #

Show Device Source # 
Instance details

Defined in Network.MPD.Commands.Types

Default Device Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

def :: Device #

data Song Source #

Represents a single song item.

Constructors

Song 

Fields

Instances

Instances details
Eq Song Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

(==) :: Song -> Song -> Bool #

(/=) :: Song -> Song -> Bool #

Show Song Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

showsPrec :: Int -> Song -> ShowS #

show :: Song -> String #

showList :: [Song] -> ShowS #

newtype Priority Source #

Constructors

Priority Int 

Instances

Instances details
Eq Priority Source # 
Instance details

Defined in Network.MPD.Commands.Types

Show Priority Source # 
Instance details

Defined in Network.MPD.Commands.Types

type Position = Int Source #

The position of a song in a playlist.

data Range Source #

A range of songs.

Constructors

Range Position Position

Start and end of the range, not including the end position.

Start Position

From the given position until the end of the playlist.

Instances

Instances details
Eq Range Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

(==) :: Range -> Range -> Bool #

(/=) :: Range -> Range -> Bool #

Show Range Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

data Volume Source #

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

Instances details
Bounded Volume Source # 
Instance details

Defined in Network.MPD.Commands.Types

Enum Volume Source # 
Instance details

Defined in Network.MPD.Commands.Types

Eq Volume Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

(==) :: Volume -> Volume -> Bool #

(/=) :: Volume -> Volume -> Bool #

Integral Volume Source # 
Instance details

Defined in Network.MPD.Commands.Types

Num Volume Source # 
Instance details

Defined in Network.MPD.Commands.Types

Ord Volume Source # 
Instance details

Defined in Network.MPD.Commands.Types

Real Volume Source # 
Instance details

Defined in Network.MPD.Commands.Types

Show Volume Source # 
Instance details

Defined in Network.MPD.Commands.Types

newtype Id Source #

Constructors

Id Int 

Instances

Instances details
Eq Id Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

(==) :: Id -> Id -> Bool #

(/=) :: Id -> Id -> Bool #

Show Id Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

sgGetTag :: Metadata -> Song -> Maybe [Value] Source #

Get list of specific tag type

sgAddTag :: Metadata -> Value -> Song -> Song Source #

Add metadata tag value.

data Stats Source #

Container for database statistics.

Constructors

Stats 

Fields

Instances

Instances details
Eq Stats Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

(==) :: Stats -> Stats -> Bool #

(/=) :: Stats -> Stats -> Bool #

Show Stats Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

showsPrec :: Int -> Stats -> ShowS #

show :: Stats -> String #

showList :: [Stats] -> ShowS #

Default Stats Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

def :: Stats #

data Status Source #

Container for MPD status.

Constructors

Status 

Fields

Instances

Instances details
Eq Status Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Show Status Source # 
Instance details

Defined in Network.MPD.Commands.Types

Default Status Source # 
Instance details

Defined in Network.MPD.Commands.Types

Methods

def :: Status #

def :: Default a => a #

The default value for this type.

clearError :: MonadMPD m => m () Source #

Clear the current error message in status.

currentSong :: MonadMPD m => m (Maybe Song) Source #

Get the currently playing song.

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.

noidle :: MonadMPD m => m () Source #

Cancel idle.

stats :: MonadMPD m => m Stats Source #

Get server statistics.

status :: MonadMPD m => m Status Source #

Get the server's status.

consume :: MonadMPD m => Bool -> m () Source #

Set consume mode

crossfade :: MonadMPD m => Seconds -> m () Source #

Set crossfading between songs.

random :: MonadMPD m => Bool -> m () Source #

Set random playing.

repeat :: MonadMPD m => Bool -> m () Source #

Set repeating.

setVolume :: MonadMPD m => Volume -> m () Source #

Set the volume.

single :: MonadMPD m => Bool -> m () Source #

Set single mode

replayGainMode :: MonadMPD m => ReplayGainMode -> m () Source #

Set the replay gain mode.

replayGainStatus :: MonadMPD m => m [(String, String)] Source #

Get the replay gain options.

next :: MonadMPD m => m () Source #

Play the next song.

pause :: MonadMPD m => Bool -> m () Source #

Pauses playback on True, resumes on False.

toggle :: MonadMPD m => m () Source #

Toggles play/pause. Plays if stopped.

Since: 0.10.0.0

play :: MonadMPD m => Maybe Position -> m () Source #

Begin/continue playing.

playId :: MonadMPD m => Id -> m () Source #

Play a file with given id.

previous :: MonadMPD m => m () Source #

Play the previous song.

seek :: MonadMPD m => Position -> FractionalSeconds -> m () Source #

Seek to some point in a song.

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

stop :: MonadMPD m => m () Source #

Stop playing.

addId :: MonadMPD m => Path -> Maybe Position -> m Id Source #

Like add, but returns a playlist id.

add :: MonadMPD m => Path -> m () Source #

Add a song (or a whole directory) to the current playlist.

clear :: MonadMPD m => m () Source #

Clear the current playlist.

delete :: MonadMPD m => Position -> m () Source #

Remove a song from the current playlist.

deleteRange :: MonadMPD m => Range -> m () Source #

Remove a range of songs from the current playlist.

Since: 0.10.0.0

deleteId :: MonadMPD m => Id -> m () Source #

Remove a song from the current playlist.

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

prioId :: MonadMPD m => Priority -> Id -> m () Source #

Set priority by song id.

shuffle :: MonadMPD m => Maybe Range -> m () Source #

Shuffle the current playlist. Optionally restrict to a range of songs.

Since: 0.10.0.0

swap :: MonadMPD m => Position -> Position -> m () Source #

Swap the positions of two songs.

swapId :: MonadMPD m => Id -> Id -> m () Source #

Swap the positions of two songs (Id version)

addTagId :: MonadMPD m => Id -> Metadata -> Value -> m () Source #

Add tag to (remote) song.

clearTagId :: MonadMPD m => Id -> Metadata -> m () Source #

Remove tag from (remote) song.

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.

rename Source #

Arguments

:: 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.

count :: MonadMPD m => Query -> m Count Source #

Count the number of entries matching a query.

find :: MonadMPD m => Query -> m [Song] Source #

Search the database for entries exactly matching a query.

findAdd :: MonadMPD m => Query -> m () Source #

Adds songs matching a query to the current playlist.

list Source #

Arguments

:: MonadMPD m 
=> Metadata

Metadata to list

-> Query 
-> m [Value] 

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.

listAllInfo :: MonadMPD m => Path -> m [LsResult] Source #

Recursive lsInfo.

lsInfo :: MonadMPD m => Path -> m [LsResult] Source #

Non-recursively list the contents of a database directory.

readComments :: MonadMPD m => Path -> m [(String, String)] Source #

Read comments from file at path.

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.

stickerGet Source #

Arguments

:: MonadMPD m 
=> ObjectType 
-> String

Object URI

-> String

Sticker name

-> m [String] 

Reads a sticker value for the specified object.

stickerSet Source #

Arguments

:: MonadMPD m 
=> ObjectType 
-> String

Object URI

-> String

Sticker name

-> String

Sticker value

-> m () 

Adds a sticker value to the specified object.

stickerDelete Source #

Arguments

:: MonadMPD m 
=> ObjectType 
-> String

Object URI

-> String

Sticker name

-> m () 

Delete a sticker value from the specified object.

stickerList Source #

Arguments

:: MonadMPD m 
=> ObjectType 
-> String

Object URI

-> m [(String, String)]

Sticker name/sticker value

Lists the stickers for the specified object.

stickerFind Source #

Arguments

:: 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.

ping :: MonadMPD m => m () Source #

Check that the server is still responding.

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.

outputs :: MonadMPD m => m [Device] Source #

Retrieve information for all output devices.

commands :: MonadMPD m => m [String] Source #

Retrieve a list of available commands.

notCommands :: MonadMPD m => m [String] Source #

Retrieve a list of unavailable (due to access restrictions) commands.

tagTypes :: MonadMPD m => m [String] Source #

Retrieve a list of available song metadata.

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.

config :: MonadMPD m => m [(String, String)] Source #

Retrieve configuration keys and values.

Types

Subscribing to channels

Communicating with other clients

mount :: MonadMPD m => String -> String -> m () Source #

unmount :: MonadMPD m => String -> m () Source #