{-# LANGUAGE CPP #-}
module Network.MPD (
MonadMPD, MPD, MPDError(..), ACKType(..), Response,
Host, Port, Password,
withMPD, withMPD_, withMPDEx,
module Network.MPD.Commands,
#ifdef TEST
getConnectionSettings, getEnvDefault
#endif
) where
import Prelude
import qualified Control.Exception as E
import Network.MPD.Commands
import Network.MPD.Core
import System.Environment (getEnv)
import System.IO.Error (isDoesNotExistError)
import Data.Maybe (listToMaybe)
withMPD :: MPD a -> IO (Response a)
withMPD = withMPD_ Nothing Nothing
withMPD_ :: Maybe String
-> Maybe String
-> MPD a -> IO (Response a)
withMPD_ mHost mPort action = do
settings <- getConnectionSettings mHost mPort
case settings of
Right (host, port, pw) -> withMPDEx host port pw action
Left err -> (return . Left . Custom) err
getConnectionSettings :: Maybe String -> Maybe String -> IO (Either String (Host, Port, Password))
getConnectionSettings mHost mPort = do
(host, pw) <- parseHost `fmap`
maybe (getEnvDefault "MPD_HOST" "localhost") return mHost
port <- maybe (getEnvDefault "MPD_PORT" "6600") return mPort
case maybeRead port of
Just p -> (return . Right) (host, p, pw)
Nothing -> (return . Left) (show port ++ " is not a valid port!")
where
parseHost s = case breakChar '@' s of
(host, "") -> (host, "")
(pw, host) -> (host, pw)
getEnvDefault :: String -> String -> IO String
getEnvDefault x dflt =
E.catch (getEnv x) (\e -> if isDoesNotExistError e
then return dflt else ioError e)
breakChar :: Char -> String -> (String, String)
breakChar c s = let (x, y) = break (== c) s in (x, drop 1 y)
maybeRead :: Read a => String -> Maybe a
maybeRead = fmap fst . listToMaybe . reads