Adjust to patched xhb version

This commit is contained in:
Matthias Schiffer 2011-10-08 05:12:41 +02:00
parent 579552b29b
commit 456f9fb6e6
7 changed files with 23 additions and 21 deletions

View file

@ -40,6 +40,7 @@ import Graphics.Rendering.Pango.Layout
import Graphics.Rendering.Pango.Font
import Graphics.XHB
import Graphics.XHB.Connection
import Graphics.XHB.Gen.Xproto
import Codec.Binary.UTF8.String
@ -624,7 +625,7 @@ getWindowGeometry x11 window =
fi :: (Integral a, Num b) => a -> b
fi = fromIntegral
showWindow :: Connection -> Atoms -> WINDOW -> IO Bool
showWindow :: ConnectionClass c r => c -> Atoms -> WINDOW -> IO Bool
showWindow conn atoms window = do
states <- liftM (map (fromXid . toXid) . fromMaybe []) $ getProperty32 conn window (atom_NET_WM_STATE atoms)
transientFor <- liftM (map fromIntegral . fromMaybe []) $ getProperty32 conn window (atomWM_TRANSIENT_FOR atoms)

View file

@ -9,6 +9,7 @@ module Phi.X11 ( X11(..)
) where
import Graphics.XHB hiding (Window)
import Graphics.XHB.Connection
import qualified Graphics.XHB.Connection.Open as CO
import Graphics.XHB.Gen.Xinerama
import Graphics.XHB.Gen.Xproto hiding (Window)
@ -54,11 +55,8 @@ instance Display X11 where
type Window X11 = WINDOW
newtype XEvent = XEvent SomeEvent deriving Typeable
newtype XEvent = XEvent SomeEvent deriving (Show, Typeable)
instance Show XEvent where
show _ = "XEvent (..)"
data XMessage = UpdateScreens [(Rectangle, WINDOW)] deriving (Show, Typeable)
@ -274,11 +272,12 @@ handleConfigureNotifyEvent MkConfigureNotifyEvent { window_ConfigureNotifyEvent
let rect = panelBounds config screenarea
win = panelWindow panel
liftIO $ configureWindow conn win $ toValueParam [ (ConfigWindowX, fromIntegral $ rect_x rect)
, (ConfigWindowY, fromIntegral $ rect_y rect)
, (ConfigWindowWidth, fromIntegral $ rect_width rect)
, (ConfigWindowHeight, fromIntegral $ rect_height rect)
]
liftIO $ configureWindow conn $ MkConfigureWindow win (toMask [ConfigWindowX, ConfigWindowY, ConfigWindowWidth, ConfigWindowHeight]) $
toValueParam [ (ConfigWindowX, fromIntegral $ rect_x rect)
, (ConfigWindowY, fromIntegral $ rect_y rect)
, (ConfigWindowWidth, fromIntegral $ rect_width rect)
, (ConfigWindowHeight, fromIntegral $ rect_height rect)
]
panel' <- createPanel win screenarea
setPanelProperties panel'

View file

@ -6,7 +6,7 @@ module Phi.X11.AtomList ( atoms
import Language.Haskell.TH
import Graphics.XHB
import Graphics.XHB.Connection
import Graphics.XHB.Connection.Open
atoms :: [String]

View file

@ -10,6 +10,7 @@ import Data.List
import Language.Haskell.TH
import Graphics.XHB
import Graphics.XHB.Connection
import Graphics.XHB.Gen.Xproto
import Phi.X11.AtomList

View file

@ -29,7 +29,7 @@ import Graphics.XHB.Gen.Xproto
import System.IO.Unsafe
getReply' :: String -> Receipt a -> IO a
getReply' :: ConnectionClass c r => String -> r a -> IO a
getReply' m = getReply >=> return . fromRight
where
fromRight (Left _) = error m
@ -60,17 +60,17 @@ castToCChar input = unsafePerformIO $
with input $ \ptr ->
peekArray (sizeOf input) (castPtr ptr)
changeProperty8 :: Connection -> PropMode -> WINDOW -> ATOM -> ATOM -> [Word8] -> IO ()
changeProperty8 :: ConnectionClass c r => c -> PropMode -> WINDOW -> ATOM -> ATOM -> [Word8] -> IO ()
changeProperty8 conn mode win prop proptype propdata = changeProperty conn $ MkChangeProperty mode win prop proptype 8 (genericLength propdata) propdata
changeProperty16 :: Connection -> PropMode -> WINDOW -> ATOM -> ATOM -> [Word16] -> IO ()
changeProperty16 :: ConnectionClass c r => c -> PropMode -> WINDOW -> ATOM -> ATOM -> [Word16] -> IO ()
changeProperty16 conn mode win prop proptype propdata = changeProperty conn $ MkChangeProperty mode win prop proptype 16 (genericLength propdata) (castWord16to8 propdata)
changeProperty32 :: Connection -> PropMode -> WINDOW -> ATOM -> ATOM -> [Word32] -> IO ()
changeProperty32 :: ConnectionClass c r => c -> PropMode -> WINDOW -> ATOM -> ATOM -> [Word32] -> IO ()
changeProperty32 conn mode win prop proptype propdata = changeProperty conn $ MkChangeProperty mode win prop proptype 32 (genericLength propdata) (castWord32to8 propdata)
getProperty' :: Word8 -> Connection -> WINDOW -> ATOM -> IO (Maybe [Word8])
getProperty' :: ConnectionClass c r => Word8 -> c -> WINDOW -> ATOM -> IO (Maybe [Word8])
getProperty' format conn win prop = do
reply <- getProperty conn (MkGetProperty False win prop (fromXid xidNone) 0 4) >>= getReply
case reply of
@ -84,13 +84,13 @@ getProperty' format conn win prop = do
Right (MkGetPropertyReply {format_GetPropertyReply = format'}) | format' /= format -> return Nothing
Right (MkGetPropertyReply {value_GetPropertyReply = value}) -> return $ Just value
getProperty8 :: Connection -> WINDOW -> ATOM -> IO (Maybe [Word8])
getProperty8 :: ConnectionClass c r => c -> WINDOW -> ATOM -> IO (Maybe [Word8])
getProperty8 = getProperty' 8
getProperty16 :: Connection -> WINDOW -> ATOM -> IO (Maybe [Word16])
getProperty16 :: ConnectionClass c r => c -> WINDOW -> ATOM -> IO (Maybe [Word16])
getProperty16 conn win prop = getProperty' 16 conn win prop >>= return . fmap castWord8to16
getProperty32 :: Connection -> WINDOW -> ATOM -> IO (Maybe [Word32])
getProperty32 :: ConnectionClass c r => c -> WINDOW -> ATOM -> IO (Maybe [Word32])
getProperty32 conn win prop = getProperty' 32 conn win prop >>= return . fmap castWord8to32