module Graphics.XHB.Connection
(Connection
,connect
,connectTo
,displayInfo
,connectionSetup
,mkConnection
,newResource
,pollForEvent
,waitForEvent
,pollForError
,waitForError
,setCrashOnError
,SomeError
,SomeEvent
,getRoot
)
where
import Data.Word
import Control.Concurrent.STM
import Control.Concurrent
import Control.Monad
import System.IO
import System.ByteOrder
import Foreign.C.String
import Data.List (genericLength)
import Data.Maybe
import Data.Monoid(mempty)
import qualified Data.Map as M
import Data.ByteString.Lazy(ByteString)
import qualified Data.ByteString.Lazy as BS
import Data.Binary.Get
import Data.Binary.Put
import Data.Bits
import Graphics.XHB.Gen.Xproto.Types
import Graphics.XHB.Gen.Extension
import Graphics.XHB.Connection.Types
import Graphics.XHB.Connection.Internal
import Graphics.XHB.Connection.Open
import Graphics.XHB.Shared
import Graphics.X11.Xauth
connectionSetup :: Connection -> Setup
connectionSetup = conf_setup . conn_conf
newResource :: XidLike a => Connection -> IO a
newResource c = do
xidM <- nextXid c
case xidM of
Just xid -> return . fromXid $ xid
Nothing -> error "resource ids exhausted"
nextXid :: Connection -> IO (Maybe Xid)
nextXid c = atomically $ do
let tv = conn_resource_ids c
xids <- readTVar tv
case xids of
[] -> return Nothing
(x:xs) -> do
writeTVar tv xs
return . return $ x
pollForEvent :: Connection -> IO (Maybe SomeEvent)
pollForEvent c = atomically $ pollTChan $ conn_event_queue c
waitForEvent :: Connection -> IO SomeEvent
waitForEvent c = atomically $ readTChan $ conn_event_queue c
pollForError :: Connection -> IO (Maybe SomeError)
pollForError c = atomically $ pollTChan $ conn_error_queue c
waitForError :: Connection -> IO SomeError
waitForError c = atomically $ readTChan $ conn_error_queue c
pollTChan :: TChan a -> STM (Maybe a)
pollTChan tc = do
empty <- isEmptyTChan tc
if empty then return Nothing
else Just `liftM` readTChan tc
setCrashOnError :: Connection -> IO ()
setCrashOnError c = do
forkIO $ do
waitForError c
error "Received error from server. Crashing."
return ()
data GenericReply = GenericReply
{grep_response_type :: ResponseType
,grep_error_code :: Word8
,grep_sequence :: Word16
,grep_reply_length :: Word32
}
data ResponseType
= ResponseTypeEvent Word8
| ResponseTypeError
| ResponseTypeReply
instance Deserialize GenericReply where
deserialize = do
type_flag <- deserialize
let rType = case type_flag of
0 -> ResponseTypeError
1 -> ResponseTypeReply
_ -> ResponseTypeEvent type_flag
code <- deserialize
sequence <- deserialize
reply_length <- deserialize
return $ GenericReply rType code sequence reply_length
data ReadLoop = ReadLoop
{read_error_queue :: TChan SomeError
,read_event_queue :: TChan SomeEvent
,read_input_queue :: Handle
,read_reps :: TChan PendedReply
,read_config :: ConnectionConfig
,read_extensions :: TVar ExtensionMap
}
queryExtMap :: (QueryExtensionReply -> Word8)
-> ReadLoop -> Word8 -> IO (Maybe (ExtensionId, Word8))
queryExtMap f r code = do
ext_map <- atomically . readTVar $ read_extensions r
return $ findFromCode ext_map
where findFromCode xmap = foldr go Nothing (M.toList xmap)
go (ident, extInfo) old
| num <= code =
case old of
Just (_oldIndent, oldNum) | oldNum > num -> old
_ -> Just (ident, num)
| otherwise = old
where num = f extInfo
extensionIdFromEventCode :: ReadLoop -> Word8
-> IO (Maybe (ExtensionId, Word8))
extensionIdFromEventCode = queryExtMap first_event_QueryExtensionReply
extensionIdFromErrorCode :: ReadLoop -> Word8
-> IO (Maybe (ExtensionId, Word8))
extensionIdFromErrorCode = queryExtMap first_error_QueryExtensionReply
bsToError :: ReadLoop
-> ByteString
-> Word8
-> IO SomeError
bsToError _r chunk code | code < 128 = case deserializeError code of
Nothing -> return . toError . UnknownError $ chunk
Just getAction -> return $ runGet getAction chunk
bsToError r chunk code
= extensionIdFromErrorCode r code >>= \errInfo -> case errInfo of
Nothing -> return . toError . UnknownError $ chunk
Just (extId, baseErr) ->
case errorDispatch extId (code baseErr) of
Nothing -> return . toError . UnknownError $ chunk
Just getAction -> return $ runGet getAction chunk
bsToEvent :: ReadLoop
-> ByteString
-> Word8
-> IO SomeEvent
bsToEvent _r chunk code | code < 64 = case deserializeEvent code of
Nothing -> return . toEvent . UnknownEvent $ chunk
Just getAction -> return $ runGet getAction chunk
bsToEvent r chunk code
= extensionIdFromEventCode r code >>= \evInfo -> case evInfo of
Nothing -> return . toEvent . UnknownEvent $ chunk
Just (extId, baseEv) ->
case eventDispatch extId (code baseEv) of
Nothing -> return . toEvent . UnknownEvent $ chunk
Just getAction -> return $ runGet getAction chunk
deserializeInReadLoop rl = deserialize
readBytes :: ReadLoop -> Int -> IO ByteString
readBytes rl n = BS.hGet (read_input_queue rl) n
readLoop :: ReadLoop -> IO ()
readLoop rl = do
chunk <- readBytes rl 32
let genRep = flip runGet chunk $ deserialize
case grep_response_type genRep of
ResponseTypeError -> readLoopError rl genRep chunk
ResponseTypeReply -> readLoopReply rl genRep chunk
ResponseTypeEvent _ -> readLoopEvent rl genRep chunk
readLoop rl
readLoopReply :: ReadLoop -> GenericReply -> ByteString -> IO ()
readLoopReply rl genRep chunk = do
let rlength = grep_reply_length genRep
extra <- readBytes rl $ fromIntegral $ 4 * rlength
let bytes = chunk `BS.append` extra
atomically $ do
nextPend <- readTChan $ read_reps rl
if (pended_sequence nextPend) == (grep_sequence genRep)
then putReceipt (pended_reply nextPend) $ Right bytes
else unGetTChan (read_reps rl) nextPend
readLoopError rl genRep chunk = do
let errorCode = grep_error_code genRep
err <- bsToError rl chunk errorCode
atomically $ do
nextPend <- readTChan $ read_reps rl
if (pended_sequence nextPend) == (grep_sequence genRep)
then putReceipt (pended_reply nextPend) $ Left err
else do
unGetTChan (read_reps rl) nextPend
writeTChan (read_error_queue rl) err
readLoopEvent rl genRep chunk = do
ev <- bsToEvent rl chunk eventCode
atomically $ writeTChan (read_event_queue rl) ev
where eventCode = case grep_response_type genRep of
ResponseTypeEvent w -> w .&. 127
connect :: IO (Maybe Connection)
connect = connectTo ""
connectTo :: String -> IO (Maybe Connection)
connectTo display = do
(h, xau, dispName) <- open display
hSetBuffering h NoBuffering
mkConnection h xau dispName
displayInfo :: Connection -> DispName
displayInfo = conn_dispInfo
mkConnection :: Handle -> Maybe Xauth -> DispName -> IO (Maybe Connection)
mkConnection hnd auth dispInfo = do
errorQueue <- newTChanIO
eventQueue <- newTChanIO
replies <- newTChanIO
sequence <- initialSequence
extensions <- newTVarIO mempty
wrappedHandle <- newMVar hnd
confM <- handshake hnd auth
if isNothing confM then return Nothing else do
let Just conf = confM
rIds <- newTVarIO $ resourceIds conf
let rlData = ReadLoop errorQueue eventQueue hnd replies conf extensions
readTid <- forkIO $ readLoop rlData
return $ Just $
Connection
errorQueue
eventQueue
readTid
wrappedHandle
replies
conf
sequence
rIds
extensions
dispInfo
resourceIds :: ConnectionConfig -> [Xid]
resourceIds cc = resourceIdsFromSetup $ conf_setup cc
resourceIdsFromSetup :: Setup -> [Xid]
resourceIdsFromSetup s =
let base = resource_id_base_Setup s
mask = resource_id_mask_Setup s
max = mask
step = mask .&. (mask)
in map MkXid $ map (.|. base) [0,step .. max]
data GenericSetup = GenericSetup
{setup_status :: SetupStatus
,setup_length :: Word16
}
deriving Show
instance Deserialize GenericSetup where
deserialize = do
status <- deserialize
skip 5
length <- deserialize
return $ GenericSetup status length
data SetupStatus = SetupFailed | SetupAuthenticate | SetupSuccess
deriving Show
instance Deserialize SetupStatus where
deserialize = wordToStatus `liftM` deserialize
where wordToStatus :: Word8 -> SetupStatus
wordToStatus 0 = SetupFailed
wordToStatus 1 = SetupSuccess
wordToStatus 2 = SetupAuthenticate
wordToStatus n = error $
"Unkonwn setup status flag: " ++ show n
handshake :: Handle -> Maybe Xauth -> IO (Maybe ConnectionConfig)
handshake hnd auth = do
let requestChunk = runPut $ serialize $ setupRequest auth
BS.hPut hnd $ requestChunk
firstChunk <- BS.hGet hnd 8
let genSetup = runGet deserialize firstChunk
secondChunk <- BS.hGet hnd $ fromIntegral $ (4 *) $ setup_length genSetup
let setupBytes = firstChunk `BS.append` secondChunk
case setup_status genSetup of
SetupFailed -> do
let failed = runGet deserialize setupBytes
failMessage = map castCCharToChar (reason_SetupFailed failed)
hPutStrLn stderr failMessage
return Nothing
SetupAuthenticate -> do
let auth = runGet deserialize setupBytes
authMessage = map castCCharToChar (reason_SetupAuthenticate auth)
hPutStrLn stderr authMessage
return Nothing
SetupSuccess -> do
let setup = runGet deserialize setupBytes
return . return $ ConnectionConfig setup
padBS n = BS.replicate n 0
initialSequence :: IO (TVar SequenceId)
initialSequence = newTVarIO 1
setupRequest :: Maybe Xauth -> SetupRequest
setupRequest auth = MkSetupRequest
(fromIntegral $ byteOrderToNum byteOrder)
11
0
anamelen
adatalen
(aname ++ replicate (requiredPadding anamelen) 0)
(adata ++ replicate (requiredPadding adatalen) 0)
where
(anamelen, aname, adatalen, adata) = case auth of
Nothing -> (0, [], 0, [])
Just (Xauth n d) -> (genericLength n, n, genericLength d, d)
getRoot :: Connection -> WINDOW
getRoot = root_SCREEN . head . roots_Setup . conf_setup . conn_conf