{-# LINE 1 "Graphics/X11/Xrender.hsc" #-}
module Graphics.X11.Xrender
where
import Graphics.X11
import Graphics.X11.Xlib.Types
import Foreign
import Foreign.C
import Foreign.C.Types
import Foreign.Ptr
import Foreign.Storable( Storable(..) )
peekCUShort :: Ptr a -> CInt -> IO Int
peekCUShort ptr off = do
v <- peekByteOff ptr (fromIntegral off)
return (fromIntegral (v::CUShort))
pokeCUShort :: Ptr a -> CInt -> Int -> IO ()
pokeCUShort ptr off v =
pokeByteOff ptr (fromIntegral off) (fromIntegral v::CUShort)
peekCShort :: Ptr a -> CInt -> IO Int
peekCShort ptr off = do
v <- peekByteOff ptr (fromIntegral off)
return (fromIntegral (v::CShort))
pokeCShort :: Ptr a -> CInt -> Int -> IO ()
pokeCShort ptr off v =
pokeByteOff ptr (fromIntegral off) (fromIntegral v::CShort)
data XRenderColor = XRenderColor {
xrendercolor_red :: Int,
xrendercolor_green :: Int,
xrendercolor_blue :: Int,
xrendercolor_alpha :: Int
}
instance Storable XRenderColor where
sizeOf _ = (8)
{-# LINE 49 "Graphics/X11/Xrender.hsc" #-}
alignment _ = alignment (undefined::CInt)
peek p = do
red <- peekCUShort p (0)
{-# LINE 52 "Graphics/X11/Xrender.hsc" #-}
blue <- peekCUShort p (4)
{-# LINE 53 "Graphics/X11/Xrender.hsc" #-}
green <- peekCUShort p (2)
{-# LINE 54 "Graphics/X11/Xrender.hsc" #-}
alpha <- peekCUShort p (6)
{-# LINE 55 "Graphics/X11/Xrender.hsc" #-}
return (XRenderColor red blue green alpha)
poke p (XRenderColor red blue green alpha) = do
pokeCUShort p (0) red
{-# LINE 58 "Graphics/X11/Xrender.hsc" #-}
pokeCUShort p (4) blue
{-# LINE 59 "Graphics/X11/Xrender.hsc" #-}
pokeCUShort p (2) green
{-# LINE 60 "Graphics/X11/Xrender.hsc" #-}
pokeCUShort p (6) alpha
{-# LINE 61 "Graphics/X11/Xrender.hsc" #-}
data XGlyphInfo = XGlyphInfo {
xglyphinfo_width :: Int,
xglyphinfo_height :: Int,
xglyphinfo_x :: Int,
xglyphinfo_y :: Int,
xglyphinfo_xOff :: Int,
xglyphinfo_yOff :: Int
}
instance Storable XGlyphInfo where
sizeOf _ = (12)
{-# LINE 73 "Graphics/X11/Xrender.hsc" #-}
alignment _ = alignment (undefined::CInt)
peek p = do
width <- peekCUShort p (0)
{-# LINE 76 "Graphics/X11/Xrender.hsc" #-}
height <- peekCUShort p (2)
{-# LINE 77 "Graphics/X11/Xrender.hsc" #-}
x <- peekCShort p (4)
{-# LINE 78 "Graphics/X11/Xrender.hsc" #-}
y <- peekCShort p (6)
{-# LINE 79 "Graphics/X11/Xrender.hsc" #-}
xOff <- peekCShort p (8)
{-# LINE 80 "Graphics/X11/Xrender.hsc" #-}
yOff <- peekCShort p (10)
{-# LINE 81 "Graphics/X11/Xrender.hsc" #-}
return (XGlyphInfo width height x y xOff yOff)
poke p (XGlyphInfo width height x y xOff yOff) = do
pokeCUShort p (0) width
{-# LINE 84 "Graphics/X11/Xrender.hsc" #-}
pokeCUShort p (2) height
{-# LINE 85 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (4) x
{-# LINE 86 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (6) y
{-# LINE 87 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (8) xOff
{-# LINE 88 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (10) yOff
{-# LINE 89 "Graphics/X11/Xrender.hsc" #-}
data XRenderDirectFormat = XRenderDirectFormat {
xrenderdirectformat_red :: Int,
xrenderdirectformat_redMask :: Int,
xrenderdirectformat_green :: Int,
xrenderdirectformat_greenMask :: Int,
xrenderdirectformat_blue :: Int,
xrenderdirectformat_blueMask :: Int,
xrenderdirectformat_alpha :: Int,
xrenderdirectformat_alphaMask :: Int
}
instance Storable XRenderDirectFormat where
sizeOf _ = (16)
{-# LINE 104 "Graphics/X11/Xrender.hsc" #-}
alignment _ = alignment (undefined::CInt)
peek p = do
red <- peekCShort p (0)
{-# LINE 107 "Graphics/X11/Xrender.hsc" #-}
redMask <- peekCShort p (2)
{-# LINE 108 "Graphics/X11/Xrender.hsc" #-}
green <- peekCShort p (4)
{-# LINE 109 "Graphics/X11/Xrender.hsc" #-}
greenMask <- peekCShort p (6)
{-# LINE 110 "Graphics/X11/Xrender.hsc" #-}
blue <- peekCShort p (8)
{-# LINE 111 "Graphics/X11/Xrender.hsc" #-}
blueMask <- peekCShort p (10)
{-# LINE 112 "Graphics/X11/Xrender.hsc" #-}
alpha <- peekCShort p (12)
{-# LINE 113 "Graphics/X11/Xrender.hsc" #-}
alphaMask <- peekCShort p (14)
{-# LINE 114 "Graphics/X11/Xrender.hsc" #-}
return (XRenderDirectFormat red redMask green greenMask blue blueMask alpha alphaMask)
poke p (XRenderDirectFormat red redMask green greenMask blue blueMask alpha alphaMask) = do
pokeCShort p (0) red
{-# LINE 117 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (2) redMask
{-# LINE 118 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (8) blue
{-# LINE 119 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (10) blueMask
{-# LINE 120 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (4) green
{-# LINE 121 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (6) greenMask
{-# LINE 122 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (12) alpha
{-# LINE 123 "Graphics/X11/Xrender.hsc" #-}
pokeCShort p (14) alphaMask
{-# LINE 124 "Graphics/X11/Xrender.hsc" #-}