module DBus.Bus
	( getBus
	, getFirstBus
	, getSystemBus
	, getSessionBus
	, getStarterBus
	) where
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as TL
import qualified Control.Exception as E
import Control.Monad (when)
import Data.Maybe (fromJust, isNothing)
import qualified Data.Set as Set
import System.Environment (getEnv)
import qualified DBus.Address as A
import qualified DBus.Authentication as Auth
import qualified DBus.Connection as C
import DBus.Constants (dbusName, dbusPath, dbusInterface)
import qualified DBus.Message as M
import qualified DBus.Types as T
import DBus.Util (fromRight)
busForConnection :: C.Connection -> IO (C.Connection, T.BusName)
busForConnection c = fmap ((,) c) $ sendHello c
getBus :: Auth.Mechanism -> A.Address -> IO (C.Connection, T.BusName)
getBus = ((busForConnection =<<) .) . C.connect
getFirstBus :: [(Auth.Mechanism, A.Address)] -> IO (C.Connection, T.BusName)
getFirstBus = (busForConnection =<<) . C.connectFirst
getSystemBus :: IO (C.Connection, T.BusName)
getSystemBus = getBus' $ fromEnv `E.catch` noEnv where
	defaultAddr = "unix:path=/var/run/dbus/system_bus_socket"
	fromEnv = getEnv "DBUS_SYSTEM_BUS_ADDRESS"
	noEnv (E.SomeException _) = return defaultAddr
getSessionBus :: IO (C.Connection, T.BusName)
getSessionBus = getBus' $ getEnv "DBUS_SESSION_BUS_ADDRESS"
getStarterBus :: IO (C.Connection, T.BusName)
getStarterBus = getBus' $ getEnv "DBUS_STARTER_ADDRESS"
getBus' :: IO String -> IO (C.Connection, T.BusName)
getBus' io = do
	addr <- fmap TL.pack io
	case A.mkAddresses addr of
		Just [x] -> getBus Auth.realUserID x
		Just  xs -> getFirstBus [(Auth.realUserID,x) | x <- xs]
		_        -> E.throwIO $ C.InvalidAddress addr
hello :: M.MethodCall
hello = M.MethodCall dbusPath
	"Hello"
	(Just dbusInterface)
	(Just dbusName)
	Set.empty
	[]
sendHello :: C.Connection -> IO T.BusName
sendHello c = do
	serial <- fromRight `fmap` C.send c return hello
	reply <- waitForReply c serial
	let name = case M.methodReturnBody reply of
		(x:_) -> T.fromVariant x
		_     -> Nothing
	
	when (isNothing name) $
		E.throwIO $ E.AssertionFailed "Invalid response to Hello()"
	
	return . fromJust $ name
waitForReply :: C.Connection -> M.Serial -> IO M.MethodReturn
waitForReply c serial = do
	received <- C.receive c
	msg <- case received of
		Right x -> return x
		Left _  -> E.throwIO $ E.AssertionFailed "Invalid response to Hello()"
	case msg of
		(M.ReceivedMethodReturn _ _ reply) ->
			if M.methodReturnSerial reply == serial
				then return reply
				else waitForReply c serial
		_ -> waitForReply c serial