Copyright | (c) Ben Sinclair 2005-2009 Joachim Fasting 2010 |
---|---|
License | MIT (see LICENSE) |
Maintainer | Joachim Fasting <joachifm@fastmail.fm> |
Stability | alpha |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- class (Monad m, MonadError MPDError m) => MonadMPD m where
- open :: m ()
- close :: m ()
- send :: String -> m [ByteString]
- getPassword :: m Password
- setPassword :: Password -> m ()
- getVersion :: m (Int, Int, Int)
- data MPD a
- data MPDError
- data ACKType
- type Response = Either MPDError
- type Host = String
- type Port = Integer
- type Password = String
- withMPDEx :: Host -> Port -> Password -> MPD a -> IO (Response a)
- getResponse :: MonadMPD m => String -> m [ByteString]
- kill :: MonadMPD m => m ()
Classes
class (Monad m, MonadError MPDError m) => MonadMPD m where Source #
A typeclass to allow for multiple implementations of a connection to an MPD server.
Open (or re-open) a connection to the MPD server.
Close the connection.
send :: String -> m [ByteString] Source #
Send a string to the server and return its response.
getPassword :: m Password Source #
Produce a password to send to the server should it ask for one.
setPassword :: Password -> m () Source #
Alters password to be sent to the server.
getVersion :: m (Int, Int, Int) Source #
Get MPD protocol version
Data types
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) |
Running
withMPDEx :: Host -> Port -> Password -> MPD a -> IO (Response a) Source #
The most configurable API for running an MPD action.
Interacting
getResponse :: MonadMPD m => String -> m [ByteString] Source #
Send a command to the MPD server and return the result.