{-# LINE 1 "Graphics/X11/Xinerama.hsc" #-}
module Graphics.X11.Xinerama (
XineramaScreenInfo(..),
xineramaIsActive,
xineramaQueryExtension,
xineramaQueryVersion,
xineramaQueryScreens,
compiledWithXinerama,
getScreenInfo
) where
import Foreign
import Foreign.C.Types
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras (WindowAttributes(..), getWindowAttributes)
import Graphics.X11.Xlib.Internal
import Control.Monad
data XineramaScreenInfo = XineramaScreenInfo
{ XineramaScreenInfo -> CInt
xsi_screen_number :: !CInt,
XineramaScreenInfo -> CShort
xsi_x_org :: !CShort,
XineramaScreenInfo -> CShort
xsi_y_org :: !CShort,
XineramaScreenInfo -> CShort
xsi_width :: !CShort,
XineramaScreenInfo -> CShort
xsi_height :: !CShort }
deriving (Int -> XineramaScreenInfo -> ShowS
[XineramaScreenInfo] -> ShowS
XineramaScreenInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [XineramaScreenInfo] -> ShowS
$cshowList :: [XineramaScreenInfo] -> ShowS
show :: XineramaScreenInfo -> String
$cshow :: XineramaScreenInfo -> String
showsPrec :: Int -> XineramaScreenInfo -> ShowS
$cshowsPrec :: Int -> XineramaScreenInfo -> ShowS
Show)
getScreenInfo :: Display -> IO [Rectangle]
getScreenInfo :: Display -> IO [Rectangle]
getScreenInfo Display
dpy = do
Maybe [XineramaScreenInfo]
mxs <- Display -> IO (Maybe [XineramaScreenInfo])
xineramaQueryScreens Display
dpy
case Maybe [XineramaScreenInfo]
mxs of
Just [XineramaScreenInfo]
xs -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map XineramaScreenInfo -> Rectangle
xsiToRect forall a b. (a -> b) -> a -> b
$ [XineramaScreenInfo]
xs
Maybe [XineramaScreenInfo]
Nothing -> do
WindowAttributes
wa <- Display -> Window -> IO WindowAttributes
getWindowAttributes Display
dpy (Display -> Window
defaultRootWindow Display
dpy)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Rectangle
{ rect_x :: Position
rect_x = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_x WindowAttributes
wa
, rect_y :: Position
rect_y = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_y WindowAttributes
wa
, rect_width :: Dimension
rect_width = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_width WindowAttributes
wa
, rect_height :: Dimension
rect_height = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ WindowAttributes -> CInt
wa_height WindowAttributes
wa }]
where
xsiToRect :: XineramaScreenInfo -> Rectangle
xsiToRect XineramaScreenInfo
xsi = Rectangle
{ rect_x :: Position
rect_x = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ XineramaScreenInfo -> CShort
xsi_x_org XineramaScreenInfo
xsi
, rect_y :: Position
rect_y = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ XineramaScreenInfo -> CShort
xsi_y_org XineramaScreenInfo
xsi
, rect_width :: Dimension
rect_width = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ XineramaScreenInfo -> CShort
xsi_width XineramaScreenInfo
xsi
, rect_height :: Dimension
rect_height = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ XineramaScreenInfo -> CShort
xsi_height XineramaScreenInfo
xsi
}
{-# LINE 68 "Graphics/X11/Xinerama.hsc" #-}
compiledWithXinerama :: Bool
compiledWithXinerama :: Bool
compiledWithXinerama = Bool
True
instance Storable XineramaScreenInfo where
sizeOf :: XineramaScreenInfo -> Int
sizeOf XineramaScreenInfo
_ = (Int
12)
{-# LINE 76 "Graphics/X11/Xinerama.hsc" #-}
alignment :: XineramaScreenInfo -> Int
alignment XineramaScreenInfo
_ = forall a. Storable a => a -> Int
alignment (forall a. HasCallStack => a
undefined :: CInt)
poke :: Ptr XineramaScreenInfo -> XineramaScreenInfo -> IO ()
poke Ptr XineramaScreenInfo
p XineramaScreenInfo
xsi = do
(\Ptr XineramaScreenInfo
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr XineramaScreenInfo
hsc_ptr Int
0) Ptr XineramaScreenInfo
p forall a b. (a -> b) -> a -> b
$ XineramaScreenInfo -> CInt
xsi_screen_number XineramaScreenInfo
xsi
{-# LINE 81 "Graphics/X11/Xinerama.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) p $ xsi_x_org xsi
{-# LINE 82 "Graphics/X11/Xinerama.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 6) p $ xsi_y_org xsi
{-# LINE 83 "Graphics/X11/Xinerama.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) p $ xsi_width xsi
{-# LINE 84 "Graphics/X11/Xinerama.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 10) p $ xsi_height xsi
{-# LINE 85 "Graphics/X11/Xinerama.hsc" #-}
peek :: Ptr XineramaScreenInfo -> IO XineramaScreenInfo
peek Ptr XineramaScreenInfo
p = forall (m :: * -> *) a. Monad m => a -> m a
return CInt -> CShort -> CShort -> CShort -> CShort -> XineramaScreenInfo
XineramaScreenInfo
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr XineramaScreenInfo
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr XineramaScreenInfo
hsc_ptr Int
0) Ptr XineramaScreenInfo
p)
{-# LINE 88 "Graphics/X11/Xinerama.hsc" #-}
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr XineramaScreenInfo
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr XineramaScreenInfo
hsc_ptr Int
4) Ptr XineramaScreenInfo
p)
{-# LINE 89 "Graphics/X11/Xinerama.hsc" #-}
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr XineramaScreenInfo
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr XineramaScreenInfo
hsc_ptr Int
6) Ptr XineramaScreenInfo
p)
{-# LINE 90 "Graphics/X11/Xinerama.hsc" #-}
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr XineramaScreenInfo
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr XineramaScreenInfo
hsc_ptr Int
8) Ptr XineramaScreenInfo
p)
{-# LINE 91 "Graphics/X11/Xinerama.hsc" #-}
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` ((\Ptr XineramaScreenInfo
hsc_ptr -> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr XineramaScreenInfo
hsc_ptr Int
10) Ptr XineramaScreenInfo
p)
{-# LINE 92 "Graphics/X11/Xinerama.hsc" #-}
foreign import ccall "XineramaIsActive"
xineramaIsActive :: Display -> IO Bool
xineramaQueryExtension :: Display -> IO (Maybe (CInt, CInt))
xineramaQueryExtension :: Display -> IO (Maybe (CInt, CInt))
xineramaQueryExtension Display
dpy = forall a b c d.
(Storable a, Storable b) =>
(Ptr a -> Ptr b -> IO c) -> (c -> a -> b -> d) -> IO d
wrapPtr2 (Display -> Ptr CInt -> Ptr CInt -> IO Bool
cXineramaQueryExtension Display
dpy) forall {a} {a} {a} {b}.
(Integral a, Integral a, Num a, Num b) =>
Bool -> a -> a -> Maybe (a, b)
go
where go :: Bool -> a -> a -> Maybe (a, b)
go Bool
False a
_ a
_ = forall a. Maybe a
Nothing
go Bool
True a
eventbase a
errorbase = forall a. a -> Maybe a
Just (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
eventbase, forall a b. (Integral a, Num b) => a -> b
fromIntegral a
errorbase)
xineramaQueryVersion :: Display -> IO (Maybe (CInt, CInt))
xineramaQueryVersion :: Display -> IO (Maybe (CInt, CInt))
xineramaQueryVersion Display
dpy = forall a b c d.
(Storable a, Storable b) =>
(Ptr a -> Ptr b -> IO c) -> (c -> a -> b -> d) -> IO d
wrapPtr2 (Display -> Ptr CInt -> Ptr CInt -> IO Bool
cXineramaQueryVersion Display
dpy) forall {a} {a} {a} {b}.
(Integral a, Integral a, Num a, Num b) =>
Bool -> a -> a -> Maybe (a, b)
go
where go :: Bool -> a -> a -> Maybe (a, b)
go Bool
False a
_ a
_ = forall a. Maybe a
Nothing
go Bool
True a
major a
minor = forall a. a -> Maybe a
Just (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
major, forall a b. (Integral a, Num b) => a -> b
fromIntegral a
minor)
xineramaQueryScreens :: Display -> IO (Maybe [XineramaScreenInfo])
xineramaQueryScreens :: Display -> IO (Maybe [XineramaScreenInfo])
xineramaQueryScreens Display
dpy =
forall b. (Pool -> IO b) -> IO b
withPool forall a b. (a -> b) -> a -> b
$ \Pool
pool -> do Ptr CInt
intp <- forall a. Storable a => Pool -> IO (Ptr a)
pooledMalloc Pool
pool
Ptr XineramaScreenInfo
p <- Display -> Ptr CInt -> IO (Ptr XineramaScreenInfo)
cXineramaQueryScreens Display
dpy Ptr CInt
intp
if Ptr XineramaScreenInfo
p forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else do CInt
nscreens <- forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
intp
[XineramaScreenInfo]
screens <- forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
nscreens) Ptr XineramaScreenInfo
p
CInt
_ <- forall a. Ptr a -> IO CInt
xFree Ptr XineramaScreenInfo
p
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just [XineramaScreenInfo]
screens)
foreign import ccall "XineramaQueryExtension"
cXineramaQueryExtension :: Display -> Ptr CInt -> Ptr CInt -> IO Bool
foreign import ccall "XineramaQueryVersion"
cXineramaQueryVersion :: Display -> Ptr CInt -> Ptr CInt -> IO Bool
foreign import ccall "XineramaQueryScreens"
cXineramaQueryScreens :: Display -> Ptr CInt -> IO (Ptr XineramaScreenInfo)
wrapPtr2 :: (Storable a, Storable b) => (Ptr a -> Ptr b -> IO c) -> (c -> a -> b -> d) -> IO d
wrapPtr2 :: forall a b c d.
(Storable a, Storable b) =>
(Ptr a -> Ptr b -> IO c) -> (c -> a -> b -> d) -> IO d
wrapPtr2 Ptr a -> Ptr b -> IO c
cfun c -> a -> b -> d
f =
forall b. (Pool -> IO b) -> IO b
withPool forall a b. (a -> b) -> a -> b
$ \Pool
pool -> do Ptr a
aptr <- forall a. Storable a => Pool -> IO (Ptr a)
pooledMalloc Pool
pool
Ptr b
bptr <- forall a. Storable a => Pool -> IO (Ptr a)
pooledMalloc Pool
pool
c
ret <- Ptr a -> Ptr b -> IO c
cfun Ptr a
aptr Ptr b
bptr
a
a <- forall a. Storable a => Ptr a -> IO a
peek Ptr a
aptr
b
b <- forall a. Storable a => Ptr a -> IO a
peek Ptr b
bptr
forall (m :: * -> *) a. Monad m => a -> m a
return (c -> a -> b -> d
f c
ret a
a b
b)
{-# LINE 155 "Graphics/X11/Xinerama.hsc" #-}