{-# INCLUDE <bindings.macros.h> #-}
{-# INCLUDE <directfb.h> #-}
{-# INCLUDE <directfb_version.h> #-}
{-# INCLUDE <directfbgl.h> #-}
{-# LINE 1 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 2 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 3 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 4 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 5 "src/Bindings/DirectFB/Types.hsc" #-}

-- | <http://directfb.org/docs/DirectFB_Reference_1_4/types.html>

module Bindings.DirectFB.Types where
import Prelude (IO,Num,return,(.),($),Eq,Show,take)
import Foreign.Ptr (Ptr,FunPtr,plusPtr)
import Foreign.Ptr (wordPtrToPtr,castPtrToFunPtr)
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String (CString,CStringLen,CWString,CWStringLen)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word

{-# LINE 10 "src/Bindings/DirectFB/Types.hsc" #-}
import Bindings.Posix.Sys.Select

foreign import ccall "&directfb_major_version" p'directfb_major_version
  :: Ptr (CUInt)

{-# LINE 13 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "&directfb_minor_version" p'directfb_minor_version
  :: Ptr (CUInt)

{-# LINE 14 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "&directfb_micro_version" p'directfb_micro_version
  :: Ptr (CUInt)

{-# LINE 15 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "&directfb_binary_age" p'directfb_binary_age
  :: Ptr (CUInt)

{-# LINE 16 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "&directfb_interface_age" p'directfb_interface_age
  :: Ptr (CUInt)

{-# LINE 17 "src/Bindings/DirectFB/Types.hsc" #-}

foreign import ccall "DirectFBCheckVersion" c'DirectFBCheckVersion
  :: CUInt -> CUInt -> CUInt -> IO CString
foreign import ccall "&DirectFBCheckVersion" p'DirectFBCheckVersion
  :: FunPtr (CUInt -> CUInt -> CUInt -> IO CString)

{-# LINE 19 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "DirectFBError" c'DirectFBError
  :: CString -> C'DFBResult -> IO C'DFBResult
foreign import ccall "&DirectFBError" p'DirectFBError
  :: FunPtr (CString -> C'DFBResult -> IO C'DFBResult)

{-# LINE 20 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "DirectFBErrorFatal" c'DirectFBErrorFatal
  :: CString -> C'DFBResult -> IO C'DFBResult
foreign import ccall "&DirectFBErrorFatal" p'DirectFBErrorFatal
  :: FunPtr (CString -> C'DFBResult -> IO C'DFBResult)

{-# LINE 21 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "DirectFBErrorString" c'DirectFBErrorString
  :: C'DFBResult -> IO CString
foreign import ccall "&DirectFBErrorString" p'DirectFBErrorString
  :: FunPtr (C'DFBResult -> IO CString)

{-# LINE 22 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "DirectFBUsageString" c'DirectFBUsageString
  :: IO CString
foreign import ccall "&DirectFBUsageString" p'DirectFBUsageString
  :: FunPtr (IO CString)

{-# LINE 23 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "DirectFBInit" c'DirectFBInit
  :: Ptr CInt -> Ptr (Ptr (CString)) -> IO C'DFBResult
foreign import ccall "&DirectFBInit" p'DirectFBInit
  :: FunPtr (Ptr CInt -> Ptr (Ptr (CString)) -> IO C'DFBResult)

{-# LINE 24 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "DirectFBSetOption" c'DirectFBSetOption
  :: CString -> CString -> IO C'DFBResult
foreign import ccall "&DirectFBSetOption" p'DirectFBSetOption
  :: FunPtr (CString -> CString -> IO C'DFBResult)

{-# LINE 25 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBResult = Word32

{-# LINE 27 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_OK = 0
c'DFB_OK :: (Num a) => a

{-# LINE 29 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_FAILURE = 1
c'DFB_FAILURE :: (Num a) => a

{-# LINE 30 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_INIT = 2
c'DFB_INIT :: (Num a) => a

{-# LINE 31 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_BUG = 3
c'DFB_BUG :: (Num a) => a

{-# LINE 32 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_DEAD = 4
c'DFB_DEAD :: (Num a) => a

{-# LINE 33 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_UNSUPPORTED = 5
c'DFB_UNSUPPORTED :: (Num a) => a

{-# LINE 34 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_UNIMPLEMENTED = 6
c'DFB_UNIMPLEMENTED :: (Num a) => a

{-# LINE 35 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_ACCESSDENIED = 7
c'DFB_ACCESSDENIED :: (Num a) => a

{-# LINE 36 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_INVAREA = 8
c'DFB_INVAREA :: (Num a) => a

{-# LINE 37 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_INVARG = 9
c'DFB_INVARG :: (Num a) => a

{-# LINE 38 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_NOSYSTEMMEMORY = 10
c'DFB_NOSYSTEMMEMORY :: (Num a) => a

{-# LINE 39 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_NOSHAREDMEMORY = 11
c'DFB_NOSHAREDMEMORY :: (Num a) => a

{-# LINE 40 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_LOCKED = 12
c'DFB_LOCKED :: (Num a) => a

{-# LINE 41 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_BUFFEREMPTY = 13
c'DFB_BUFFEREMPTY :: (Num a) => a

{-# LINE 42 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_FILENOTFOUND = 14
c'DFB_FILENOTFOUND :: (Num a) => a

{-# LINE 43 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_IO = 15
c'DFB_IO :: (Num a) => a

{-# LINE 44 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_BUSY = 16
c'DFB_BUSY :: (Num a) => a

{-# LINE 45 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_NOIMPL = 17
c'DFB_NOIMPL :: (Num a) => a

{-# LINE 46 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_TIMEOUT = 18
c'DFB_TIMEOUT :: (Num a) => a

{-# LINE 47 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_THIZNULL = 19
c'DFB_THIZNULL :: (Num a) => a

{-# LINE 48 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_IDNOTFOUND = 20
c'DFB_IDNOTFOUND :: (Num a) => a

{-# LINE 49 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_DESTROYED = 21
c'DFB_DESTROYED :: (Num a) => a

{-# LINE 50 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_FUSION = 22
c'DFB_FUSION :: (Num a) => a

{-# LINE 51 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_BUFFERTOOLARGE = 23
c'DFB_BUFFERTOOLARGE :: (Num a) => a

{-# LINE 52 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_INTERRUPTED = 24
c'DFB_INTERRUPTED :: (Num a) => a

{-# LINE 53 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_NOCONTEXT = 25
c'DFB_NOCONTEXT :: (Num a) => a

{-# LINE 54 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_TEMPUNAVAIL = 26
c'DFB_TEMPUNAVAIL :: (Num a) => a

{-# LINE 55 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_LIMITEXCEEDED = 27
c'DFB_LIMITEXCEEDED :: (Num a) => a

{-# LINE 56 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_NOSUCHMETHOD = 28
c'DFB_NOSUCHMETHOD :: (Num a) => a

{-# LINE 57 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_NOSUCHINSTANCE = 29
c'DFB_NOSUCHINSTANCE :: (Num a) => a

{-# LINE 58 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_ITEMNOTFOUND = 30
c'DFB_ITEMNOTFOUND :: (Num a) => a

{-# LINE 59 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_VERSIONMISMATCH = 31
c'DFB_VERSIONMISMATCH :: (Num a) => a

{-# LINE 60 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_EOF = 32
c'DFB_EOF :: (Num a) => a

{-# LINE 61 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_SUSPENDED = 33
c'DFB_SUSPENDED :: (Num a) => a

{-# LINE 62 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_INCOMPLETE = 34
c'DFB_INCOMPLETE :: (Num a) => a

{-# LINE 63 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_NOCORE = 35
c'DFB_NOCORE :: (Num a) => a

{-# LINE 64 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_NOVIDEOMEMORY = 2300186625
c'DFB_NOVIDEOMEMORY :: (Num a) => a

{-# LINE 65 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_MISSINGFONT = 2300186626
c'DFB_MISSINGFONT :: (Num a) => a

{-# LINE 66 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_MISSINGIMAGE = 2300186627
c'DFB_MISSINGIMAGE :: (Num a) => a

{-# LINE 67 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBBoolean = Word32

{-# LINE 69 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_FALSE = 0
c'DFB_FALSE :: (Num a) => a

{-# LINE 71 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_TRUE = 1
c'DFB_TRUE :: (Num a) => a

{-# LINE 72 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBPoint = C'DFBPoint{
{-# LINE 74 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBPoint'x :: CInt
{-# LINE 75 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBPoint'y :: CInt
{-# LINE 76 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBPoint where
  sizeOf _ = 8
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    return $ C'DFBPoint v0 v1
  poke p (C'DFBPoint v0 v1) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    return ()

{-# LINE 77 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBSpan = C'DFBSpan{
{-# LINE 79 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBSpan'x :: CInt
{-# LINE 80 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSpan'w :: CInt
{-# LINE 81 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBSpan where
  sizeOf _ = 8
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    return $ C'DFBSpan v0 v1
  poke p (C'DFBSpan v0 v1) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    return ()

{-# LINE 82 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBDimension = C'DFBDimension{
{-# LINE 84 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBDimension'w :: CInt
{-# LINE 85 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDimension'h :: CInt
{-# LINE 86 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBDimension where
  sizeOf _ = 8
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    return $ C'DFBDimension v0 v1
  poke p (C'DFBDimension v0 v1) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    return ()

{-# LINE 87 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBRectangle = C'DFBRectangle{
{-# LINE 89 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBRectangle'x :: CInt
{-# LINE 90 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBRectangle'y :: CInt
{-# LINE 91 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBRectangle'w :: CInt
{-# LINE 92 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBRectangle'h :: CInt
{-# LINE 93 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBRectangle where
  sizeOf _ = 16
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    return $ C'DFBRectangle v0 v1 v2 v3
  poke p (C'DFBRectangle v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    return ()

{-# LINE 94 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBLocation = C'DFBLocation{
{-# LINE 96 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBLocation'x :: CFloat
{-# LINE 97 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBLocation'y :: CFloat
{-# LINE 98 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBLocation'w :: CFloat
{-# LINE 99 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBLocation'h :: CFloat
{-# LINE 100 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBLocation where
  sizeOf _ = 16
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    return $ C'DFBLocation v0 v1 v2 v3
  poke p (C'DFBLocation v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    return ()

{-# LINE 101 "src/Bindings/DirectFB/Types.hsc" #-}


data C'DFBRegion = C'DFBRegion{
{-# LINE 104 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBRegion'x1 :: CInt
{-# LINE 105 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBRegion'y1 :: CInt
{-# LINE 106 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBRegion'x2 :: CInt
{-# LINE 107 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBRegion'y2 :: CInt
{-# LINE 108 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBRegion where
  sizeOf _ = 16
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    return $ C'DFBRegion v0 v1 v2 v3
  poke p (C'DFBRegion v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    return ()

{-# LINE 109 "src/Bindings/DirectFB/Types.hsc" #-}


data C'DFBInsets = C'DFBInsets{
{-# LINE 112 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBInsets'l :: CInt
{-# LINE 113 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInsets't :: CInt
{-# LINE 114 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInsets'r :: CInt
{-# LINE 115 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInsets'b :: CInt
{-# LINE 116 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBInsets where
  sizeOf _ = 16
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    return $ C'DFBInsets v0 v1 v2 v3
  poke p (C'DFBInsets v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    return ()

{-# LINE 117 "src/Bindings/DirectFB/Types.hsc" #-}


data C'DFBTriangle = C'DFBTriangle{
{-# LINE 120 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBTriangle'x1 :: CInt
{-# LINE 121 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBTriangle'y1 :: CInt
{-# LINE 122 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBTriangle'x2 :: CInt
{-# LINE 123 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBTriangle'y2 :: CInt
{-# LINE 124 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBTriangle'x3 :: CInt
{-# LINE 125 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBTriangle'y3 :: CInt
{-# LINE 126 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBTriangle where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'DFBTriangle v0 v1 v2 v3 v4 v5
  poke p (C'DFBTriangle v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 127 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBColor = C'DFBColor{
{-# LINE 129 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBColor'a :: Word8
{-# LINE 130 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColor'r :: Word8
{-# LINE 131 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColor'g :: Word8
{-# LINE 132 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColor'b :: Word8
{-# LINE 133 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBColor where
  sizeOf _ = 4
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 1
    v2 <- peekByteOff p 2
    v3 <- peekByteOff p 3
    return $ C'DFBColor v0 v1 v2 v3
  poke p (C'DFBColor v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 1 v1
    pokeByteOff p 2 v2
    pokeByteOff p 3 v3
    return ()

{-# LINE 134 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBColorKey = C'DFBColorKey{
{-# LINE 136 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBColorKey'index :: Word8
{-# LINE 137 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColorKey'r :: Word8
{-# LINE 138 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColorKey'g :: Word8
{-# LINE 139 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColorKey'b :: Word8
{-# LINE 140 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBColorKey where
  sizeOf _ = 4
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 1
    v2 <- peekByteOff p 2
    v3 <- peekByteOff p 3
    return $ C'DFBColorKey v0 v1 v2 v3
  poke p (C'DFBColorKey v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 1 v1
    pokeByteOff p 2 v2
    pokeByteOff p 3 v3
    return ()

{-# LINE 141 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBColorYUV = C'DFBColorYUV{
{-# LINE 143 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBColorYUV'a :: Word8
{-# LINE 144 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColorYUV'y :: Word8
{-# LINE 145 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColorYUV'u :: Word8
{-# LINE 146 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColorYUV'v :: Word8
{-# LINE 147 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBColorYUV where
  sizeOf _ = 4
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 1
    v2 <- peekByteOff p 2
    v3 <- peekByteOff p 3
    return $ C'DFBColorYUV v0 v1 v2 v3
  poke p (C'DFBColorYUV v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 1 v1
    pokeByteOff p 2 v2
    pokeByteOff p 3 v3
    return ()

{-# LINE 148 "src/Bindings/DirectFB/Types.hsc" #-}


{-# LINE 152 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 155 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_DISPLAYLAYER_IDS_MAX = 32
c'DFB_DISPLAYLAYER_IDS_MAX :: (Num a) => a

{-# LINE 156 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenID = Word32

{-# LINE 158 "src/Bindings/DirectFB/Types.hsc" #-}
type C'DFBDisplayLayerID = Word32

{-# LINE 159 "src/Bindings/DirectFB/Types.hsc" #-}
type C'DFBDisplayLayerSourceID = Word32

{-# LINE 160 "src/Bindings/DirectFB/Types.hsc" #-}
type C'DFBWindowID = Word32

{-# LINE 161 "src/Bindings/DirectFB/Types.hsc" #-}
type C'DFBInputDeviceID = Word32

{-# LINE 162 "src/Bindings/DirectFB/Types.hsc" #-}
type C'DFBTextEncodingID = Word32

{-# LINE 163 "src/Bindings/DirectFB/Types.hsc" #-}
type C'DFBDisplayLayerIDs = Word32

{-# LINE 164 "src/Bindings/DirectFB/Types.hsc" #-}

c'DTEID_UTF8 = 0
c'DTEID_UTF8 :: (Num a) => a

{-# LINE 166 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBCooperativeLevel = Word32

{-# LINE 168 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFSCL_NORMAL = 0
c'DFSCL_NORMAL :: (Num a) => a

{-# LINE 170 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFSCL_FULLSCREEN = 1
c'DFSCL_FULLSCREEN :: (Num a) => a

{-# LINE 171 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFSCL_EXCLUSIVE = 2
c'DFSCL_EXCLUSIVE :: (Num a) => a

{-# LINE 172 "src/Bindings/DirectFB/Types.hsc" #-}


type C'DFBDisplayLayerCapabilities = Word32

{-# LINE 175 "src/Bindings/DirectFB/Types.hsc" #-}

c'DLCAPS_NONE = 0
c'DLCAPS_NONE :: (Num a) => a

{-# LINE 177 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_SURFACE = 1
c'DLCAPS_SURFACE :: (Num a) => a

{-# LINE 178 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_OPACITY = 2
c'DLCAPS_OPACITY :: (Num a) => a

{-# LINE 179 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_ALPHACHANNEL = 4
c'DLCAPS_ALPHACHANNEL :: (Num a) => a

{-# LINE 180 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_SCREEN_LOCATION = 8
c'DLCAPS_SCREEN_LOCATION :: (Num a) => a

{-# LINE 181 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_FLICKER_FILTERING = 16
c'DLCAPS_FLICKER_FILTERING :: (Num a) => a

{-# LINE 182 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_DEINTERLACING = 32
c'DLCAPS_DEINTERLACING :: (Num a) => a

{-# LINE 183 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_SRC_COLORKEY = 64
c'DLCAPS_SRC_COLORKEY :: (Num a) => a

{-# LINE 184 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_DST_COLORKEY = 128
c'DLCAPS_DST_COLORKEY :: (Num a) => a

{-# LINE 185 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_BRIGHTNESS = 256
c'DLCAPS_BRIGHTNESS :: (Num a) => a

{-# LINE 186 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_CONTRAST = 512
c'DLCAPS_CONTRAST :: (Num a) => a

{-# LINE 187 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_HUE = 1024
c'DLCAPS_HUE :: (Num a) => a

{-# LINE 188 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_SATURATION = 2048
c'DLCAPS_SATURATION :: (Num a) => a

{-# LINE 189 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_LEVELS = 4096
c'DLCAPS_LEVELS :: (Num a) => a

{-# LINE 190 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_FIELD_PARITY = 8192
c'DLCAPS_FIELD_PARITY :: (Num a) => a

{-# LINE 191 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_WINDOWS = 16384
c'DLCAPS_WINDOWS :: (Num a) => a

{-# LINE 192 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_SOURCES = 32768
c'DLCAPS_SOURCES :: (Num a) => a

{-# LINE 193 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_ALPHA_RAMP = 65536
c'DLCAPS_ALPHA_RAMP :: (Num a) => a

{-# LINE 194 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_PREMULTIPLIED = 131072
c'DLCAPS_PREMULTIPLIED :: (Num a) => a

{-# LINE 195 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_SCREEN_POSITION = 1048576
c'DLCAPS_SCREEN_POSITION :: (Num a) => a

{-# LINE 196 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_SCREEN_SIZE = 2097152
c'DLCAPS_SCREEN_SIZE :: (Num a) => a

{-# LINE 197 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_CLIP_REGIONS = 4194304
c'DLCAPS_CLIP_REGIONS :: (Num a) => a

{-# LINE 198 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCAPS_ALL = 7602175
c'DLCAPS_ALL :: (Num a) => a

{-# LINE 199 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenCapabilities = Word32

{-# LINE 201 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSCCAPS_NONE = 0
c'DSCCAPS_NONE :: (Num a) => a

{-# LINE 203 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCCAPS_VSYNC = 1
c'DSCCAPS_VSYNC :: (Num a) => a

{-# LINE 204 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCCAPS_POWER_MANAGEMENT = 2
c'DSCCAPS_POWER_MANAGEMENT :: (Num a) => a

{-# LINE 205 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCCAPS_MIXERS = 16
c'DSCCAPS_MIXERS :: (Num a) => a

{-# LINE 206 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCCAPS_ENCODERS = 32
c'DSCCAPS_ENCODERS :: (Num a) => a

{-# LINE 207 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCCAPS_OUTPUTS = 64
c'DSCCAPS_OUTPUTS :: (Num a) => a

{-# LINE 208 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCCAPS_ALL = 115
c'DSCCAPS_ALL :: (Num a) => a

{-# LINE 209 "src/Bindings/DirectFB/Types.hsc" #-}


type C'DFBDisplayLayerOptions = Word32

{-# LINE 212 "src/Bindings/DirectFB/Types.hsc" #-}

c'DLOP_NONE = 0
c'DLOP_NONE :: (Num a) => a

{-# LINE 214 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLOP_ALPHACHANNEL = 1
c'DLOP_ALPHACHANNEL :: (Num a) => a

{-# LINE 215 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLOP_FLICKER_FILTERING = 2
c'DLOP_FLICKER_FILTERING :: (Num a) => a

{-# LINE 216 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLOP_DEINTERLACING = 4
c'DLOP_DEINTERLACING :: (Num a) => a

{-# LINE 217 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLOP_SRC_COLORKEY = 8
c'DLOP_SRC_COLORKEY :: (Num a) => a

{-# LINE 218 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLOP_DST_COLORKEY = 16
c'DLOP_DST_COLORKEY :: (Num a) => a

{-# LINE 219 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLOP_OPACITY = 32
c'DLOP_OPACITY :: (Num a) => a

{-# LINE 220 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLOP_FIELD_PARITY = 64
c'DLOP_FIELD_PARITY :: (Num a) => a

{-# LINE 221 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBDisplayLayerBufferMode = Word32

{-# LINE 223 "src/Bindings/DirectFB/Types.hsc" #-}

c'DLBM_UNKNOWN = 0
c'DLBM_UNKNOWN :: (Num a) => a

{-# LINE 225 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLBM_FRONTONLY = 1
c'DLBM_FRONTONLY :: (Num a) => a

{-# LINE 226 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLBM_BACKVIDEO = 2
c'DLBM_BACKVIDEO :: (Num a) => a

{-# LINE 227 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLBM_BACKSYSTEM = 4
c'DLBM_BACKSYSTEM :: (Num a) => a

{-# LINE 228 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLBM_TRIPLE = 8
c'DLBM_TRIPLE :: (Num a) => a

{-# LINE 229 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLBM_WINDOWS = 16
c'DLBM_WINDOWS :: (Num a) => a

{-# LINE 230 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBSurfaceDescriptionFlags = Word32

{-# LINE 232 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSDESC_NONE = 0
c'DSDESC_NONE :: (Num a) => a

{-# LINE 234 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDESC_CAPS = 1
c'DSDESC_CAPS :: (Num a) => a

{-# LINE 235 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDESC_WIDTH = 2
c'DSDESC_WIDTH :: (Num a) => a

{-# LINE 236 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDESC_HEIGHT = 4
c'DSDESC_HEIGHT :: (Num a) => a

{-# LINE 237 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDESC_PIXELFORMAT = 8
c'DSDESC_PIXELFORMAT :: (Num a) => a

{-# LINE 238 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDESC_PREALLOCATED = 16
c'DSDESC_PREALLOCATED :: (Num a) => a

{-# LINE 239 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDESC_PALETTE = 32
c'DSDESC_PALETTE :: (Num a) => a

{-# LINE 240 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDESC_RESOURCE_ID = 256
c'DSDESC_RESOURCE_ID :: (Num a) => a

{-# LINE 241 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 244 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDESC_ALL = 319
c'DSDESC_ALL :: (Num a) => a

{-# LINE 245 "src/Bindings/DirectFB/Types.hsc" #-}


type C'DFBPaletteDescriptionFlags = Word32

{-# LINE 248 "src/Bindings/DirectFB/Types.hsc" #-}

c'DPDESC_CAPS = 1
c'DPDESC_CAPS :: (Num a) => a

{-# LINE 250 "src/Bindings/DirectFB/Types.hsc" #-}
c'DPDESC_SIZE = 2
c'DPDESC_SIZE :: (Num a) => a

{-# LINE 251 "src/Bindings/DirectFB/Types.hsc" #-}
c'DPDESC_ENTRIES = 4
c'DPDESC_ENTRIES :: (Num a) => a

{-# LINE 252 "src/Bindings/DirectFB/Types.hsc" #-}


type C'DFBSurfaceCapabilities = Word32

{-# LINE 255 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSCAPS_NONE = 0
c'DSCAPS_NONE :: (Num a) => a

{-# LINE 257 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_PRIMARY = 1
c'DSCAPS_PRIMARY :: (Num a) => a

{-# LINE 258 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_SYSTEMONLY = 2
c'DSCAPS_SYSTEMONLY :: (Num a) => a

{-# LINE 259 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_VIDEOONLY = 4
c'DSCAPS_VIDEOONLY :: (Num a) => a

{-# LINE 260 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_DOUBLE = 16
c'DSCAPS_DOUBLE :: (Num a) => a

{-# LINE 261 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_SUBSURFACE = 32
c'DSCAPS_SUBSURFACE :: (Num a) => a

{-# LINE 262 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_INTERLACED = 64
c'DSCAPS_INTERLACED :: (Num a) => a

{-# LINE 263 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_SEPARATED = 128
c'DSCAPS_SEPARATED :: (Num a) => a

{-# LINE 264 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_STATIC_ALLOC = 256
c'DSCAPS_STATIC_ALLOC :: (Num a) => a

{-# LINE 265 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_TRIPLE = 512
c'DSCAPS_TRIPLE :: (Num a) => a

{-# LINE 266 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_PREMULTIPLIED = 4096
c'DSCAPS_PREMULTIPLIED :: (Num a) => a

{-# LINE 267 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_DEPTH = 65536
c'DSCAPS_DEPTH :: (Num a) => a

{-# LINE 268 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_SHARED = 1048576
c'DSCAPS_SHARED :: (Num a) => a

{-# LINE 269 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 272 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_ALL = 1119223
c'DSCAPS_ALL :: (Num a) => a

{-# LINE 273 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCAPS_FLIPPING = 528
c'DSCAPS_FLIPPING :: (Num a) => a

{-# LINE 274 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBPaletteCapabilities = Word32

{-# LINE 276 "src/Bindings/DirectFB/Types.hsc" #-}

c'DPCAPS_NONE = 0
c'DPCAPS_NONE :: (Num a) => a

{-# LINE 278 "src/Bindings/DirectFB/Types.hsc" #-}


type C'DFBSurfaceDrawingFlags = Word32

{-# LINE 281 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSDRAW_NOFX = 0
c'DSDRAW_NOFX :: (Num a) => a

{-# LINE 283 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDRAW_BLEND = 1
c'DSDRAW_BLEND :: (Num a) => a

{-# LINE 284 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDRAW_DST_COLORKEY = 2
c'DSDRAW_DST_COLORKEY :: (Num a) => a

{-# LINE 285 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDRAW_SRC_PREMULTIPLY = 4
c'DSDRAW_SRC_PREMULTIPLY :: (Num a) => a

{-# LINE 286 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDRAW_DST_PREMULTIPLY = 8
c'DSDRAW_DST_PREMULTIPLY :: (Num a) => a

{-# LINE 287 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDRAW_DEMULTIPLY = 16
c'DSDRAW_DEMULTIPLY :: (Num a) => a

{-# LINE 288 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSDRAW_XOR = 32
c'DSDRAW_XOR :: (Num a) => a

{-# LINE 289 "src/Bindings/DirectFB/Types.hsc" #-}


type C'DFBSurfaceBlittingFlags = Word32

{-# LINE 292 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSBLIT_NOFX = 0
c'DSBLIT_NOFX :: (Num a) => a

{-# LINE 294 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_BLEND_ALPHACHANNEL = 1
c'DSBLIT_BLEND_ALPHACHANNEL :: (Num a) => a

{-# LINE 295 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_BLEND_COLORALPHA = 2
c'DSBLIT_BLEND_COLORALPHA :: (Num a) => a

{-# LINE 296 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_COLORIZE = 4
c'DSBLIT_COLORIZE :: (Num a) => a

{-# LINE 297 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_SRC_COLORKEY = 8
c'DSBLIT_SRC_COLORKEY :: (Num a) => a

{-# LINE 298 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_DST_COLORKEY = 16
c'DSBLIT_DST_COLORKEY :: (Num a) => a

{-# LINE 299 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_SRC_PREMULTIPLY = 32
c'DSBLIT_SRC_PREMULTIPLY :: (Num a) => a

{-# LINE 300 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_DST_PREMULTIPLY = 64
c'DSBLIT_DST_PREMULTIPLY :: (Num a) => a

{-# LINE 301 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_DEMULTIPLY = 128
c'DSBLIT_DEMULTIPLY :: (Num a) => a

{-# LINE 302 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_DEINTERLACE = 256
c'DSBLIT_DEINTERLACE :: (Num a) => a

{-# LINE 303 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_SRC_PREMULTCOLOR = 512
c'DSBLIT_SRC_PREMULTCOLOR :: (Num a) => a

{-# LINE 304 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_XOR = 1024
c'DSBLIT_XOR :: (Num a) => a

{-# LINE 305 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_INDEX_TRANSLATION = 2048
c'DSBLIT_INDEX_TRANSLATION :: (Num a) => a

{-# LINE 306 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 309 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_ROTATE180 = 4096
c'DSBLIT_ROTATE180 :: (Num a) => a

{-# LINE 310 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 313 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_COLORKEY_PROTECT = 65536
c'DSBLIT_COLORKEY_PROTECT :: (Num a) => a

{-# LINE 314 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_SRC_MASK_ALPHA = 1048576
c'DSBLIT_SRC_MASK_ALPHA :: (Num a) => a

{-# LINE 315 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBLIT_SRC_MASK_COLOR = 2097152
c'DSBLIT_SRC_MASK_COLOR :: (Num a) => a

{-# LINE 316 "src/Bindings/DirectFB/Types.hsc" #-}


type C'DFBSurfaceRenderOptions = Word32

{-# LINE 319 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSRO_NONE = 0
c'DSRO_NONE :: (Num a) => a

{-# LINE 321 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSRO_SMOOTH_UPSCALE = 1
c'DSRO_SMOOTH_UPSCALE :: (Num a) => a

{-# LINE 322 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSRO_SMOOTH_DOWNSCALE = 2
c'DSRO_SMOOTH_DOWNSCALE :: (Num a) => a

{-# LINE 323 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSRO_MATRIX = 4
c'DSRO_MATRIX :: (Num a) => a

{-# LINE 324 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSRO_ANTIALIAS = 8
c'DSRO_ANTIALIAS :: (Num a) => a

{-# LINE 325 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSRO_ALL = 15
c'DSRO_ALL :: (Num a) => a

{-# LINE 326 "src/Bindings/DirectFB/Types.hsc" #-}


type C'DFBAccelerationMask = Word32

{-# LINE 329 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFXL_NONE = 0
c'DFXL_NONE :: (Num a) => a

{-# LINE 331 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_FILLRECTANGLE = 1
c'DFXL_FILLRECTANGLE :: (Num a) => a

{-# LINE 332 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_DRAWRECTANGLE = 2
c'DFXL_DRAWRECTANGLE :: (Num a) => a

{-# LINE 333 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_DRAWLINE = 4
c'DFXL_DRAWLINE :: (Num a) => a

{-# LINE 334 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_FILLTRIANGLE = 8
c'DFXL_FILLTRIANGLE :: (Num a) => a

{-# LINE 335 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_BLIT = 65536
c'DFXL_BLIT :: (Num a) => a

{-# LINE 336 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_STRETCHBLIT = 131072
c'DFXL_STRETCHBLIT :: (Num a) => a

{-# LINE 337 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_TEXTRIANGLES = 262144
c'DFXL_TEXTRIANGLES :: (Num a) => a

{-# LINE 338 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_DRAWSTRING = 16777216
c'DFXL_DRAWSTRING :: (Num a) => a

{-# LINE 339 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_ALL = 17235983
c'DFXL_ALL :: (Num a) => a

{-# LINE 340 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_ALL_DRAW = 15
c'DFXL_ALL_DRAW :: (Num a) => a

{-# LINE 341 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFXL_ALL_BLIT = 17235968
c'DFXL_ALL_BLIT :: (Num a) => a

{-# LINE 342 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBDisplayLayerTypeFlags = Word32

{-# LINE 344 "src/Bindings/DirectFB/Types.hsc" #-}

c'DLTF_NONE = 0
c'DLTF_NONE :: (Num a) => a

{-# LINE 346 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLTF_GRAPHICS = 1
c'DLTF_GRAPHICS :: (Num a) => a

{-# LINE 347 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLTF_VIDEO = 2
c'DLTF_VIDEO :: (Num a) => a

{-# LINE 348 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLTF_STILL_PICTURE = 4
c'DLTF_STILL_PICTURE :: (Num a) => a

{-# LINE 349 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLTF_BACKGROUND = 8
c'DLTF_BACKGROUND :: (Num a) => a

{-# LINE 350 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLTF_ALL = 15
c'DLTF_ALL :: (Num a) => a

{-# LINE 351 "src/Bindings/DirectFB/Types.hsc" #-}


type C'DFBInputDeviceTypeFlags = Word32

{-# LINE 354 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIDTF_NONE = 0
c'DIDTF_NONE :: (Num a) => a

{-# LINE 356 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIDTF_KEYBOARD = 1
c'DIDTF_KEYBOARD :: (Num a) => a

{-# LINE 357 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIDTF_MOUSE = 2
c'DIDTF_MOUSE :: (Num a) => a

{-# LINE 358 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIDTF_JOYSTICK = 4
c'DIDTF_JOYSTICK :: (Num a) => a

{-# LINE 359 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIDTF_REMOTE = 8
c'DIDTF_REMOTE :: (Num a) => a

{-# LINE 360 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIDTF_VIRTUAL = 16
c'DIDTF_VIRTUAL :: (Num a) => a

{-# LINE 361 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIDTF_ALL = 31
c'DIDTF_ALL :: (Num a) => a

{-# LINE 362 "src/Bindings/DirectFB/Types.hsc" #-}


type C'DFBInputDeviceCapabilities = Word32

{-# LINE 365 "src/Bindings/DirectFB/Types.hsc" #-}

c'DICAPS_KEYS = 1
c'DICAPS_KEYS :: (Num a) => a

{-# LINE 367 "src/Bindings/DirectFB/Types.hsc" #-}
c'DICAPS_AXES = 2
c'DICAPS_AXES :: (Num a) => a

{-# LINE 368 "src/Bindings/DirectFB/Types.hsc" #-}
c'DICAPS_BUTTONS = 4
c'DICAPS_BUTTONS :: (Num a) => a

{-# LINE 369 "src/Bindings/DirectFB/Types.hsc" #-}
c'DICAPS_ALL = 7
c'DICAPS_ALL :: (Num a) => a

{-# LINE 370 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceButtonIdentifier = Word32

{-# LINE 372 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIBI_LEFT = 0
c'DIBI_LEFT :: (Num a) => a

{-# LINE 374 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIBI_RIGHT = 1
c'DIBI_RIGHT :: (Num a) => a

{-# LINE 375 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIBI_MIDDLE = 2
c'DIBI_MIDDLE :: (Num a) => a

{-# LINE 376 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIBI_FIRST = 0
c'DIBI_FIRST :: (Num a) => a

{-# LINE 377 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIBI_LAST = 31
c'DIBI_LAST :: (Num a) => a

{-# LINE 378 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceAxisIdentifier = Word32

{-# LINE 380 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIAI_X = 0
c'DIAI_X :: (Num a) => a

{-# LINE 382 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIAI_Y = 1
c'DIAI_Y :: (Num a) => a

{-# LINE 383 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIAI_Z = 2
c'DIAI_Z :: (Num a) => a

{-# LINE 384 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIAI_FIRST = 0
c'DIAI_FIRST :: (Num a) => a

{-# LINE 385 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIAI_LAST = 31
c'DIAI_LAST :: (Num a) => a

{-# LINE 386 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBWindowDescriptionFlags = Word32

{-# LINE 388 "src/Bindings/DirectFB/Types.hsc" #-}

c'DWDESC_CAPS = 1
c'DWDESC_CAPS :: (Num a) => a

{-# LINE 390 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWDESC_WIDTH = 2
c'DWDESC_WIDTH :: (Num a) => a

{-# LINE 391 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWDESC_HEIGHT = 4
c'DWDESC_HEIGHT :: (Num a) => a

{-# LINE 392 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWDESC_PIXELFORMAT = 8
c'DWDESC_PIXELFORMAT :: (Num a) => a

{-# LINE 393 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWDESC_POSX = 16
c'DWDESC_POSX :: (Num a) => a

{-# LINE 394 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWDESC_POSY = 32
c'DWDESC_POSY :: (Num a) => a

{-# LINE 395 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWDESC_SURFACE_CAPS = 64
c'DWDESC_SURFACE_CAPS :: (Num a) => a

{-# LINE 396 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWDESC_PARENT = 128
c'DWDESC_PARENT :: (Num a) => a

{-# LINE 397 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWDESC_OPTIONS = 256
c'DWDESC_OPTIONS :: (Num a) => a

{-# LINE 398 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWDESC_STACKING = 512
c'DWDESC_STACKING :: (Num a) => a

{-# LINE 399 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 402 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWDESC_RESOURCE_ID = 4096
c'DWDESC_RESOURCE_ID :: (Num a) => a

{-# LINE 403 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBDataBufferDescriptionFlags = Word32

{-# LINE 405 "src/Bindings/DirectFB/Types.hsc" #-}

c'DBDESC_FILE = 1
c'DBDESC_FILE :: (Num a) => a

{-# LINE 407 "src/Bindings/DirectFB/Types.hsc" #-}
c'DBDESC_MEMORY = 2
c'DBDESC_MEMORY :: (Num a) => a

{-# LINE 408 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBWindowCapabilities = Word32

{-# LINE 410 "src/Bindings/DirectFB/Types.hsc" #-}

c'DWCAPS_NONE = 0
c'DWCAPS_NONE :: (Num a) => a

{-# LINE 412 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWCAPS_ALPHACHANNEL = 1
c'DWCAPS_ALPHACHANNEL :: (Num a) => a

{-# LINE 413 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWCAPS_DOUBLEBUFFER = 2
c'DWCAPS_DOUBLEBUFFER :: (Num a) => a

{-# LINE 414 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWCAPS_INPUTONLY = 4
c'DWCAPS_INPUTONLY :: (Num a) => a

{-# LINE 415 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWCAPS_NODECORATION = 8
c'DWCAPS_NODECORATION :: (Num a) => a

{-# LINE 416 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 419 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 422 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWCAPS_NOFOCUS = 256
c'DWCAPS_NOFOCUS :: (Num a) => a

{-# LINE 423 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWCAPS_ALL = 271
c'DWCAPS_ALL :: (Num a) => a

{-# LINE 424 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBWindowOptions = Word32

{-# LINE 426 "src/Bindings/DirectFB/Types.hsc" #-}

c'DWOP_NONE = 0
c'DWOP_NONE :: (Num a) => a

{-# LINE 428 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_COLORKEYING = 1
c'DWOP_COLORKEYING :: (Num a) => a

{-# LINE 429 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_ALPHACHANNEL = 2
c'DWOP_ALPHACHANNEL :: (Num a) => a

{-# LINE 430 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_OPAQUE_REGION = 4
c'DWOP_OPAQUE_REGION :: (Num a) => a

{-# LINE 431 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_SHAPED = 8
c'DWOP_SHAPED :: (Num a) => a

{-# LINE 432 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_KEEP_POSITION = 16
c'DWOP_KEEP_POSITION :: (Num a) => a

{-# LINE 433 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_KEEP_SIZE = 32
c'DWOP_KEEP_SIZE :: (Num a) => a

{-# LINE 434 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_KEEP_STACKING = 64
c'DWOP_KEEP_STACKING :: (Num a) => a

{-# LINE 435 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_GHOST = 4096
c'DWOP_GHOST :: (Num a) => a

{-# LINE 436 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_INDESTRUCTIBLE = 8192
c'DWOP_INDESTRUCTIBLE :: (Num a) => a

{-# LINE 437 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_SCALE = 65536
c'DWOP_SCALE :: (Num a) => a

{-# LINE 438 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_KEEP_ABOVE = 1048576
c'DWOP_KEEP_ABOVE :: (Num a) => a

{-# LINE 439 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_KEEP_UNDER = 2097152
c'DWOP_KEEP_UNDER :: (Num a) => a

{-# LINE 440 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 443 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWOP_ALL = 3223679
c'DWOP_ALL :: (Num a) => a

{-# LINE 444 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBWindowStackingClass = Word32

{-# LINE 446 "src/Bindings/DirectFB/Types.hsc" #-}

c'DWSC_MIDDLE = 0
c'DWSC_MIDDLE :: (Num a) => a

{-# LINE 448 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWSC_UPPER = 1
c'DWSC_UPPER :: (Num a) => a

{-# LINE 449 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWSC_LOWER = 2
c'DWSC_LOWER :: (Num a) => a

{-# LINE 450 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBFontAttributes = Word32

{-# LINE 452 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFFA_NONE = 0
c'DFFA_NONE :: (Num a) => a

{-# LINE 454 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFFA_NOKERNING = 1
c'DFFA_NOKERNING :: (Num a) => a

{-# LINE 455 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFFA_NOHINTING = 2
c'DFFA_NOHINTING :: (Num a) => a

{-# LINE 456 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFFA_MONOCHROME = 4
c'DFFA_MONOCHROME :: (Num a) => a

{-# LINE 457 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFFA_NOCHARMAP = 8
c'DFFA_NOCHARMAP :: (Num a) => a

{-# LINE 458 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFFA_FIXEDCLIP = 16
c'DFFA_FIXEDCLIP :: (Num a) => a

{-# LINE 459 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 462 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 465 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBFontDescriptionFlags = Word32

{-# LINE 467 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFDESC_ATTRIBUTES = 1
c'DFDESC_ATTRIBUTES :: (Num a) => a

{-# LINE 469 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFDESC_HEIGHT = 2
c'DFDESC_HEIGHT :: (Num a) => a

{-# LINE 470 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFDESC_WIDTH = 4
c'DFDESC_WIDTH :: (Num a) => a

{-# LINE 471 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFDESC_INDEX = 8
c'DFDESC_INDEX :: (Num a) => a

{-# LINE 472 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFDESC_FIXEDADVANCE = 16
c'DFDESC_FIXEDADVANCE :: (Num a) => a

{-# LINE 473 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFDESC_FRACT_HEIGHT = 32
c'DFDESC_FRACT_HEIGHT :: (Num a) => a

{-# LINE 474 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFDESC_FRACT_WIDTH = 64
c'DFDESC_FRACT_WIDTH :: (Num a) => a

{-# LINE 475 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 478 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 481 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBFontDescription = C'DFBFontDescription{
{-# LINE 483 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBFontDescription'flags :: C'DFBFontDescriptionFlags
{-# LINE 484 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBFontDescription'attributes :: C'DFBFontAttributes
{-# LINE 485 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBFontDescription'height :: CInt
{-# LINE 486 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBFontDescription'width :: CInt
{-# LINE 487 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBFontDescription'index :: CUInt
{-# LINE 488 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBFontDescription'fixed_advance :: CInt
{-# LINE 489 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBFontDescription'fract_height :: CInt
{-# LINE 490 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBFontDescription'fract_width :: CInt
{-# LINE 491 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 495 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBFontDescription where
  sizeOf _ = 32
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    return $ C'DFBFontDescription v0 v1 v2 v3 v4 v5 v6 v7
  poke p (C'DFBFontDescription v0 v1 v2 v3 v4 v5 v6 v7) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    return ()

{-# LINE 496 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBSurfacePixelFormat = CInt

{-# LINE 498 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSPF_UNKNOWN = 0
c'DSPF_UNKNOWN :: (Num a) => a

{-# LINE 500 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_ARGB1555 = 2168704
c'DSPF_ARGB1555 :: (Num a) => a

{-# LINE 501 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_RGB16 = 2099201
c'DSPF_RGB16 :: (Num a) => a

{-# LINE 502 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_RGB24 = 3148802
c'DSPF_RGB24 :: (Num a) => a

{-# LINE 503 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_RGB32 = 4197379
c'DSPF_RGB32 :: (Num a) => a

{-# LINE 504 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_ARGB = 4295684
c'DSPF_ARGB :: (Num a) => a

{-# LINE 505 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_A8 = 1146885
c'DSPF_A8 :: (Num a) => a

{-# LINE 506 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_YUY2 = 2099206
c'DSPF_YUY2 :: (Num a) => a

{-# LINE 507 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_RGB332 = 1049607
c'DSPF_RGB332 :: (Num a) => a

{-# LINE 508 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_UYVY = 2099208
c'DSPF_UYVY :: (Num a) => a

{-# LINE 509 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_I420 = 135267849
c'DSPF_I420 :: (Num a) => a

{-# LINE 510 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_YV12 = 135267850
c'DSPF_YV12 :: (Num a) => a

{-# LINE 511 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_LUT8 = 1074856971
c'DSPF_LUT8 :: (Num a) => a

{-# LINE 512 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_ALUT44 = 1074872844
c'DSPF_ALUT44 :: (Num a) => a

{-# LINE 513 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_AiRGB = -2143187955
c'DSPF_AiRGB :: (Num a) => a

{-# LINE 514 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_A1 = 58920974
c'DSPF_A1 :: (Num a) => a

{-# LINE 515 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_NV12 = 135267855
c'DSPF_NV12 :: (Num a) => a

{-# LINE 516 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_NV16 = 269487120
c'DSPF_NV16 :: (Num a) => a

{-# LINE 517 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_ARGB2554 = 2172689
c'DSPF_ARGB2554 :: (Num a) => a

{-# LINE 518 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_ARGB4444 = 2180626
c'DSPF_ARGB4444 :: (Num a) => a

{-# LINE 519 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 522 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_NV21 = 135267859
c'DSPF_NV21 :: (Num a) => a

{-# LINE 523 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_AYUV = 4295700
c'DSPF_AYUV :: (Num a) => a

{-# LINE 524 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_A4 = 8994837
c'DSPF_A4 :: (Num a) => a

{-# LINE 525 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_ARGB1666 = 3217686
c'DSPF_ARGB1666 :: (Num a) => a

{-# LINE 526 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_ARGB6666 = 3238167
c'DSPF_ARGB6666 :: (Num a) => a

{-# LINE 527 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_RGB18 = 3148056
c'DSPF_RGB18 :: (Num a) => a

{-# LINE 528 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_LUT2 = 1099235609
c'DSPF_LUT2 :: (Num a) => a

{-# LINE 529 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_RGB444 = 2098714
c'DSPF_RGB444 :: (Num a) => a

{-# LINE 530 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_RGB555 = 2099099
c'DSPF_RGB555 :: (Num a) => a

{-# LINE 531 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPF_BGR555 = 2099100
c'DSPF_BGR555 :: (Num a) => a

{-# LINE 532 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 535 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_NUM_PIXELFORMATS = 29
c'DFB_NUM_PIXELFORMATS :: (Num a) => a

{-# LINE 536 "src/Bindings/DirectFB/Types.hsc" #-}

foreign import ccall "inline_DFB_PIXELFORMAT_INDEX" c'DFB_PIXELFORMAT_INDEX
  :: C'DFBSurfacePixelFormat -> CInt

{-# LINE 538 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_COLOR_BITS_PER_PIXEL" c'DFB_COLOR_BITS_PER_PIXEL
  :: C'DFBSurfacePixelFormat -> CInt

{-# LINE 539 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_ALPHA_BITS_PER_PIXEL" c'DFB_ALPHA_BITS_PER_PIXEL
  :: C'DFBSurfacePixelFormat -> CInt

{-# LINE 540 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_PIXELFORMAT_HAS_ALPHA" c'DFB_PIXELFORMAT_HAS_ALPHA
  :: C'DFBSurfacePixelFormat -> CInt

{-# LINE 541 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_BITS_PER_PIXEL" c'DFB_BITS_PER_PIXEL
  :: C'DFBSurfacePixelFormat -> CInt

{-# LINE 542 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_BYTES_PER_PIXEL" c'DFB_BYTES_PER_PIXEL
  :: C'DFBSurfacePixelFormat -> CInt

{-# LINE 543 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_BYTES_PER_LINE" c'DFB_BYTES_PER_LINE
  :: C'DFBSurfacePixelFormat -> CInt -> CInt

{-# LINE 544 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_PIXELFORMAT_ALIGNMENT" c'DFB_PIXELFORMAT_ALIGNMENT
  :: C'DFBSurfacePixelFormat -> CInt

{-# LINE 545 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_PLANE_MULTIPLY" c'DFB_PLANE_MULTIPLY
  :: C'DFBSurfacePixelFormat -> CInt -> CInt

{-# LINE 546 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_PIXELFORMAT_IS_INDEXED" c'DFB_PIXELFORMAT_IS_INDEXED
  :: C'DFBSurfacePixelFormat -> CInt

{-# LINE 547 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_PLANAR_PIXELFORMAT" c'DFB_PLANAR_PIXELFORMAT
  :: C'DFBSurfacePixelFormat -> CInt

{-# LINE 548 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_PIXELFORMAT_INV_ALPHA" c'DFB_PIXELFORMAT_INV_ALPHA
  :: C'DFBSurfacePixelFormat -> CInt

{-# LINE 549 "src/Bindings/DirectFB/Types.hsc" #-}


{-# LINE 559 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBSurfaceDescription = C'DFBSurfaceDescription{
{-# LINE 561 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBSurfaceDescription'flags :: C'DFBSurfaceDescriptionFlags
{-# LINE 562 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'caps :: C'DFBSurfaceCapabilities
{-# LINE 563 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'width :: CInt
{-# LINE 564 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'height :: CInt
{-# LINE 565 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'pixelformat :: C'DFBSurfacePixelFormat
{-# LINE 566 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'preallocated_0_'data :: Ptr ()
{-# LINE 567 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'preallocated_0_'pitch :: CInt
{-# LINE 568 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'preallocated_1_'data :: Ptr ()
{-# LINE 569 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'preallocated_1_'pitch :: CInt
{-# LINE 570 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'palette'entries :: Ptr C'DFBColor
{-# LINE 571 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'palette'size :: CUInt
{-# LINE 572 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBSurfaceDescription'resource_id :: CULong
{-# LINE 573 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 576 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBSurfaceDescription where
  sizeOf _ = 48
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    v8 <- peekByteOff p 32
    v9 <- peekByteOff p 36
    v10 <- peekByteOff p 40
    v11 <- peekByteOff p 44
    return $ C'DFBSurfaceDescription v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11
  poke p (C'DFBSurfaceDescription v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    pokeByteOff p 32 v8
    pokeByteOff p 36 v9
    pokeByteOff p 40 v10
    pokeByteOff p 44 v11
    return ()

{-# LINE 577 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBPaletteDescription = C'DFBPaletteDescription{
{-# LINE 579 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBPaletteDescription'caps :: C'DFBPaletteCapabilities
{-# LINE 580 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBPaletteDescription'size :: CUInt
{-# LINE 581 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBPaletteDescription'entries :: Ptr C'DFBColor
{-# LINE 582 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBPaletteDescription where
  sizeOf _ = 16
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 4
    v1 <- peekByteOff p 8
    v2 <- peekByteOff p 12
    return $ C'DFBPaletteDescription v0 v1 v2
  poke p (C'DFBPaletteDescription v0 v1 v2) = do
    pokeByteOff p 4 v0
    pokeByteOff p 8 v1
    pokeByteOff p 12 v2
    return ()

{-# LINE 583 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_DISPLAY_LAYER_DESC_NAME_LENGTH = 32
c'DFB_DISPLAY_LAYER_DESC_NAME_LENGTH :: (Num a) => a

{-# LINE 585 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBDisplayLayerDescription = C'DFBDisplayLayerDescription{
{-# LINE 587 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBDisplayLayerDescription'type :: C'DFBDisplayLayerTypeFlags
{-# LINE 588 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerDescription'caps :: C'DFBDisplayLayerCapabilities
{-# LINE 589 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerDescription'name :: [CChar]
{-# LINE 590 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerDescription'level :: CInt
{-# LINE 591 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerDescription'regions :: CInt
{-# LINE 592 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerDescription'sources :: CInt
{-# LINE 593 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerDescription'clip_regions :: CInt
{-# LINE 594 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBDisplayLayerDescription where
  sizeOf _ = 56
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekArray 32 (plusPtr p 8)
    v3 <- peekByteOff p 40
    v4 <- peekByteOff p 44
    v5 <- peekByteOff p 48
    v6 <- peekByteOff p 52
    return $ C'DFBDisplayLayerDescription v0 v1 v2 v3 v4 v5 v6
  poke p (C'DFBDisplayLayerDescription v0 v1 v2 v3 v4 v5 v6) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeArray (plusPtr p 8) (take 32 v2)
    pokeByteOff p 40 v3
    pokeByteOff p 44 v4
    pokeByteOff p 48 v5
    pokeByteOff p 52 v6
    return ()

{-# LINE 595 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBDisplayLayerSourceCaps = Word32

{-# LINE 597 "src/Bindings/DirectFB/Types.hsc" #-}

c'DDLSCAPS_NONE = 0
c'DDLSCAPS_NONE :: (Num a) => a

{-# LINE 599 "src/Bindings/DirectFB/Types.hsc" #-}
c'DDLSCAPS_SURFACE = 1
c'DDLSCAPS_SURFACE :: (Num a) => a

{-# LINE 600 "src/Bindings/DirectFB/Types.hsc" #-}
c'DDLSCAPS_ALL = 1
c'DDLSCAPS_ALL :: (Num a) => a

{-# LINE 601 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_DISPLAY_LAYER_SOURCE_DESC_NAME_LENGTH = 24
c'DFB_DISPLAY_LAYER_SOURCE_DESC_NAME_LENGTH :: (Num a) => a

{-# LINE 603 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBDisplayLayerSourceDescription = C'DFBDisplayLayerSourceDescription{
{-# LINE 605 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBDisplayLayerSourceDescription'source_id :: C'DFBDisplayLayerSourceID
{-# LINE 606 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerSourceDescription'name :: [CChar]
{-# LINE 607 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerSourceDescription'caps :: C'DFBDisplayLayerSourceCaps
{-# LINE 608 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBDisplayLayerSourceDescription where
  sizeOf _ = 32
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekArray 24 (plusPtr p 4)
    v2 <- peekByteOff p 28
    return $ C'DFBDisplayLayerSourceDescription v0 v1 v2
  poke p (C'DFBDisplayLayerSourceDescription v0 v1 v2) = do
    pokeByteOff p 0 v0
    pokeArray (plusPtr p 4) (take 24 v1)
    pokeByteOff p 28 v2
    return ()

{-# LINE 609 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_SCREEN_DESC_NAME_LENGTH = 32
c'DFB_SCREEN_DESC_NAME_LENGTH :: (Num a) => a

{-# LINE 611 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBScreenDescription = C'DFBScreenDescription{
{-# LINE 613 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBScreenDescription'caps :: C'DFBScreenCapabilities
{-# LINE 614 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenDescription'name :: [CChar]
{-# LINE 615 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenDescription'mixers :: CInt
{-# LINE 616 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenDescription'encoders :: CInt
{-# LINE 617 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenDescription'outputs :: CInt
{-# LINE 618 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBScreenDescription where
  sizeOf _ = 48
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekArray 32 (plusPtr p 4)
    v2 <- peekByteOff p 36
    v3 <- peekByteOff p 40
    v4 <- peekByteOff p 44
    return $ C'DFBScreenDescription v0 v1 v2 v3 v4
  poke p (C'DFBScreenDescription v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeArray (plusPtr p 4) (take 32 v1)
    pokeByteOff p 36 v2
    pokeByteOff p 40 v3
    pokeByteOff p 44 v4
    return ()

{-# LINE 619 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_INPUT_DEVICE_DESC_NAME_LENGTH = 32
c'DFB_INPUT_DEVICE_DESC_NAME_LENGTH :: (Num a) => a

{-# LINE 621 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBInputDeviceDescription = C'DFBInputDeviceDescription{
{-# LINE 623 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBInputDeviceDescription'type :: C'DFBInputDeviceTypeFlags
{-# LINE 624 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceDescription'caps :: C'DFBInputDeviceCapabilities
{-# LINE 625 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceDescription'min_keycode :: CInt
{-# LINE 626 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceDescription'max_keycode :: CInt
{-# LINE 627 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceDescription'max_axis :: C'DFBInputDeviceAxisIdentifier
{-# LINE 628 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceDescription'max_button :: C'DFBInputDeviceButtonIdentifier
{-# LINE 629 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceDescription'name :: [CChar]
{-# LINE 630 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceDescription'vendor :: [CChar]
{-# LINE 631 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBInputDeviceDescription where
  sizeOf _ = 96
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekArray 32 (plusPtr p 24)
    v7 <- peekArray 40 (plusPtr p 56)
    return $ C'DFBInputDeviceDescription v0 v1 v2 v3 v4 v5 v6 v7
  poke p (C'DFBInputDeviceDescription v0 v1 v2 v3 v4 v5 v6 v7) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeArray (plusPtr p 24) (take 32 v6)
    pokeArray (plusPtr p 56) (take 40 v7)
    return ()

{-# LINE 632 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceAxisInfoFlags = Word32

{-# LINE 634 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIAIF_NONE = 0
c'DIAIF_NONE :: (Num a) => a

{-# LINE 636 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIAIF_ABS_MIN = 1
c'DIAIF_ABS_MIN :: (Num a) => a

{-# LINE 637 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIAIF_ABS_MAX = 2
c'DIAIF_ABS_MAX :: (Num a) => a

{-# LINE 638 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIAIF_ALL = 3
c'DIAIF_ALL :: (Num a) => a

{-# LINE 639 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBInputDeviceAxisInfo = C'DFBInputDeviceAxisInfo{
{-# LINE 641 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBInputDeviceAxisInfo'flags :: C'DFBInputDeviceAxisInfoFlags
{-# LINE 642 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceAxisInfo'abs_min :: CInt
{-# LINE 643 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceAxisInfo'abs_max :: CInt
{-# LINE 644 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBInputDeviceAxisInfo where
  sizeOf _ = 12
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    return $ C'DFBInputDeviceAxisInfo v0 v1 v2
  poke p (C'DFBInputDeviceAxisInfo v0 v1 v2) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    return ()

{-# LINE 645 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_GRAPHICS_DRIVER_INFO_NAME_LENGTH = 40
c'DFB_GRAPHICS_DRIVER_INFO_NAME_LENGTH :: (Num a) => a

{-# LINE 647 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBGraphicsDriverInfo = C'DFBGraphicsDriverInfo{
{-# LINE 649 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBGraphicsDriverInfo'major :: CInt
{-# LINE 650 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGraphicsDriverInfo'minor :: CInt
{-# LINE 651 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGraphicsDriverInfo'name :: [CChar]
{-# LINE 652 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGraphicsDriverInfo'vendor :: [CChar]
{-# LINE 653 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBGraphicsDriverInfo where
  sizeOf _ = 108
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekArray 40 (plusPtr p 8)
    v3 <- peekArray 60 (plusPtr p 48)
    return $ C'DFBGraphicsDriverInfo v0 v1 v2 v3
  poke p (C'DFBGraphicsDriverInfo v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeArray (plusPtr p 8) (take 40 v2)
    pokeArray (plusPtr p 48) (take 60 v3)
    return ()

{-# LINE 654 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_GRAPHICS_DEVICE_DESC_NAME_LENGTH = 48
c'DFB_GRAPHICS_DEVICE_DESC_NAME_LENGTH :: (Num a) => a

{-# LINE 656 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBGraphicsDeviceDescription = C'DFBGraphicsDeviceDescription{
{-# LINE 658 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBGraphicsDeviceDescription'acceleration_mask :: C'DFBAccelerationMask
{-# LINE 659 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGraphicsDeviceDescription'blitting_flags :: C'DFBSurfaceBlittingFlags
{-# LINE 660 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGraphicsDeviceDescription'drawing_flags :: C'DFBSurfaceDrawingFlags
{-# LINE 661 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGraphicsDeviceDescription'video_memory :: CUInt
{-# LINE 662 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGraphicsDeviceDescription'name :: [CChar]
{-# LINE 663 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGraphicsDeviceDescription'vendor :: [CChar]
{-# LINE 664 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGraphicsDeviceDescription'driver :: C'DFBGraphicsDriverInfo
{-# LINE 665 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBGraphicsDeviceDescription where
  sizeOf _ = 236
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekArray 48 (plusPtr p 16)
    v5 <- peekArray 64 (plusPtr p 64)
    v6 <- peekByteOff p 128
    return $ C'DFBGraphicsDeviceDescription v0 v1 v2 v3 v4 v5 v6
  poke p (C'DFBGraphicsDeviceDescription v0 v1 v2 v3 v4 v5 v6) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeArray (plusPtr p 16) (take 48 v4)
    pokeArray (plusPtr p 64) (take 64 v5)
    pokeByteOff p 128 v6
    return ()

{-# LINE 666 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBWindowDescription = C'DFBWindowDescription{
{-# LINE 668 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBWindowDescription'flags :: C'DFBWindowDescriptionFlags
{-# LINE 669 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'caps :: C'DFBWindowCapabilities
{-# LINE 670 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'width :: CInt
{-# LINE 671 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'height :: CInt
{-# LINE 672 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'pixelformat :: C'DFBSurfacePixelFormat
{-# LINE 673 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'posx :: CInt
{-# LINE 674 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'posy :: CInt
{-# LINE 675 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'surface_caps :: C'DFBSurfaceCapabilities
{-# LINE 676 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'parent_id :: C'DFBWindowID
{-# LINE 677 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'options :: C'DFBWindowOptions
{-# LINE 678 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'stacking :: C'DFBWindowStackingClass
{-# LINE 679 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowDescription'resource_id :: CULong
{-# LINE 680 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 683 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBWindowDescription where
  sizeOf _ = 48
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    v8 <- peekByteOff p 32
    v9 <- peekByteOff p 36
    v10 <- peekByteOff p 40
    v11 <- peekByteOff p 44
    return $ C'DFBWindowDescription v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11
  poke p (C'DFBWindowDescription v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    pokeByteOff p 32 v8
    pokeByteOff p 36 v9
    pokeByteOff p 40 v10
    pokeByteOff p 44 v11
    return ()

{-# LINE 684 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBDataBufferDescription = C'DFBDataBufferDescription{
{-# LINE 686 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBDataBufferDescription'flags :: C'DFBDataBufferDescriptionFlags
{-# LINE 687 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDataBufferDescription'file :: CString
{-# LINE 688 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDataBufferDescription'memory'data :: Ptr ()
{-# LINE 689 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDataBufferDescription'memory'length :: CUInt
{-# LINE 690 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBDataBufferDescription where
  sizeOf _ = 16
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    return $ C'DFBDataBufferDescription v0 v1 v2 v3
  poke p (C'DFBDataBufferDescription v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    return ()

{-# LINE 691 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBEnumerationResult = Word32

{-# LINE 693 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFENUM_OK = 0
c'DFENUM_OK :: (Num a) => a

{-# LINE 695 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFENUM_CANCEL = 1
c'DFENUM_CANCEL :: (Num a) => a

{-# LINE 696 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBVideoModeCallback = FunPtr (CInt -> CInt -> CInt -> Ptr () -> IO C'DFBEnumerationResult)
foreign import ccall "wrapper" mk'DFBVideoModeCallback
  :: (CInt -> CInt -> CInt -> Ptr () -> IO C'DFBEnumerationResult) -> IO C'DFBVideoModeCallback

{-# LINE 699 "src/Bindings/DirectFB/Types.hsc" #-}
-- callback DFBScreenCallback , <DFBScreenID> -> \
--   <DFBScreenDescription> -> Ptr () -> \
--   IO <DFBEnumerationResult>
-- callback DFBDisplayLayerCallback , <DFBDisplayLayerID> -> \
--   <DFBDisplayLayerDescription> -> Ptr () -> \
--   IO <DFBEnumerationResult>
-- callback DFBInputDeviceCallback , <DFBInputDeviceID> -> \
--   <DFBInputDeviceDescription> -> Ptr () -> \
--   IO <DFBEnumerationResult>
type C'DFBGetDataCallback = FunPtr (Ptr () -> CUInt -> Ptr () -> IO CInt)
foreign import ccall "wrapper" mk'DFBGetDataCallback
  :: (Ptr () -> CUInt -> Ptr () -> IO CInt) -> IO C'DFBGetDataCallback

{-# LINE 709 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBVideoProviderCapabilities = Word32

{-# LINE 711 "src/Bindings/DirectFB/Types.hsc" #-}

c'DVCAPS_BASIC = 0
c'DVCAPS_BASIC :: (Num a) => a

{-# LINE 713 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_SEEK = 1
c'DVCAPS_SEEK :: (Num a) => a

{-# LINE 714 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_SCALE = 2
c'DVCAPS_SCALE :: (Num a) => a

{-# LINE 715 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_INTERLACED = 4
c'DVCAPS_INTERLACED :: (Num a) => a

{-# LINE 716 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_SPEED = 8
c'DVCAPS_SPEED :: (Num a) => a

{-# LINE 717 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_BRIGHTNESS = 16
c'DVCAPS_BRIGHTNESS :: (Num a) => a

{-# LINE 718 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_CONTRAST = 32
c'DVCAPS_CONTRAST :: (Num a) => a

{-# LINE 719 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_HUE = 64
c'DVCAPS_HUE :: (Num a) => a

{-# LINE 720 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_SATURATION = 128
c'DVCAPS_SATURATION :: (Num a) => a

{-# LINE 721 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_INTERACTIVE = 256
c'DVCAPS_INTERACTIVE :: (Num a) => a

{-# LINE 722 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_VOLUME = 512
c'DVCAPS_VOLUME :: (Num a) => a

{-# LINE 723 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_EVENT = 1024
c'DVCAPS_EVENT :: (Num a) => a

{-# LINE 724 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_ATTRIBUTES = 2048
c'DVCAPS_ATTRIBUTES :: (Num a) => a

{-# LINE 725 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVCAPS_AUDIO_SEL = 4096
c'DVCAPS_AUDIO_SEL :: (Num a) => a

{-# LINE 726 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBVideoProviderStatus = Word32

{-# LINE 728 "src/Bindings/DirectFB/Types.hsc" #-}

c'DVSTATE_UNKNOWN = 0
c'DVSTATE_UNKNOWN :: (Num a) => a

{-# LINE 730 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVSTATE_PLAY = 1
c'DVSTATE_PLAY :: (Num a) => a

{-# LINE 731 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVSTATE_STOP = 2
c'DVSTATE_STOP :: (Num a) => a

{-# LINE 732 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVSTATE_FINISHED = 3
c'DVSTATE_FINISHED :: (Num a) => a

{-# LINE 733 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVSTATE_BUFFERING = 4
c'DVSTATE_BUFFERING :: (Num a) => a

{-# LINE 734 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBVideoProviderPlaybackFlags = Word32

{-# LINE 736 "src/Bindings/DirectFB/Types.hsc" #-}

c'DVPLAY_NOFX = 0
c'DVPLAY_NOFX :: (Num a) => a

{-# LINE 738 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPLAY_REWIND = 1
c'DVPLAY_REWIND :: (Num a) => a

{-# LINE 739 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPLAY_LOOPING = 2
c'DVPLAY_LOOPING :: (Num a) => a

{-# LINE 740 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBVideoProviderAudioUnits = Word32

{-# LINE 742 "src/Bindings/DirectFB/Types.hsc" #-}

c'DVAUDIOUNIT_NONE = 0
c'DVAUDIOUNIT_NONE :: (Num a) => a

{-# LINE 744 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVAUDIOUNIT_ONE = 1
c'DVAUDIOUNIT_ONE :: (Num a) => a

{-# LINE 745 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVAUDIOUNIT_TWO = 2
c'DVAUDIOUNIT_TWO :: (Num a) => a

{-# LINE 746 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVAUDIOUNIT_THREE = 4
c'DVAUDIOUNIT_THREE :: (Num a) => a

{-# LINE 747 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVAUDIOUNIT_FOUR = 8
c'DVAUDIOUNIT_FOUR :: (Num a) => a

{-# LINE 748 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVAUDIOUNIT_ALL = 15
c'DVAUDIOUNIT_ALL :: (Num a) => a

{-# LINE 749 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBColorAdjustmentFlags = Word32

{-# LINE 751 "src/Bindings/DirectFB/Types.hsc" #-}

c'DCAF_NONE = 0
c'DCAF_NONE :: (Num a) => a

{-# LINE 753 "src/Bindings/DirectFB/Types.hsc" #-}
c'DCAF_BRIGHTNESS = 1
c'DCAF_BRIGHTNESS :: (Num a) => a

{-# LINE 754 "src/Bindings/DirectFB/Types.hsc" #-}
c'DCAF_CONTRAST = 2
c'DCAF_CONTRAST :: (Num a) => a

{-# LINE 755 "src/Bindings/DirectFB/Types.hsc" #-}
c'DCAF_HUE = 4
c'DCAF_HUE :: (Num a) => a

{-# LINE 756 "src/Bindings/DirectFB/Types.hsc" #-}
c'DCAF_SATURATION = 8
c'DCAF_SATURATION :: (Num a) => a

{-# LINE 757 "src/Bindings/DirectFB/Types.hsc" #-}
c'DCAF_ALL = 15
c'DCAF_ALL :: (Num a) => a

{-# LINE 758 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBColorAdjustment = C'DFBColorAdjustment{
{-# LINE 760 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBColorAdjustment'flags :: C'DFBColorAdjustmentFlags
{-# LINE 761 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColorAdjustment'brightness :: Word16
{-# LINE 762 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColorAdjustment'contrast :: Word16
{-# LINE 763 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColorAdjustment'hue :: Word16
{-# LINE 764 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBColorAdjustment'saturation :: Word16
{-# LINE 765 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBColorAdjustment where
  sizeOf _ = 12
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 6
    v3 <- peekByteOff p 8
    v4 <- peekByteOff p 10
    return $ C'DFBColorAdjustment v0 v1 v2 v3 v4
  poke p (C'DFBColorAdjustment v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 6 v2
    pokeByteOff p 8 v3
    pokeByteOff p 10 v4
    return ()

{-# LINE 766 "src/Bindings/DirectFB/Types.hsc" #-}

c'DLID_PRIMARY = 0
c'DLID_PRIMARY :: (Num a) => a

{-# LINE 768 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLSID_SURFACE = 0
c'DLSID_SURFACE :: (Num a) => a

{-# LINE 769 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSCID_PRIMARY = 0
c'DSCID_PRIMARY :: (Num a) => a

{-# LINE 770 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIDID_KEYBOARD = 0
c'DIDID_KEYBOARD :: (Num a) => a

{-# LINE 771 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIDID_JOYSTICK = 2
c'DIDID_JOYSTICK :: (Num a) => a

{-# LINE 772 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIDID_ANY = 16
c'DIDID_ANY :: (Num a) => a

{-# LINE 773 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBDisplayLayerCooperativeLevel = Word32

{-# LINE 775 "src/Bindings/DirectFB/Types.hsc" #-}

c'DLSCL_SHARED = 0
c'DLSCL_SHARED :: (Num a) => a

{-# LINE 777 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLSCL_EXCLUSIVE = 1
c'DLSCL_EXCLUSIVE :: (Num a) => a

{-# LINE 778 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLSCL_ADMINISTRATIVE = 2
c'DLSCL_ADMINISTRATIVE :: (Num a) => a

{-# LINE 779 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBDisplayLayerBackgroundMode = Word32

{-# LINE 781 "src/Bindings/DirectFB/Types.hsc" #-}

c'DLBM_DONTCARE = 0
c'DLBM_DONTCARE :: (Num a) => a

{-# LINE 783 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLBM_COLOR = 1
c'DLBM_COLOR :: (Num a) => a

{-# LINE 784 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLBM_IMAGE = 2
c'DLBM_IMAGE :: (Num a) => a

{-# LINE 785 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLBM_TILE = 3
c'DLBM_TILE :: (Num a) => a

{-# LINE 786 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBDisplayLayerConfigFlags = Word32

{-# LINE 788 "src/Bindings/DirectFB/Types.hsc" #-}

c'DLCONF_NONE = 0
c'DLCONF_NONE :: (Num a) => a

{-# LINE 790 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCONF_WIDTH = 1
c'DLCONF_WIDTH :: (Num a) => a

{-# LINE 791 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCONF_HEIGHT = 2
c'DLCONF_HEIGHT :: (Num a) => a

{-# LINE 792 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCONF_PIXELFORMAT = 4
c'DLCONF_PIXELFORMAT :: (Num a) => a

{-# LINE 793 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCONF_BUFFERMODE = 8
c'DLCONF_BUFFERMODE :: (Num a) => a

{-# LINE 794 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCONF_OPTIONS = 16
c'DLCONF_OPTIONS :: (Num a) => a

{-# LINE 795 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCONF_SOURCE = 32
c'DLCONF_SOURCE :: (Num a) => a

{-# LINE 796 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCONF_SURFACE_CAPS = 64
c'DLCONF_SURFACE_CAPS :: (Num a) => a

{-# LINE 797 "src/Bindings/DirectFB/Types.hsc" #-}
c'DLCONF_ALL = 127
c'DLCONF_ALL :: (Num a) => a

{-# LINE 798 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBDisplayLayerConfig = C'DFBDisplayLayerConfig{
{-# LINE 800 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBDisplayLayerConfig'flags :: C'DFBDisplayLayerConfigFlags
{-# LINE 801 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerConfig'width :: CInt
{-# LINE 802 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerConfig'height :: CInt
{-# LINE 803 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerConfig'pixelformat :: C'DFBSurfacePixelFormat
{-# LINE 804 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerConfig'buffermode :: C'DFBDisplayLayerBufferMode
{-# LINE 805 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerConfig'options :: C'DFBDisplayLayerOptions
{-# LINE 806 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerConfig'source :: C'DFBDisplayLayerSourceID
{-# LINE 807 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBDisplayLayerConfig'surface_caps :: C'DFBSurfaceCapabilities
{-# LINE 808 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBDisplayLayerConfig where
  sizeOf _ = 32
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    return $ C'DFBDisplayLayerConfig v0 v1 v2 v3 v4 v5 v6 v7
  poke p (C'DFBDisplayLayerConfig v0 v1 v2 v3 v4 v5 v6 v7) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    return ()

{-# LINE 809 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenPowerMode = Word32

{-# LINE 811 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSPM_ON = 0
c'DSPM_ON :: (Num a) => a

{-# LINE 813 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPM_STANDBY = 1
c'DSPM_STANDBY :: (Num a) => a

{-# LINE 814 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPM_SUSPEND = 2
c'DSPM_SUSPEND :: (Num a) => a

{-# LINE 815 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPM_OFF = 3
c'DSPM_OFF :: (Num a) => a

{-# LINE 816 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenMixerCapabilities = Word32

{-# LINE 818 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSMCAPS_NONE = 0
c'DSMCAPS_NONE :: (Num a) => a

{-# LINE 820 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMCAPS_FULL = 1
c'DSMCAPS_FULL :: (Num a) => a

{-# LINE 821 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMCAPS_SUB_LEVEL = 2
c'DSMCAPS_SUB_LEVEL :: (Num a) => a

{-# LINE 822 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMCAPS_SUB_LAYERS = 4
c'DSMCAPS_SUB_LAYERS :: (Num a) => a

{-# LINE 823 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMCAPS_BACKGROUND = 8
c'DSMCAPS_BACKGROUND :: (Num a) => a

{-# LINE 824 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_SCREEN_MIXER_DESC_NAME_LENGTH = 24
c'DFB_SCREEN_MIXER_DESC_NAME_LENGTH :: (Num a) => a

{-# LINE 826 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBScreenMixerDescription = C'DFBScreenMixerDescription{
{-# LINE 828 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBScreenMixerDescription'caps :: C'DFBScreenMixerCapabilities
{-# LINE 829 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenMixerDescription'layers :: C'DFBDisplayLayerIDs
{-# LINE 830 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenMixerDescription'sub_num :: CInt
{-# LINE 831 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenMixerDescription'sub_layers :: C'DFBDisplayLayerIDs
{-# LINE 832 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenMixerDescription'name :: [CChar]
{-# LINE 833 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBScreenMixerDescription where
  sizeOf _ = 40
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekArray 24 (plusPtr p 16)
    return $ C'DFBScreenMixerDescription v0 v1 v2 v3 v4
  poke p (C'DFBScreenMixerDescription v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeArray (plusPtr p 16) (take 24 v4)
    return ()

{-# LINE 834 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenMixerConfigFlags = Word32

{-# LINE 836 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSMCONF_NONE = 0
c'DSMCONF_NONE :: (Num a) => a

{-# LINE 838 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMCONF_TREE = 1
c'DSMCONF_TREE :: (Num a) => a

{-# LINE 839 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMCONF_LEVEL = 2
c'DSMCONF_LEVEL :: (Num a) => a

{-# LINE 840 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMCONF_LAYERS = 4
c'DSMCONF_LAYERS :: (Num a) => a

{-# LINE 841 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMCONF_BACKGROUND = 16
c'DSMCONF_BACKGROUND :: (Num a) => a

{-# LINE 842 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMCONF_ALL = 23
c'DSMCONF_ALL :: (Num a) => a

{-# LINE 843 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenMixerTree = Word32

{-# LINE 845 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSMT_UNKNOWN = 0
c'DSMT_UNKNOWN :: (Num a) => a

{-# LINE 847 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMT_FULL = 1
c'DSMT_FULL :: (Num a) => a

{-# LINE 848 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMT_SUB_LEVEL = 2
c'DSMT_SUB_LEVEL :: (Num a) => a

{-# LINE 849 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMT_SUB_LAYERS = 3
c'DSMT_SUB_LAYERS :: (Num a) => a

{-# LINE 850 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBScreenMixerConfig = C'DFBScreenMixerConfig{
{-# LINE 852 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBScreenMixerConfig'flags :: C'DFBScreenMixerConfigFlags
{-# LINE 853 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenMixerConfig'tree :: C'DFBScreenMixerTree
{-# LINE 854 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenMixerConfig'level :: CInt
{-# LINE 855 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenMixerConfig'layers :: C'DFBDisplayLayerIDs
{-# LINE 856 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenMixerConfig'background :: C'DFBColor
{-# LINE 857 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBScreenMixerConfig where
  sizeOf _ = 20
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    return $ C'DFBScreenMixerConfig v0 v1 v2 v3 v4
  poke p (C'DFBScreenMixerConfig v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    return ()

{-# LINE 858 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenOutputCapabilities = Word32

{-# LINE 860 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSOCAPS_NONE = 0
c'DSOCAPS_NONE :: (Num a) => a

{-# LINE 862 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCAPS_CONNECTORS = 1
c'DSOCAPS_CONNECTORS :: (Num a) => a

{-# LINE 863 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCAPS_ENCODER_SEL = 16
c'DSOCAPS_ENCODER_SEL :: (Num a) => a

{-# LINE 864 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCAPS_SIGNAL_SEL = 32
c'DSOCAPS_SIGNAL_SEL :: (Num a) => a

{-# LINE 865 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCAPS_CONNECTOR_SEL = 64
c'DSOCAPS_CONNECTOR_SEL :: (Num a) => a

{-# LINE 866 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCAPS_SLOW_BLANKING = 128
c'DSOCAPS_SLOW_BLANKING :: (Num a) => a

{-# LINE 867 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCAPS_RESOLUTION = 256
c'DSOCAPS_RESOLUTION :: (Num a) => a

{-# LINE 868 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCAPS_ALL = 497
c'DSOCAPS_ALL :: (Num a) => a

{-# LINE 869 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenOutputConnectors = Word32

{-# LINE 871 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSOC_UNKNOWN = 0
c'DSOC_UNKNOWN :: (Num a) => a

{-# LINE 873 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOC_VGA = 1
c'DSOC_VGA :: (Num a) => a

{-# LINE 874 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOC_SCART = 2
c'DSOC_SCART :: (Num a) => a

{-# LINE 875 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOC_YC = 4
c'DSOC_YC :: (Num a) => a

{-# LINE 876 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOC_CVBS = 8
c'DSOC_CVBS :: (Num a) => a

{-# LINE 877 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOC_SCART2 = 16
c'DSOC_SCART2 :: (Num a) => a

{-# LINE 878 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOC_COMPONENT = 32
c'DSOC_COMPONENT :: (Num a) => a

{-# LINE 879 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOC_HDMI = 64
c'DSOC_HDMI :: (Num a) => a

{-# LINE 880 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenOutputSignals = Word32

{-# LINE 882 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSOS_NONE = 0
c'DSOS_NONE :: (Num a) => a

{-# LINE 884 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOS_VGA = 1
c'DSOS_VGA :: (Num a) => a

{-# LINE 885 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOS_YC = 2
c'DSOS_YC :: (Num a) => a

{-# LINE 886 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOS_CVBS = 4
c'DSOS_CVBS :: (Num a) => a

{-# LINE 887 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOS_RGB = 8
c'DSOS_RGB :: (Num a) => a

{-# LINE 888 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOS_YCBCR = 16
c'DSOS_YCBCR :: (Num a) => a

{-# LINE 889 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOS_HDMI = 32
c'DSOS_HDMI :: (Num a) => a

{-# LINE 890 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOS_656 = 64
c'DSOS_656 :: (Num a) => a

{-# LINE 891 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenOutputSlowBlankingSignals = Word32

{-# LINE 893 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSOSB_OFF = 0
c'DSOSB_OFF :: (Num a) => a

{-# LINE 895 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOSB_16x9 = 1
c'DSOSB_16x9 :: (Num a) => a

{-# LINE 896 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOSB_4x3 = 2
c'DSOSB_4x3 :: (Num a) => a

{-# LINE 897 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOSB_FOLLOW = 4
c'DSOSB_FOLLOW :: (Num a) => a

{-# LINE 898 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOSB_MONITOR = 8
c'DSOSB_MONITOR :: (Num a) => a

{-# LINE 899 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenOutputResolution = Word32

{-# LINE 901 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSOR_UNKNOWN = 0
c'DSOR_UNKNOWN :: (Num a) => a

{-# LINE 903 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_640_480 = 1
c'DSOR_640_480 :: (Num a) => a

{-# LINE 904 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_720_480 = 2
c'DSOR_720_480 :: (Num a) => a

{-# LINE 905 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_720_576 = 4
c'DSOR_720_576 :: (Num a) => a

{-# LINE 906 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_800_600 = 8
c'DSOR_800_600 :: (Num a) => a

{-# LINE 907 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_1024_768 = 16
c'DSOR_1024_768 :: (Num a) => a

{-# LINE 908 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_1152_864 = 32
c'DSOR_1152_864 :: (Num a) => a

{-# LINE 909 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_1280_720 = 64
c'DSOR_1280_720 :: (Num a) => a

{-# LINE 910 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_1280_768 = 128
c'DSOR_1280_768 :: (Num a) => a

{-# LINE 911 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_1280_960 = 256
c'DSOR_1280_960 :: (Num a) => a

{-# LINE 912 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_1280_1024 = 512
c'DSOR_1280_1024 :: (Num a) => a

{-# LINE 913 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_1400_1050 = 1024
c'DSOR_1400_1050 :: (Num a) => a

{-# LINE 914 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_1600_1200 = 2048
c'DSOR_1600_1200 :: (Num a) => a

{-# LINE 915 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_1920_1080 = 4096
c'DSOR_1920_1080 :: (Num a) => a

{-# LINE 916 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOR_ALL = 8191
c'DSOR_ALL :: (Num a) => a

{-# LINE 917 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_SCREEN_OUTPUT_DESC_NAME_LENGTH = 24
c'DFB_SCREEN_OUTPUT_DESC_NAME_LENGTH :: (Num a) => a

{-# LINE 919 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBScreenOutputDescription = C'DFBScreenOutputDescription{
{-# LINE 921 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBScreenOutputDescription'caps :: C'DFBScreenOutputCapabilities
{-# LINE 922 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenOutputDescription'all_connectors :: C'DFBScreenOutputConnectors
{-# LINE 923 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenOutputDescription'all_signals :: C'DFBScreenOutputSignals
{-# LINE 924 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenOutputDescription'all_resolutions :: C'DFBScreenOutputResolution
{-# LINE 925 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenOutputDescription'name :: [CChar]
{-# LINE 926 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBScreenOutputDescription where
  sizeOf _ = 40
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekArray 24 (plusPtr p 16)
    return $ C'DFBScreenOutputDescription v0 v1 v2 v3 v4
  poke p (C'DFBScreenOutputDescription v0 v1 v2 v3 v4) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeArray (plusPtr p 16) (take 24 v4)
    return ()

{-# LINE 927 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenOutputConfigFlags = Word32

{-# LINE 929 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSOCONF_NONE = 0
c'DSOCONF_NONE :: (Num a) => a

{-# LINE 931 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCONF_ENCODER = 1
c'DSOCONF_ENCODER :: (Num a) => a

{-# LINE 932 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCONF_SIGNALS = 2
c'DSOCONF_SIGNALS :: (Num a) => a

{-# LINE 933 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCONF_CONNECTORS = 4
c'DSOCONF_CONNECTORS :: (Num a) => a

{-# LINE 934 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCONF_SLOW_BLANKING = 8
c'DSOCONF_SLOW_BLANKING :: (Num a) => a

{-# LINE 935 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCONF_RESOLUTION = 16
c'DSOCONF_RESOLUTION :: (Num a) => a

{-# LINE 936 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSOCONF_ALL = 31
c'DSOCONF_ALL :: (Num a) => a

{-# LINE 937 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBScreenOutputConfig = C'DFBScreenOutputConfig{
{-# LINE 939 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBScreenOutputConfig'flags :: C'DFBScreenOutputConfigFlags
{-# LINE 940 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenOutputConfig'encoder :: CInt
{-# LINE 941 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenOutputConfig'out_signals :: C'DFBScreenOutputSignals
{-# LINE 942 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenOutputConfig'out_connectors :: C'DFBScreenOutputConnectors
{-# LINE 943 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenOutputConfig'slow_blanking :: C'DFBScreenOutputSlowBlankingSignals
{-# LINE 944 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenOutputConfig'resolution :: C'DFBScreenOutputResolution
{-# LINE 945 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBScreenOutputConfig where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'DFBScreenOutputConfig v0 v1 v2 v3 v4 v5
  poke p (C'DFBScreenOutputConfig v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 946 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenEncoderCapabilities = Word32

{-# LINE 948 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSECAPS_NONE = 0
c'DSECAPS_NONE :: (Num a) => a

{-# LINE 950 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_TV_STANDARDS = 1
c'DSECAPS_TV_STANDARDS :: (Num a) => a

{-# LINE 951 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_TEST_PICTURE = 2
c'DSECAPS_TEST_PICTURE :: (Num a) => a

{-# LINE 952 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_MIXER_SEL = 4
c'DSECAPS_MIXER_SEL :: (Num a) => a

{-# LINE 953 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_OUT_SIGNALS = 8
c'DSECAPS_OUT_SIGNALS :: (Num a) => a

{-# LINE 954 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_SCANMODE = 16
c'DSECAPS_SCANMODE :: (Num a) => a

{-# LINE 955 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_FREQUENCY = 32
c'DSECAPS_FREQUENCY :: (Num a) => a

{-# LINE 956 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_BRIGHTNESS = 256
c'DSECAPS_BRIGHTNESS :: (Num a) => a

{-# LINE 957 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_CONTRAST = 512
c'DSECAPS_CONTRAST :: (Num a) => a

{-# LINE 958 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_HUE = 1024
c'DSECAPS_HUE :: (Num a) => a

{-# LINE 959 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_SATURATION = 2048
c'DSECAPS_SATURATION :: (Num a) => a

{-# LINE 960 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_CONNECTORS = 4096
c'DSECAPS_CONNECTORS :: (Num a) => a

{-# LINE 961 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_SLOW_BLANKING = 8192
c'DSECAPS_SLOW_BLANKING :: (Num a) => a

{-# LINE 962 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_RESOLUTION = 16384
c'DSECAPS_RESOLUTION :: (Num a) => a

{-# LINE 963 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECAPS_ALL = 32575
c'DSECAPS_ALL :: (Num a) => a

{-# LINE 964 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenEncoderType = Word32

{-# LINE 966 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSET_UNKNOWN = 0
c'DSET_UNKNOWN :: (Num a) => a

{-# LINE 968 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSET_CRTC = 1
c'DSET_CRTC :: (Num a) => a

{-# LINE 969 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSET_TV = 2
c'DSET_TV :: (Num a) => a

{-# LINE 970 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSET_DIGITAL = 4
c'DSET_DIGITAL :: (Num a) => a

{-# LINE 971 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenEncoderTVStandards = Word32

{-# LINE 973 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSETV_UNKNOWN = 0
c'DSETV_UNKNOWN :: (Num a) => a

{-# LINE 975 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_PAL = 1
c'DSETV_PAL :: (Num a) => a

{-# LINE 976 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_NTSC = 2
c'DSETV_NTSC :: (Num a) => a

{-# LINE 977 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_SECAM = 4
c'DSETV_SECAM :: (Num a) => a

{-# LINE 978 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_PAL_60 = 8
c'DSETV_PAL_60 :: (Num a) => a

{-# LINE 979 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_PAL_BG = 16
c'DSETV_PAL_BG :: (Num a) => a

{-# LINE 980 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_PAL_I = 32
c'DSETV_PAL_I :: (Num a) => a

{-# LINE 981 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_PAL_M = 64
c'DSETV_PAL_M :: (Num a) => a

{-# LINE 982 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_PAL_N = 128
c'DSETV_PAL_N :: (Num a) => a

{-# LINE 983 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_PAL_NC = 256
c'DSETV_PAL_NC :: (Num a) => a

{-# LINE 984 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_NTSC_M_JPN = 512
c'DSETV_NTSC_M_JPN :: (Num a) => a

{-# LINE 985 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 988 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_DIGITAL = 1024
c'DSETV_DIGITAL :: (Num a) => a

{-# LINE 989 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETV_ALL = 2047
c'DSETV_ALL :: (Num a) => a

{-# LINE 990 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenEncoderScanMode = Word32

{-# LINE 992 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSESM_UNKNOWN = 0
c'DSESM_UNKNOWN :: (Num a) => a

{-# LINE 994 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSESM_INTERLACED = 1
c'DSESM_INTERLACED :: (Num a) => a

{-# LINE 995 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSESM_PROGRESSIVE = 2
c'DSESM_PROGRESSIVE :: (Num a) => a

{-# LINE 996 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenEncoderFrequency = Word32

{-# LINE 998 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSEF_UNKNOWN = 0
c'DSEF_UNKNOWN :: (Num a) => a

{-# LINE 1000 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSEF_25HZ = 1
c'DSEF_25HZ :: (Num a) => a

{-# LINE 1001 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSEF_29_97HZ = 2
c'DSEF_29_97HZ :: (Num a) => a

{-# LINE 1002 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSEF_50HZ = 4
c'DSEF_50HZ :: (Num a) => a

{-# LINE 1003 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSEF_59_94HZ = 8
c'DSEF_59_94HZ :: (Num a) => a

{-# LINE 1004 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSEF_60HZ = 16
c'DSEF_60HZ :: (Num a) => a

{-# LINE 1005 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSEF_75HZ = 32
c'DSEF_75HZ :: (Num a) => a

{-# LINE 1006 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 1011 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_SCREEN_ENCODER_DESC_NAME_LENGTH = 24
c'DFB_SCREEN_ENCODER_DESC_NAME_LENGTH :: (Num a) => a

{-# LINE 1013 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBScreenEncoderDescription = C'DFBScreenEncoderDescription{
{-# LINE 1015 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBScreenEncoderDescription'caps :: C'DFBScreenEncoderCapabilities
{-# LINE 1016 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderDescription'type :: C'DFBScreenEncoderType
{-# LINE 1017 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderDescription'tv_standards :: C'DFBScreenEncoderTVStandards
{-# LINE 1018 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderDescription'out_signals :: C'DFBScreenOutputSignals
{-# LINE 1019 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderDescription'all_connectors :: C'DFBScreenOutputConnectors
{-# LINE 1020 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderDescription'all_resolutions :: C'DFBScreenOutputResolution
{-# LINE 1021 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderDescription'name :: [CChar]
{-# LINE 1022 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBScreenEncoderDescription where
  sizeOf _ = 48
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekArray 24 (plusPtr p 24)
    return $ C'DFBScreenEncoderDescription v0 v1 v2 v3 v4 v5 v6
  poke p (C'DFBScreenEncoderDescription v0 v1 v2 v3 v4 v5 v6) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeArray (plusPtr p 24) (take 24 v6)
    return ()

{-# LINE 1023 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenEncoderConfigFlags = Word32

{-# LINE 1025 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSECONF_NONE = 0
c'DSECONF_NONE :: (Num a) => a

{-# LINE 1027 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_TV_STANDARD = 1
c'DSECONF_TV_STANDARD :: (Num a) => a

{-# LINE 1028 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_TEST_PICTURE = 2
c'DSECONF_TEST_PICTURE :: (Num a) => a

{-# LINE 1029 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_MIXER = 4
c'DSECONF_MIXER :: (Num a) => a

{-# LINE 1030 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_OUT_SIGNALS = 8
c'DSECONF_OUT_SIGNALS :: (Num a) => a

{-# LINE 1031 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_SCANMODE = 16
c'DSECONF_SCANMODE :: (Num a) => a

{-# LINE 1032 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_TEST_COLOR = 32
c'DSECONF_TEST_COLOR :: (Num a) => a

{-# LINE 1033 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_ADJUSTMENT = 64
c'DSECONF_ADJUSTMENT :: (Num a) => a

{-# LINE 1034 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_FREQUENCY = 128
c'DSECONF_FREQUENCY :: (Num a) => a

{-# LINE 1035 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_CONNECTORS = 256
c'DSECONF_CONNECTORS :: (Num a) => a

{-# LINE 1036 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_SLOW_BLANKING = 512
c'DSECONF_SLOW_BLANKING :: (Num a) => a

{-# LINE 1037 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_RESOLUTION = 1024
c'DSECONF_RESOLUTION :: (Num a) => a

{-# LINE 1038 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSECONF_ALL = 2047
c'DSECONF_ALL :: (Num a) => a

{-# LINE 1039 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBScreenEncoderTestPicture = Word32

{-# LINE 1041 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSETP_OFF = 0
c'DSETP_OFF :: (Num a) => a

{-# LINE 1043 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETP_MULTI = 1
c'DSETP_MULTI :: (Num a) => a

{-# LINE 1044 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETP_SINGLE = 2
c'DSETP_SINGLE :: (Num a) => a

{-# LINE 1045 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETP_WHITE = 16
c'DSETP_WHITE :: (Num a) => a

{-# LINE 1046 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETP_YELLOW = 32
c'DSETP_YELLOW :: (Num a) => a

{-# LINE 1047 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETP_CYAN = 48
c'DSETP_CYAN :: (Num a) => a

{-# LINE 1048 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETP_GREEN = 64
c'DSETP_GREEN :: (Num a) => a

{-# LINE 1049 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETP_MAGENTA = 80
c'DSETP_MAGENTA :: (Num a) => a

{-# LINE 1050 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETP_RED = 96
c'DSETP_RED :: (Num a) => a

{-# LINE 1051 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETP_BLUE = 112
c'DSETP_BLUE :: (Num a) => a

{-# LINE 1052 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSETP_BLACK = 128
c'DSETP_BLACK :: (Num a) => a

{-# LINE 1053 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBScreenEncoderConfig = C'DFBScreenEncoderConfig{
{-# LINE 1055 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBScreenEncoderConfig'flags :: C'DFBScreenEncoderConfigFlags
{-# LINE 1056 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'tv_standard :: C'DFBScreenEncoderTVStandards
{-# LINE 1057 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'test_picture :: C'DFBScreenEncoderTestPicture
{-# LINE 1058 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'mixer :: CInt
{-# LINE 1059 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'out_signals :: C'DFBScreenOutputSignals
{-# LINE 1060 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'out_connectors :: C'DFBScreenOutputConnectors
{-# LINE 1061 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'slow_blanking :: C'DFBScreenOutputSlowBlankingSignals
{-# LINE 1062 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'scanmode :: C'DFBScreenEncoderScanMode
{-# LINE 1063 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'test_color :: C'DFBColor
{-# LINE 1064 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'adjustment :: C'DFBColorAdjustment
{-# LINE 1065 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'frequency :: C'DFBScreenEncoderFrequency
{-# LINE 1066 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBScreenEncoderConfig'resolution :: C'DFBScreenOutputResolution
{-# LINE 1067 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBScreenEncoderConfig where
  sizeOf _ = 56
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    v8 <- peekByteOff p 32
    v9 <- peekByteOff p 36
    v10 <- peekByteOff p 48
    v11 <- peekByteOff p 52
    return $ C'DFBScreenEncoderConfig v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11
  poke p (C'DFBScreenEncoderConfig v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    pokeByteOff p 32 v8
    pokeByteOff p 36 v9
    pokeByteOff p 48 v10
    pokeByteOff p 52 v11
    return ()

{-# LINE 1068 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBSurfaceFlipFlags = Word32

{-# LINE 1070 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSFLIP_NONE = 0
c'DSFLIP_NONE :: (Num a) => a

{-# LINE 1072 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSFLIP_WAIT = 1
c'DSFLIP_WAIT :: (Num a) => a

{-# LINE 1073 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSFLIP_BLIT = 2
c'DSFLIP_BLIT :: (Num a) => a

{-# LINE 1074 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSFLIP_ONSYNC = 4
c'DSFLIP_ONSYNC :: (Num a) => a

{-# LINE 1075 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSFLIP_PIPELINE = 8
c'DSFLIP_PIPELINE :: (Num a) => a

{-# LINE 1076 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSFLIP_WAITFORSYNC = 5
c'DSFLIP_WAITFORSYNC :: (Num a) => a

{-# LINE 1077 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBSurfaceTextFlags = Word32

{-# LINE 1079 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSTF_LEFT = 0
c'DSTF_LEFT :: (Num a) => a

{-# LINE 1081 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSTF_CENTER = 1
c'DSTF_CENTER :: (Num a) => a

{-# LINE 1082 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSTF_RIGHT = 2
c'DSTF_RIGHT :: (Num a) => a

{-# LINE 1083 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSTF_TOP = 4
c'DSTF_TOP :: (Num a) => a

{-# LINE 1084 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSTF_BOTTOM = 8
c'DSTF_BOTTOM :: (Num a) => a

{-# LINE 1085 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 1088 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSTF_TOPLEFT = 4
c'DSTF_TOPLEFT :: (Num a) => a

{-# LINE 1089 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSTF_TOPCENTER = 5
c'DSTF_TOPCENTER :: (Num a) => a

{-# LINE 1090 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSTF_TOPRIGHT = 6
c'DSTF_TOPRIGHT :: (Num a) => a

{-# LINE 1091 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSTF_BOTTOMLEFT = 8
c'DSTF_BOTTOMLEFT :: (Num a) => a

{-# LINE 1092 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSTF_BOTTOMCENTER = 9
c'DSTF_BOTTOMCENTER :: (Num a) => a

{-# LINE 1093 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSTF_BOTTOMRIGHT = 10
c'DSTF_BOTTOMRIGHT :: (Num a) => a

{-# LINE 1094 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBSurfaceLockFlags = Word32

{-# LINE 1096 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSLF_READ = 1
c'DSLF_READ :: (Num a) => a

{-# LINE 1098 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSLF_WRITE = 2
c'DSLF_WRITE :: (Num a) => a

{-# LINE 1099 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBSurfacePorterDuffRule = Word32

{-# LINE 1101 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSPD_NONE = 0
c'DSPD_NONE :: (Num a) => a

{-# LINE 1103 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_CLEAR = 1
c'DSPD_CLEAR :: (Num a) => a

{-# LINE 1104 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_SRC = 2
c'DSPD_SRC :: (Num a) => a

{-# LINE 1105 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_SRC_OVER = 3
c'DSPD_SRC_OVER :: (Num a) => a

{-# LINE 1106 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_DST_OVER = 4
c'DSPD_DST_OVER :: (Num a) => a

{-# LINE 1107 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_SRC_IN = 5
c'DSPD_SRC_IN :: (Num a) => a

{-# LINE 1108 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_DST_IN = 6
c'DSPD_DST_IN :: (Num a) => a

{-# LINE 1109 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_SRC_OUT = 7
c'DSPD_SRC_OUT :: (Num a) => a

{-# LINE 1110 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_DST_OUT = 8
c'DSPD_DST_OUT :: (Num a) => a

{-# LINE 1111 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_SRC_ATOP = 9
c'DSPD_SRC_ATOP :: (Num a) => a

{-# LINE 1112 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_DST_ATOP = 10
c'DSPD_DST_ATOP :: (Num a) => a

{-# LINE 1113 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_ADD = 11
c'DSPD_ADD :: (Num a) => a

{-# LINE 1114 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSPD_XOR = 12
c'DSPD_XOR :: (Num a) => a

{-# LINE 1115 "src/Bindings/DirectFB/Types.hsc" #-}

{-# LINE 1118 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBSurfaceBlendFunction = Word32

{-# LINE 1120 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSBF_UNKNOWN = 0
c'DSBF_UNKNOWN :: (Num a) => a

{-# LINE 1122 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_ZERO = 1
c'DSBF_ZERO :: (Num a) => a

{-# LINE 1123 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_ONE = 2
c'DSBF_ONE :: (Num a) => a

{-# LINE 1124 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_SRCCOLOR = 3
c'DSBF_SRCCOLOR :: (Num a) => a

{-# LINE 1125 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_INVSRCCOLOR = 4
c'DSBF_INVSRCCOLOR :: (Num a) => a

{-# LINE 1126 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_SRCALPHA = 5
c'DSBF_SRCALPHA :: (Num a) => a

{-# LINE 1127 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_INVSRCALPHA = 6
c'DSBF_INVSRCALPHA :: (Num a) => a

{-# LINE 1128 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_DESTALPHA = 7
c'DSBF_DESTALPHA :: (Num a) => a

{-# LINE 1129 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_INVDESTALPHA = 8
c'DSBF_INVDESTALPHA :: (Num a) => a

{-# LINE 1130 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_DESTCOLOR = 9
c'DSBF_DESTCOLOR :: (Num a) => a

{-# LINE 1131 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_INVDESTCOLOR = 10
c'DSBF_INVDESTCOLOR :: (Num a) => a

{-# LINE 1132 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSBF_SRCALPHASAT = 11
c'DSBF_SRCALPHASAT :: (Num a) => a

{-# LINE 1133 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBVertex = C'DFBVertex{
{-# LINE 1135 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBVertex'x :: CFloat
{-# LINE 1136 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBVertex'y :: CFloat
{-# LINE 1137 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBVertex'z :: CFloat
{-# LINE 1138 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBVertex'w :: CFloat
{-# LINE 1139 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBVertex's :: CFloat
{-# LINE 1140 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBVertex't :: CFloat
{-# LINE 1141 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBVertex where
  sizeOf _ = 24
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    return $ C'DFBVertex v0 v1 v2 v3 v4 v5
  poke p (C'DFBVertex v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    return ()

{-# LINE 1142 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBTriangleFormation = Word32

{-# LINE 1144 "src/Bindings/DirectFB/Types.hsc" #-}

c'DTTF_LIST = 0
c'DTTF_LIST :: (Num a) => a

{-# LINE 1146 "src/Bindings/DirectFB/Types.hsc" #-}
c'DTTF_STRIP = 1
c'DTTF_STRIP :: (Num a) => a

{-# LINE 1147 "src/Bindings/DirectFB/Types.hsc" #-}
c'DTTF_FAN = 2
c'DTTF_FAN :: (Num a) => a

{-# LINE 1148 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBSurfaceMaskFlags = Word32

{-# LINE 1150 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSMF_NONE = 0
c'DSMF_NONE :: (Num a) => a

{-# LINE 1152 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMF_STENCIL = 1
c'DSMF_STENCIL :: (Num a) => a

{-# LINE 1153 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSMF_ALL = 1
c'DSMF_ALL :: (Num a) => a

{-# LINE 1154 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceKeyState = Word32

{-# LINE 1156 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIKS_UP = 0
c'DIKS_UP :: (Num a) => a

{-# LINE 1158 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DOWN = 1
c'DIKS_DOWN :: (Num a) => a

{-# LINE 1159 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceButtonState = Word32

{-# LINE 1161 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIBS_UP = 0
c'DIBS_UP :: (Num a) => a

{-# LINE 1163 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIBS_DOWN = 1
c'DIBS_DOWN :: (Num a) => a

{-# LINE 1164 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceButtonMask = Word32

{-# LINE 1166 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIBM_LEFT = 1
c'DIBM_LEFT :: (Num a) => a

{-# LINE 1168 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIBM_RIGHT = 2
c'DIBM_RIGHT :: (Num a) => a

{-# LINE 1169 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIBM_MIDDLE = 4
c'DIBM_MIDDLE :: (Num a) => a

{-# LINE 1170 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceModifierMask = Word32

{-# LINE 1172 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIMM_SHIFT = 1
c'DIMM_SHIFT :: (Num a) => a

{-# LINE 1174 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMM_CONTROL = 2
c'DIMM_CONTROL :: (Num a) => a

{-# LINE 1175 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMM_ALT = 4
c'DIMM_ALT :: (Num a) => a

{-# LINE 1176 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMM_ALTGR = 8
c'DIMM_ALTGR :: (Num a) => a

{-# LINE 1177 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMM_META = 16
c'DIMM_META :: (Num a) => a

{-# LINE 1178 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMM_SUPER = 32
c'DIMM_SUPER :: (Num a) => a

{-# LINE 1179 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMM_HYPER = 64
c'DIMM_HYPER :: (Num a) => a

{-# LINE 1180 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBEventClass = Word32

{-# LINE 1182 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFEC_NONE = 0
c'DFEC_NONE :: (Num a) => a

{-# LINE 1184 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFEC_INPUT = 1
c'DFEC_INPUT :: (Num a) => a

{-# LINE 1185 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFEC_WINDOW = 2
c'DFEC_WINDOW :: (Num a) => a

{-# LINE 1186 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFEC_USER = 3
c'DFEC_USER :: (Num a) => a

{-# LINE 1187 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFEC_UNIVERSAL = 4
c'DFEC_UNIVERSAL :: (Num a) => a

{-# LINE 1188 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFEC_VIDEOPROVIDER = 5
c'DFEC_VIDEOPROVIDER :: (Num a) => a

{-# LINE 1189 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputEventType = Word32

{-# LINE 1191 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIET_UNKNOWN = 0
c'DIET_UNKNOWN :: (Num a) => a

{-# LINE 1193 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIET_KEYPRESS = 1
c'DIET_KEYPRESS :: (Num a) => a

{-# LINE 1194 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIET_KEYRELEASE = 2
c'DIET_KEYRELEASE :: (Num a) => a

{-# LINE 1195 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIET_BUTTONPRESS = 3
c'DIET_BUTTONPRESS :: (Num a) => a

{-# LINE 1196 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIET_BUTTONRELEASE = 4
c'DIET_BUTTONRELEASE :: (Num a) => a

{-# LINE 1197 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIET_AXISMOTION = 5
c'DIET_AXISMOTION :: (Num a) => a

{-# LINE 1198 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputEventFlags = Word32

{-# LINE 1200 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIEF_NONE = 0
c'DIEF_NONE :: (Num a) => a

{-# LINE 1202 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_TIMESTAMP = 1
c'DIEF_TIMESTAMP :: (Num a) => a

{-# LINE 1203 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_AXISABS = 2
c'DIEF_AXISABS :: (Num a) => a

{-# LINE 1204 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_AXISREL = 4
c'DIEF_AXISREL :: (Num a) => a

{-# LINE 1205 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_KEYCODE = 8
c'DIEF_KEYCODE :: (Num a) => a

{-# LINE 1206 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_KEYID = 16
c'DIEF_KEYID :: (Num a) => a

{-# LINE 1207 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_KEYSYMBOL = 32
c'DIEF_KEYSYMBOL :: (Num a) => a

{-# LINE 1208 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_MODIFIERS = 64
c'DIEF_MODIFIERS :: (Num a) => a

{-# LINE 1209 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_LOCKS = 128
c'DIEF_LOCKS :: (Num a) => a

{-# LINE 1210 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_BUTTONS = 256
c'DIEF_BUTTONS :: (Num a) => a

{-# LINE 1211 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_GLOBAL = 512
c'DIEF_GLOBAL :: (Num a) => a

{-# LINE 1212 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_REPEAT = 1024
c'DIEF_REPEAT :: (Num a) => a

{-# LINE 1213 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_FOLLOW = 2048
c'DIEF_FOLLOW :: (Num a) => a

{-# LINE 1214 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_MIN = 4096
c'DIEF_MIN :: (Num a) => a

{-# LINE 1215 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIEF_MAX = 8192
c'DIEF_MAX :: (Num a) => a

{-# LINE 1216 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBInputEvent = C'DFBInputEvent{
{-# LINE 1218 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBInputEvent'clazz :: C'DFBEventClass
{-# LINE 1219 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'type :: C'DFBInputEventType
{-# LINE 1220 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'device_id :: C'DFBInputDeviceID
{-# LINE 1221 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'flags :: C'DFBInputEventFlags
{-# LINE 1222 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'timestamp :: C'timeval
{-# LINE 1223 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'key_code :: CInt
{-# LINE 1224 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'key_id :: C'DFBInputDeviceKeyIdentifier
{-# LINE 1225 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'key_symbol :: C'DFBInputDeviceKeySymbol
{-# LINE 1226 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'modifiers :: C'DFBInputDeviceModifierMask
{-# LINE 1227 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'locks :: C'DFBInputDeviceLockState
{-# LINE 1228 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'button :: C'DFBInputDeviceButtonIdentifier
{-# LINE 1229 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'buttons :: C'DFBInputDeviceButtonMask
{-# LINE 1230 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'axis :: C'DFBInputDeviceAxisIdentifier
{-# LINE 1231 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'axisabs :: CInt
{-# LINE 1232 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'axisrel :: CInt
{-# LINE 1233 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'min :: CInt
{-# LINE 1234 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputEvent'max :: CInt
{-# LINE 1235 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBInputEvent where
  sizeOf _ = 72
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 24
    v6 <- peekByteOff p 28
    v7 <- peekByteOff p 32
    v8 <- peekByteOff p 36
    v9 <- peekByteOff p 40
    v10 <- peekByteOff p 44
    v11 <- peekByteOff p 48
    v12 <- peekByteOff p 52
    v13 <- peekByteOff p 56
    v14 <- peekByteOff p 60
    v15 <- peekByteOff p 64
    v16 <- peekByteOff p 68
    return $ C'DFBInputEvent v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14 v15 v16
  poke p (C'DFBInputEvent v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14 v15 v16) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 24 v5
    pokeByteOff p 28 v6
    pokeByteOff p 32 v7
    pokeByteOff p 36 v8
    pokeByteOff p 40 v9
    pokeByteOff p 44 v10
    pokeByteOff p 48 v11
    pokeByteOff p 52 v12
    pokeByteOff p 56 v13
    pokeByteOff p 60 v14
    pokeByteOff p 64 v15
    pokeByteOff p 68 v16
    return ()

{-# LINE 1236 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBWindowEventType = Word32

{-# LINE 1238 "src/Bindings/DirectFB/Types.hsc" #-}

c'DWET_NONE = 0
c'DWET_NONE :: (Num a) => a

{-# LINE 1240 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_POSITION = 1
c'DWET_POSITION :: (Num a) => a

{-# LINE 1241 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_SIZE = 2
c'DWET_SIZE :: (Num a) => a

{-# LINE 1242 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_CLOSE = 4
c'DWET_CLOSE :: (Num a) => a

{-# LINE 1243 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_DESTROYED = 8
c'DWET_DESTROYED :: (Num a) => a

{-# LINE 1244 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_GOTFOCUS = 16
c'DWET_GOTFOCUS :: (Num a) => a

{-# LINE 1245 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_LOSTFOCUS = 32
c'DWET_LOSTFOCUS :: (Num a) => a

{-# LINE 1246 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_KEYDOWN = 256
c'DWET_KEYDOWN :: (Num a) => a

{-# LINE 1247 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_KEYUP = 512
c'DWET_KEYUP :: (Num a) => a

{-# LINE 1248 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_BUTTONDOWN = 65536
c'DWET_BUTTONDOWN :: (Num a) => a

{-# LINE 1249 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_BUTTONUP = 131072
c'DWET_BUTTONUP :: (Num a) => a

{-# LINE 1250 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_MOTION = 262144
c'DWET_MOTION :: (Num a) => a

{-# LINE 1251 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_ENTER = 524288
c'DWET_ENTER :: (Num a) => a

{-# LINE 1252 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_LEAVE = 1048576
c'DWET_LEAVE :: (Num a) => a

{-# LINE 1253 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_WHEEL = 2097152
c'DWET_WHEEL :: (Num a) => a

{-# LINE 1254 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_POSITION_SIZE = 3
c'DWET_POSITION_SIZE :: (Num a) => a

{-# LINE 1255 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWET_ALL = 4129599
c'DWET_ALL :: (Num a) => a

{-# LINE 1256 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBWindowEventFlags = Word32

{-# LINE 1258 "src/Bindings/DirectFB/Types.hsc" #-}

c'DWEF_NONE = 0
c'DWEF_NONE :: (Num a) => a

{-# LINE 1260 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWEF_RETURNED = 1
c'DWEF_RETURNED :: (Num a) => a

{-# LINE 1261 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWEF_ALL = 1
c'DWEF_ALL :: (Num a) => a

{-# LINE 1262 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBVideoProviderEventType = Word32

{-# LINE 1264 "src/Bindings/DirectFB/Types.hsc" #-}

c'DVPET_NONE = 0
c'DVPET_NONE :: (Num a) => a

{-# LINE 1266 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_STARTED = 1
c'DVPET_STARTED :: (Num a) => a

{-# LINE 1267 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_STOPPED = 2
c'DVPET_STOPPED :: (Num a) => a

{-# LINE 1268 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_SPEEDCHANGE = 4
c'DVPET_SPEEDCHANGE :: (Num a) => a

{-# LINE 1269 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_STREAMCHANGE = 8
c'DVPET_STREAMCHANGE :: (Num a) => a

{-# LINE 1270 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_FATALERROR = 16
c'DVPET_FATALERROR :: (Num a) => a

{-# LINE 1271 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_FINISHED = 32
c'DVPET_FINISHED :: (Num a) => a

{-# LINE 1272 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_SURFACECHANGE = 64
c'DVPET_SURFACECHANGE :: (Num a) => a

{-# LINE 1273 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_FRAMEDECODED = 128
c'DVPET_FRAMEDECODED :: (Num a) => a

{-# LINE 1274 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_FRAMEDISPLAYED = 256
c'DVPET_FRAMEDISPLAYED :: (Num a) => a

{-# LINE 1275 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_DATAEXHAUSTED = 512
c'DVPET_DATAEXHAUSTED :: (Num a) => a

{-# LINE 1276 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_VIDEOACTION = 1024
c'DVPET_VIDEOACTION :: (Num a) => a

{-# LINE 1277 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_DATALOW = 2048
c'DVPET_DATALOW :: (Num a) => a

{-# LINE 1278 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_DATAHIGH = 4096
c'DVPET_DATAHIGH :: (Num a) => a

{-# LINE 1279 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_BUFFERTIMELOW = 8192
c'DVPET_BUFFERTIMELOW :: (Num a) => a

{-# LINE 1280 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_BUFFERTIMEHIGH = 16384
c'DVPET_BUFFERTIMEHIGH :: (Num a) => a

{-# LINE 1281 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPET_ALL = 32767
c'DVPET_ALL :: (Num a) => a

{-# LINE 1282 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBWindowEvent = C'DFBWindowEvent{
{-# LINE 1284 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBWindowEvent'clazz :: C'DFBEventClass
{-# LINE 1285 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'type :: C'DFBWindowEventType
{-# LINE 1286 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'flags :: C'DFBWindowEventFlags
{-# LINE 1287 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'window_id :: C'DFBWindowID
{-# LINE 1288 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'x :: CInt
{-# LINE 1289 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'y :: CInt
{-# LINE 1290 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'cx :: CInt
{-# LINE 1291 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'cy :: CInt
{-# LINE 1292 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'step :: CInt
{-# LINE 1293 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'w :: CInt
{-# LINE 1294 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'h :: CInt
{-# LINE 1295 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'key_code :: CInt
{-# LINE 1296 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'key_id :: C'DFBInputDeviceKeyIdentifier
{-# LINE 1297 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'key_symbol :: C'DFBInputDeviceKeySymbol
{-# LINE 1298 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'modifiers :: C'DFBInputDeviceModifierMask
{-# LINE 1299 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'locks :: C'DFBInputDeviceLockState
{-# LINE 1300 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'button :: C'DFBInputDeviceButtonIdentifier
{-# LINE 1301 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'buttons :: C'DFBInputDeviceButtonMask
{-# LINE 1302 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowEvent'timestamp :: C'timeval
{-# LINE 1303 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBWindowEvent where
  sizeOf _ = 80
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    v8 <- peekByteOff p 32
    v9 <- peekByteOff p 36
    v10 <- peekByteOff p 40
    v11 <- peekByteOff p 44
    v12 <- peekByteOff p 48
    v13 <- peekByteOff p 52
    v14 <- peekByteOff p 56
    v15 <- peekByteOff p 60
    v16 <- peekByteOff p 64
    v17 <- peekByteOff p 68
    v18 <- peekByteOff p 72
    return $ C'DFBWindowEvent v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14 v15 v16 v17 v18
  poke p (C'DFBWindowEvent v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14 v15 v16 v17 v18) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    pokeByteOff p 32 v8
    pokeByteOff p 36 v9
    pokeByteOff p 40 v10
    pokeByteOff p 44 v11
    pokeByteOff p 48 v12
    pokeByteOff p 52 v13
    pokeByteOff p 56 v14
    pokeByteOff p 60 v15
    pokeByteOff p 64 v16
    pokeByteOff p 68 v17
    pokeByteOff p 72 v18
    return ()

{-# LINE 1304 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBVideoProviderEventDataSubType = Word32

{-# LINE 1306 "src/Bindings/DirectFB/Types.hsc" #-}

c'DVPEDST_UNKNOWN = 0
c'DVPEDST_UNKNOWN :: (Num a) => a

{-# LINE 1308 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPEDST_AUDIO = 1
c'DVPEDST_AUDIO :: (Num a) => a

{-# LINE 1309 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPEDST_VIDEO = 2
c'DVPEDST_VIDEO :: (Num a) => a

{-# LINE 1310 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPEDST_DATA = 4
c'DVPEDST_DATA :: (Num a) => a

{-# LINE 1311 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVPEDST_ALL = 7
c'DVPEDST_ALL :: (Num a) => a

{-# LINE 1312 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBVideoProviderEvent = C'DFBVideoProviderEvent{
{-# LINE 1314 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBVideoProviderEvent'clazz :: C'DFBEventClass
{-# LINE 1315 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBVideoProviderEvent'type :: C'DFBVideoProviderEventType
{-# LINE 1316 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBVideoProviderEvent'data_type :: C'DFBVideoProviderEventDataSubType
{-# LINE 1317 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBVideoProviderEvent'data :: [CInt]
{-# LINE 1318 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
p'DFBVideoProviderEvent'data p = plusPtr p 12
p'DFBVideoProviderEvent'data :: Ptr (C'DFBVideoProviderEvent) -> Ptr (CInt)
instance Storable C'DFBVideoProviderEvent where
  sizeOf _ = 28
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- return []
    return $ C'DFBVideoProviderEvent v0 v1 v2 v3
  poke p (C'DFBVideoProviderEvent v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeArray (plusPtr p 12) v3
    return ()

{-# LINE 1319 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBUserEvent = C'DFBUserEvent{
{-# LINE 1321 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBUserEvent'clazz :: C'DFBEventClass
{-# LINE 1322 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBUserEvent'type :: CUInt
{-# LINE 1323 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBUserEvent'data :: Ptr ()
{-# LINE 1324 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBUserEvent where
  sizeOf _ = 12
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    return $ C'DFBUserEvent v0 v1 v2
  poke p (C'DFBUserEvent v0 v1 v2) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    return ()

{-# LINE 1325 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBUniversalEvent = C'DFBUniversalEvent{
{-# LINE 1327 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBUniversalEvent'clazz :: C'DFBEventClass
{-# LINE 1328 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBUniversalEvent'size :: CUInt
{-# LINE 1329 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBUniversalEvent where
  sizeOf _ = 8
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    return $ C'DFBUniversalEvent v0 v1
  poke p (C'DFBUniversalEvent v0 v1) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    return ()

{-# LINE 1330 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBEvent = C'DFBEvent{
{-# LINE 1332 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBEvent'clazz :: C'DFBEventClass
{-# LINE 1333 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEvent'input :: C'DFBInputEvent
{-# LINE 1334 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEvent'window :: C'DFBWindowEvent
{-# LINE 1335 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEvent'user :: C'DFBUserEvent
{-# LINE 1336 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEvent'universal :: C'DFBUniversalEvent
{-# LINE 1337 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEvent'videoprovider :: C'DFBVideoProviderEvent
{-# LINE 1338 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBEvent where
  sizeOf _ = 80
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 0
    v2 <- peekByteOff p 0
    v3 <- peekByteOff p 0
    v4 <- peekByteOff p 0
    v5 <- peekByteOff p 0
    return $ C'DFBEvent v0 v1 v2 v3 v4 v5
  poke p (C'DFBEvent v0 v1 v2 v3 v4 v5) = do
    pokeByteOff p 0 v0
    pokeByteOff p 0 v1
    pokeByteOff p 0 v2
    pokeByteOff p 0 v3
    pokeByteOff p 0 v4
    pokeByteOff p 0 v5
    return ()

{-# LINE 1339 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBEventBufferStats = C'DFBEventBufferStats{
{-# LINE 1341 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBEventBufferStats'num_events :: CUInt
{-# LINE 1342 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DFEC_INPUT :: CUInt
{-# LINE 1343 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DFEC_WINDOW :: CUInt
{-# LINE 1344 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DFEC_USER :: CUInt
{-# LINE 1345 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DFEC_UNIVERSAL :: CUInt
{-# LINE 1346 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DFEC_VIDEOPROVIDER :: CUInt
{-# LINE 1347 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DIET_KEYPRESS :: CUInt
{-# LINE 1348 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DIET_KEYRELEASE :: CUInt
{-# LINE 1349 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DIET_BUTTONPRESS :: CUInt
{-# LINE 1350 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DIET_BUTTONRELEASE :: CUInt
{-# LINE 1351 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DIET_AXISMOTION :: CUInt
{-# LINE 1352 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_POSITION :: CUInt
{-# LINE 1353 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_SIZE :: CUInt
{-# LINE 1354 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_CLOSE :: CUInt
{-# LINE 1355 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_DESTROYED :: CUInt
{-# LINE 1356 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_GOTFOCUS :: CUInt
{-# LINE 1357 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_LOSTFOCUS :: CUInt
{-# LINE 1358 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_KEYDOWN :: CUInt
{-# LINE 1359 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_KEYUP :: CUInt
{-# LINE 1360 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_BUTTONDOWN :: CUInt
{-# LINE 1361 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_BUTTONUP :: CUInt
{-# LINE 1362 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_MOTION :: CUInt
{-# LINE 1363 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_ENTER :: CUInt
{-# LINE 1364 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_LEAVE :: CUInt
{-# LINE 1365 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_WHEEL :: CUInt
{-# LINE 1366 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DWET_POSITION_SIZE :: CUInt
{-# LINE 1367 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_STARTED :: CUInt
{-# LINE 1368 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_STOPPED :: CUInt
{-# LINE 1369 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_SPEEDCHANGE :: CUInt
{-# LINE 1370 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_STREAMCHANGE :: CUInt
{-# LINE 1371 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_FATALERROR :: CUInt
{-# LINE 1372 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_FINISHED :: CUInt
{-# LINE 1373 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_SURFACECHANGE :: CUInt
{-# LINE 1374 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_FRAMEDECODED :: CUInt
{-# LINE 1375 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_FRAMEDISPLAYED :: CUInt
{-# LINE 1376 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_DATAEXHAUSTED :: CUInt
{-# LINE 1377 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_DATALOW :: CUInt
{-# LINE 1378 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_VIDEOACTION :: CUInt
{-# LINE 1379 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_DATAHIGH :: CUInt
{-# LINE 1380 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_BUFFERTIMELOW :: CUInt
{-# LINE 1381 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBEventBufferStats'DVPET_BUFFERTIMEHIGH :: CUInt
{-# LINE 1382 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBEventBufferStats where
  sizeOf _ = 164
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    v8 <- peekByteOff p 32
    v9 <- peekByteOff p 36
    v10 <- peekByteOff p 40
    v11 <- peekByteOff p 44
    v12 <- peekByteOff p 48
    v13 <- peekByteOff p 52
    v14 <- peekByteOff p 56
    v15 <- peekByteOff p 60
    v16 <- peekByteOff p 64
    v17 <- peekByteOff p 68
    v18 <- peekByteOff p 72
    v19 <- peekByteOff p 76
    v20 <- peekByteOff p 80
    v21 <- peekByteOff p 84
    v22 <- peekByteOff p 88
    v23 <- peekByteOff p 92
    v24 <- peekByteOff p 96
    v25 <- peekByteOff p 100
    v26 <- peekByteOff p 104
    v27 <- peekByteOff p 108
    v28 <- peekByteOff p 112
    v29 <- peekByteOff p 116
    v30 <- peekByteOff p 120
    v31 <- peekByteOff p 124
    v32 <- peekByteOff p 128
    v33 <- peekByteOff p 132
    v34 <- peekByteOff p 136
    v35 <- peekByteOff p 140
    v36 <- peekByteOff p 144
    v37 <- peekByteOff p 148
    v38 <- peekByteOff p 152
    v39 <- peekByteOff p 156
    v40 <- peekByteOff p 160
    return $ C'DFBEventBufferStats v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14 v15 v16 v17 v18 v19 v20 v21 v22 v23 v24 v25 v26 v27 v28 v29 v30 v31 v32 v33 v34 v35 v36 v37 v38 v39 v40
  poke p (C'DFBEventBufferStats v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14 v15 v16 v17 v18 v19 v20 v21 v22 v23 v24 v25 v26 v27 v28 v29 v30 v31 v32 v33 v34 v35 v36 v37 v38 v39 v40) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    pokeByteOff p 32 v8
    pokeByteOff p 36 v9
    pokeByteOff p 40 v10
    pokeByteOff p 44 v11
    pokeByteOff p 48 v12
    pokeByteOff p 52 v13
    pokeByteOff p 56 v14
    pokeByteOff p 60 v15
    pokeByteOff p 64 v16
    pokeByteOff p 68 v17
    pokeByteOff p 72 v18
    pokeByteOff p 76 v19
    pokeByteOff p 80 v20
    pokeByteOff p 84 v21
    pokeByteOff p 88 v22
    pokeByteOff p 92 v23
    pokeByteOff p 96 v24
    pokeByteOff p 100 v25
    pokeByteOff p 104 v26
    pokeByteOff p 108 v27
    pokeByteOff p 112 v28
    pokeByteOff p 116 v29
    pokeByteOff p 120 v30
    pokeByteOff p 124 v31
    pokeByteOff p 128 v32
    pokeByteOff p 132 v33
    pokeByteOff p 136 v34
    pokeByteOff p 140 v35
    pokeByteOff p 144 v36
    pokeByteOff p 148 v37
    pokeByteOff p 152 v38
    pokeByteOff p 156 v39
    pokeByteOff p 160 v40
    return ()

{-# LINE 1383 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBWindowKeySelection = Word32

{-# LINE 1385 "src/Bindings/DirectFB/Types.hsc" #-}

c'DWKS_ALL = 0
c'DWKS_ALL :: (Num a) => a

{-# LINE 1387 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWKS_NONE = 1
c'DWKS_NONE :: (Num a) => a

{-# LINE 1388 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWKS_LIST = 2
c'DWKS_LIST :: (Num a) => a

{-# LINE 1389 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBWindowGeometryMode = Word32

{-# LINE 1391 "src/Bindings/DirectFB/Types.hsc" #-}

c'DWGM_DEFAULT = 0
c'DWGM_DEFAULT :: (Num a) => a

{-# LINE 1393 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWGM_FOLLOW = 1
c'DWGM_FOLLOW :: (Num a) => a

{-# LINE 1394 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWGM_RECTANGLE = 2
c'DWGM_RECTANGLE :: (Num a) => a

{-# LINE 1395 "src/Bindings/DirectFB/Types.hsc" #-}
c'DWGM_LOCATION = 3
c'DWGM_LOCATION :: (Num a) => a

{-# LINE 1396 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBWindowGeometry = C'DFBWindowGeometry{
{-# LINE 1398 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBWindowGeometry'mode :: C'DFBWindowGeometryMode
{-# LINE 1399 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowGeometry'rectangle :: C'DFBRectangle
{-# LINE 1400 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBWindowGeometry'location :: C'DFBLocation
{-# LINE 1401 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBWindowGeometry where
  sizeOf _ = 36
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 20
    return $ C'DFBWindowGeometry v0 v1 v2
  poke p (C'DFBWindowGeometry v0 v1 v2) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 20 v2
    return ()

{-# LINE 1402 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBTextEncodingCallback = FunPtr (C'DFBTextEncodingID -> CString -> Ptr () -> IO C'DFBEnumerationResult)
foreign import ccall "wrapper" mk'DFBTextEncodingCallback
  :: (C'DFBTextEncodingID -> CString -> Ptr () -> IO C'DFBEnumerationResult) -> IO C'DFBTextEncodingCallback

{-# LINE 1405 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBImageCapabilities = Word32

{-# LINE 1407 "src/Bindings/DirectFB/Types.hsc" #-}

c'DICAPS_NONE = 0
c'DICAPS_NONE :: (Num a) => a

{-# LINE 1409 "src/Bindings/DirectFB/Types.hsc" #-}
c'DICAPS_ALPHACHANNEL = 1
c'DICAPS_ALPHACHANNEL :: (Num a) => a

{-# LINE 1410 "src/Bindings/DirectFB/Types.hsc" #-}
c'DICAPS_COLORKEY = 2
c'DICAPS_COLORKEY :: (Num a) => a

{-# LINE 1411 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBImageDescription = C'DFBImageDescription{
{-# LINE 1413 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBImageDescription'caps :: C'DFBImageCapabilities
{-# LINE 1414 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBImageDescription'colorkey_r :: Word8
{-# LINE 1415 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBImageDescription'colorkey_g :: Word8
{-# LINE 1416 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBImageDescription'colorkey_b :: Word8
{-# LINE 1417 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBImageDescription where
  sizeOf _ = 8
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 5
    v3 <- peekByteOff p 6
    return $ C'DFBImageDescription v0 v1 v2 v3
  poke p (C'DFBImageDescription v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 5 v2
    pokeByteOff p 6 v3
    return ()

{-# LINE 1418 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DIRenderCallbackResult = Word32

{-# LINE 1420 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIRCR_OK = 0
c'DIRCR_OK :: (Num a) => a

{-# LINE 1422 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIRCR_ABORT = 1
c'DIRCR_ABORT :: (Num a) => a

{-# LINE 1423 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DIRenderCallback = FunPtr (Ptr C'DFBRectangle -> Ptr () -> IO C'DIRenderCallbackResult)
foreign import ccall "wrapper" mk'DIRenderCallback
  :: (Ptr C'DFBRectangle -> Ptr () -> IO C'DIRenderCallbackResult) -> IO C'DIRenderCallback

{-# LINE 1426 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBStreamCapabilities = Word32

{-# LINE 1428 "src/Bindings/DirectFB/Types.hsc" #-}

c'DVSCAPS_NONE = 0
c'DVSCAPS_NONE :: (Num a) => a

{-# LINE 1430 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVSCAPS_VIDEO = 1
c'DVSCAPS_VIDEO :: (Num a) => a

{-# LINE 1431 "src/Bindings/DirectFB/Types.hsc" #-}
c'DVSCAPS_AUDIO = 2
c'DVSCAPS_AUDIO :: (Num a) => a

{-# LINE 1432 "src/Bindings/DirectFB/Types.hsc" #-}

c'DFB_STREAM_DESC_ENCODING_LENGTH = 30
c'DFB_STREAM_DESC_ENCODING_LENGTH :: (Num a) => a

{-# LINE 1434 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_STREAM_DESC_TITLE_LENGTH = 255
c'DFB_STREAM_DESC_TITLE_LENGTH :: (Num a) => a

{-# LINE 1435 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_STREAM_DESC_AUTHOR_LENGTH = 255
c'DFB_STREAM_DESC_AUTHOR_LENGTH :: (Num a) => a

{-# LINE 1436 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_STREAM_DESC_ALBUM_LENGTH = 255
c'DFB_STREAM_DESC_ALBUM_LENGTH :: (Num a) => a

{-# LINE 1437 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_STREAM_DESC_GENRE_LENGTH = 32
c'DFB_STREAM_DESC_GENRE_LENGTH :: (Num a) => a

{-# LINE 1438 "src/Bindings/DirectFB/Types.hsc" #-}
c'DFB_STREAM_DESC_COMMENT_LENGTH = 255
c'DFB_STREAM_DESC_COMMENT_LENGTH :: (Num a) => a

{-# LINE 1439 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBStreamDescription = C'DFBStreamDescription{
{-# LINE 1441 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBStreamDescription'caps :: C'DFBStreamCapabilities
{-# LINE 1442 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'video'encoding :: [CChar]
{-# LINE 1443 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'video'framerate :: CDouble
{-# LINE 1444 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'video'aspect :: CDouble
{-# LINE 1445 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'video'bitrate :: CInt
{-# LINE 1446 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'video'afd :: CInt
{-# LINE 1447 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'video'width :: CInt
{-# LINE 1448 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'video'height :: CInt
{-# LINE 1449 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'audio'encoding :: [CChar]
{-# LINE 1450 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'audio'samplerate :: CInt
{-# LINE 1451 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'audio'channels :: CInt
{-# LINE 1452 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'audio'bitrate :: CInt
{-# LINE 1453 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'title :: [CChar]
{-# LINE 1454 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'author :: [CChar]
{-# LINE 1455 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'album :: [CChar]
{-# LINE 1456 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'year :: CShort
{-# LINE 1457 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'genre :: [CChar]
{-# LINE 1458 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamDescription'comment :: [CChar]
{-# LINE 1459 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBStreamDescription where
  sizeOf _ = 1168
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekArray 30 (plusPtr p 4)
    v2 <- peekByteOff p 36
    v3 <- peekByteOff p 44
    v4 <- peekByteOff p 52
    v5 <- peekByteOff p 56
    v6 <- peekByteOff p 60
    v7 <- peekByteOff p 64
    v8 <- peekArray 30 (plusPtr p 68)
    v9 <- peekByteOff p 100
    v10 <- peekByteOff p 104
    v11 <- peekByteOff p 108
    v12 <- peekArray 255 (plusPtr p 112)
    v13 <- peekArray 255 (plusPtr p 367)
    v14 <- peekArray 255 (plusPtr p 622)
    v15 <- peekByteOff p 878
    v16 <- peekArray 32 (plusPtr p 880)
    v17 <- peekArray 255 (plusPtr p 912)
    return $ C'DFBStreamDescription v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14 v15 v16 v17
  poke p (C'DFBStreamDescription v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13 v14 v15 v16 v17) = do
    pokeByteOff p 0 v0
    pokeArray (plusPtr p 4) (take 30 v1)
    pokeByteOff p 36 v2
    pokeByteOff p 44 v3
    pokeByteOff p 52 v4
    pokeByteOff p 56 v5
    pokeByteOff p 60 v6
    pokeByteOff p 64 v7
    pokeArray (plusPtr p 68) (take 30 v8)
    pokeByteOff p 100 v9
    pokeByteOff p 104 v10
    pokeByteOff p 108 v11
    pokeArray (plusPtr p 112) (take 255 v12)
    pokeArray (plusPtr p 367) (take 255 v13)
    pokeArray (plusPtr p 622) (take 255 v14)
    pokeByteOff p 878 v15
    pokeArray (plusPtr p 880) (take 32 v16)
    pokeArray (plusPtr p 912) (take 255 v17)
    return ()

{-# LINE 1460 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBStreamFormat = Word32

{-# LINE 1462 "src/Bindings/DirectFB/Types.hsc" #-}

c'DSF_ES = 0
c'DSF_ES :: (Num a) => a

{-# LINE 1464 "src/Bindings/DirectFB/Types.hsc" #-}
c'DSF_PES = 1
c'DSF_PES :: (Num a) => a

{-# LINE 1465 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBStreamAttributes = C'DFBStreamAttributes{
{-# LINE 1467 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBStreamAttributes'video'encoding :: [CChar]
{-# LINE 1468 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamAttributes'video'format :: C'DFBStreamFormat
{-# LINE 1469 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamAttributes'audio'encoding :: [CChar]
{-# LINE 1470 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBStreamAttributes'audio'format :: C'DFBStreamFormat
{-# LINE 1471 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBStreamAttributes where
  sizeOf _ = 72
  alignment = sizeOf
  peek p = do
    v0 <- peekArray 30 (plusPtr p 0)
    v1 <- peekByteOff p 32
    v2 <- peekArray 30 (plusPtr p 36)
    v3 <- peekByteOff p 68
    return $ C'DFBStreamAttributes v0 v1 v2 v3
  poke p (C'DFBStreamAttributes v0 v1 v2 v3) = do
    pokeArray (plusPtr p 0) (take 30 v0)
    pokeByteOff p 32 v1
    pokeArray (plusPtr p 36) (take 30 v2)
    pokeByteOff p 68 v3
    return ()

{-# LINE 1472 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBBufferOccupancy = C'DFBBufferOccupancy{
{-# LINE 1474 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBBufferOccupancy'valid :: C'DFBStreamCapabilities
{-# LINE 1475 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferOccupancy'video'buffer_size :: CUInt
{-# LINE 1476 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferOccupancy'video'minimum_level :: CUInt
{-# LINE 1477 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferOccupancy'video'maximum_level :: CUInt
{-# LINE 1478 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferOccupancy'video'current_level :: CUInt
{-# LINE 1479 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferOccupancy'audio'buffer_size :: CUInt
{-# LINE 1480 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferOccupancy'audio'minimum_level :: CUInt
{-# LINE 1481 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferOccupancy'audio'maximum_level :: CUInt
{-# LINE 1482 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferOccupancy'audio'current_level :: CUInt
{-# LINE 1483 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBBufferOccupancy where
  sizeOf _ = 36
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    v8 <- peekByteOff p 32
    return $ C'DFBBufferOccupancy v0 v1 v2 v3 v4 v5 v6 v7 v8
  poke p (C'DFBBufferOccupancy v0 v1 v2 v3 v4 v5 v6 v7 v8) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    pokeByteOff p 32 v8
    return ()

{-# LINE 1484 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBBufferThresholds = C'DFBBufferThresholds{
{-# LINE 1486 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBBufferThresholds'selection :: C'DFBStreamCapabilities
{-# LINE 1487 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferThresholds'video'minimum_level :: CUInt
{-# LINE 1488 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferThresholds'video'maximum_level :: CUInt
{-# LINE 1489 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferThresholds'video'minimum_time :: CUInt
{-# LINE 1490 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferThresholds'video'maximum_time :: CUInt
{-# LINE 1491 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferThresholds'audio'minimum_level :: CUInt
{-# LINE 1492 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferThresholds'audio'maximum_level :: CUInt
{-# LINE 1493 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferThresholds'audio'minimum_time :: CUInt
{-# LINE 1494 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBBufferThresholds'audio'maximum_time :: CUInt
{-# LINE 1495 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBBufferThresholds where
  sizeOf _ = 36
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    v8 <- peekByteOff p 32
    return $ C'DFBBufferThresholds v0 v1 v2 v3 v4 v5 v6 v7 v8
  poke p (C'DFBBufferThresholds v0 v1 v2 v3 v4 v5 v6 v7 v8) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    pokeByteOff p 32 v8
    return ()

{-# LINE 1496 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DVFrameCallback = FunPtr (Ptr () -> IO ())
foreign import ccall "wrapper" mk'DVFrameCallback
  :: (Ptr () -> IO ()) -> IO C'DVFrameCallback

{-# LINE 1498 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceKeyType = Word32

{-# LINE 1500 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIKT_UNICODE = 0
c'DIKT_UNICODE :: (Num a) => a

{-# LINE 1502 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKT_SPECIAL = 61440
c'DIKT_SPECIAL :: (Num a) => a

{-# LINE 1503 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKT_FUNCTION = 61696
c'DIKT_FUNCTION :: (Num a) => a

{-# LINE 1504 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKT_MODIFIER = 61952
c'DIKT_MODIFIER :: (Num a) => a

{-# LINE 1505 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKT_LOCK = 62208
c'DIKT_LOCK :: (Num a) => a

{-# LINE 1506 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKT_DEAD = 62464
c'DIKT_DEAD :: (Num a) => a

{-# LINE 1507 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKT_CUSTOM = 62720
c'DIKT_CUSTOM :: (Num a) => a

{-# LINE 1508 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKT_IDENTIFIER = 62976
c'DIKT_IDENTIFIER :: (Num a) => a

{-# LINE 1509 "src/Bindings/DirectFB/Types.hsc" #-}

foreign import ccall "inline_DFB_KEY" c'DFB_KEY
  :: C'DFBInputDeviceKeyType -> CInt -> C'DFBInputDeviceKeySymbol

{-# LINE 1512 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_KEY_TYPE" c'DFB_KEY_TYPE
  :: C'DFBInputDeviceKeySymbol -> C'DFBInputDeviceKeyType

{-# LINE 1514 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_KEY_IS_ASCII" c'DFB_KEY_IS_ASCII
  :: C'DFBInputDeviceKeySymbol -> CInt

{-# LINE 1515 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_FUNCTION_KEY" c'DFB_FUNCTION_KEY
  :: CInt -> C'DFBInputDeviceKeySymbol

{-# LINE 1516 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_CUSTOM_KEY" c'DFB_CUSTOM_KEY
  :: CInt -> C'DFBInputDeviceKeySymbol

{-# LINE 1517 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_LOWER_CASE" c'DFB_LOWER_CASE
  :: C'DFBInputDeviceKeySymbol -> CInt

{-# LINE 1518 "src/Bindings/DirectFB/Types.hsc" #-}
foreign import ccall "inline_DFB_UPPER_CASE" c'DFB_UPPER_CASE
  :: C'DFBInputDeviceKeySymbol -> CInt

{-# LINE 1519 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceModifierKeyIdentifier = Word32

{-# LINE 1521 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIMKI_SHIFT = 0
c'DIMKI_SHIFT :: (Num a) => a

{-# LINE 1523 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMKI_CONTROL = 1
c'DIMKI_CONTROL :: (Num a) => a

{-# LINE 1524 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMKI_ALT = 2
c'DIMKI_ALT :: (Num a) => a

{-# LINE 1525 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMKI_ALTGR = 3
c'DIMKI_ALTGR :: (Num a) => a

{-# LINE 1526 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMKI_META = 4
c'DIMKI_META :: (Num a) => a

{-# LINE 1527 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMKI_SUPER = 5
c'DIMKI_SUPER :: (Num a) => a

{-# LINE 1528 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMKI_HYPER = 6
c'DIMKI_HYPER :: (Num a) => a

{-# LINE 1529 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMKI_FIRST = 0
c'DIMKI_FIRST :: (Num a) => a

{-# LINE 1530 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIMKI_LAST = 6
c'DIMKI_LAST :: (Num a) => a

{-# LINE 1531 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceKeyIdentifier = Word32

{-# LINE 1533 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIKI_UNKNOWN = 62976
c'DIKI_UNKNOWN :: (Num a) => a

{-# LINE 1535 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_A = 62977
c'DIKI_A :: (Num a) => a

{-# LINE 1536 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_B = 62978
c'DIKI_B :: (Num a) => a

{-# LINE 1537 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_C = 62979
c'DIKI_C :: (Num a) => a

{-# LINE 1538 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_D = 62980
c'DIKI_D :: (Num a) => a

{-# LINE 1539 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_E = 62981
c'DIKI_E :: (Num a) => a

{-# LINE 1540 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F = 62982
c'DIKI_F :: (Num a) => a

{-# LINE 1541 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_G = 62983
c'DIKI_G :: (Num a) => a

{-# LINE 1542 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_H = 62984
c'DIKI_H :: (Num a) => a

{-# LINE 1543 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_I = 62985
c'DIKI_I :: (Num a) => a

{-# LINE 1544 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_J = 62986
c'DIKI_J :: (Num a) => a

{-# LINE 1545 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_K = 62987
c'DIKI_K :: (Num a) => a

{-# LINE 1546 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_L = 62988
c'DIKI_L :: (Num a) => a

{-# LINE 1547 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_M = 62989
c'DIKI_M :: (Num a) => a

{-# LINE 1548 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_N = 62990
c'DIKI_N :: (Num a) => a

{-# LINE 1549 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_O = 62991
c'DIKI_O :: (Num a) => a

{-# LINE 1550 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_P = 62992
c'DIKI_P :: (Num a) => a

{-# LINE 1551 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_Q = 62993
c'DIKI_Q :: (Num a) => a

{-# LINE 1552 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_R = 62994
c'DIKI_R :: (Num a) => a

{-# LINE 1553 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_S = 62995
c'DIKI_S :: (Num a) => a

{-# LINE 1554 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_T = 62996
c'DIKI_T :: (Num a) => a

{-# LINE 1555 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_U = 62997
c'DIKI_U :: (Num a) => a

{-# LINE 1556 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_V = 62998
c'DIKI_V :: (Num a) => a

{-# LINE 1557 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_W = 62999
c'DIKI_W :: (Num a) => a

{-# LINE 1558 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_X = 63000
c'DIKI_X :: (Num a) => a

{-# LINE 1559 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_Y = 63001
c'DIKI_Y :: (Num a) => a

{-# LINE 1560 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_Z = 63002
c'DIKI_Z :: (Num a) => a

{-# LINE 1561 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_0 = 63003
c'DIKI_0 :: (Num a) => a

{-# LINE 1562 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_1 = 63004
c'DIKI_1 :: (Num a) => a

{-# LINE 1563 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_2 = 63005
c'DIKI_2 :: (Num a) => a

{-# LINE 1564 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_3 = 63006
c'DIKI_3 :: (Num a) => a

{-# LINE 1565 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_4 = 63007
c'DIKI_4 :: (Num a) => a

{-# LINE 1566 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_5 = 63008
c'DIKI_5 :: (Num a) => a

{-# LINE 1567 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_6 = 63009
c'DIKI_6 :: (Num a) => a

{-# LINE 1568 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_7 = 63010
c'DIKI_7 :: (Num a) => a

{-# LINE 1569 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_8 = 63011
c'DIKI_8 :: (Num a) => a

{-# LINE 1570 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_9 = 63012
c'DIKI_9 :: (Num a) => a

{-# LINE 1571 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F1 = 63013
c'DIKI_F1 :: (Num a) => a

{-# LINE 1572 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F2 = 63014
c'DIKI_F2 :: (Num a) => a

{-# LINE 1573 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F3 = 63015
c'DIKI_F3 :: (Num a) => a

{-# LINE 1574 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F4 = 63016
c'DIKI_F4 :: (Num a) => a

{-# LINE 1575 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F5 = 63017
c'DIKI_F5 :: (Num a) => a

{-# LINE 1576 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F6 = 63018
c'DIKI_F6 :: (Num a) => a

{-# LINE 1577 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F7 = 63019
c'DIKI_F7 :: (Num a) => a

{-# LINE 1578 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F8 = 63020
c'DIKI_F8 :: (Num a) => a

{-# LINE 1579 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F9 = 63021
c'DIKI_F9 :: (Num a) => a

{-# LINE 1580 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F10 = 63022
c'DIKI_F10 :: (Num a) => a

{-# LINE 1581 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F11 = 63023
c'DIKI_F11 :: (Num a) => a

{-# LINE 1582 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_F12 = 63024
c'DIKI_F12 :: (Num a) => a

{-# LINE 1583 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_SHIFT_L = 63025
c'DIKI_SHIFT_L :: (Num a) => a

{-# LINE 1584 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_SHIFT_R = 63026
c'DIKI_SHIFT_R :: (Num a) => a

{-# LINE 1585 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_CONTROL_L = 63027
c'DIKI_CONTROL_L :: (Num a) => a

{-# LINE 1586 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_CONTROL_R = 63028
c'DIKI_CONTROL_R :: (Num a) => a

{-# LINE 1587 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_ALT_L = 63029
c'DIKI_ALT_L :: (Num a) => a

{-# LINE 1588 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_ALT_R = 63030
c'DIKI_ALT_R :: (Num a) => a

{-# LINE 1589 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_META_L = 63031
c'DIKI_META_L :: (Num a) => a

{-# LINE 1590 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_META_R = 63032
c'DIKI_META_R :: (Num a) => a

{-# LINE 1591 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_SUPER_L = 63033
c'DIKI_SUPER_L :: (Num a) => a

{-# LINE 1592 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_SUPER_R = 63034
c'DIKI_SUPER_R :: (Num a) => a

{-# LINE 1593 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_HYPER_L = 63035
c'DIKI_HYPER_L :: (Num a) => a

{-# LINE 1594 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_HYPER_R = 63036
c'DIKI_HYPER_R :: (Num a) => a

{-# LINE 1595 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_CAPS_LOCK = 63037
c'DIKI_CAPS_LOCK :: (Num a) => a

{-# LINE 1596 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_NUM_LOCK = 63038
c'DIKI_NUM_LOCK :: (Num a) => a

{-# LINE 1597 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_SCROLL_LOCK = 63039
c'DIKI_SCROLL_LOCK :: (Num a) => a

{-# LINE 1598 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_ESCAPE = 63040
c'DIKI_ESCAPE :: (Num a) => a

{-# LINE 1599 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_LEFT = 63041
c'DIKI_LEFT :: (Num a) => a

{-# LINE 1600 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_RIGHT = 63042
c'DIKI_RIGHT :: (Num a) => a

{-# LINE 1601 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_UP = 63043
c'DIKI_UP :: (Num a) => a

{-# LINE 1602 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_DOWN = 63044
c'DIKI_DOWN :: (Num a) => a

{-# LINE 1603 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_TAB = 63045
c'DIKI_TAB :: (Num a) => a

{-# LINE 1604 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_ENTER = 63046
c'DIKI_ENTER :: (Num a) => a

{-# LINE 1605 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_SPACE = 63047
c'DIKI_SPACE :: (Num a) => a

{-# LINE 1606 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_BACKSPACE = 63048
c'DIKI_BACKSPACE :: (Num a) => a

{-# LINE 1607 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_INSERT = 63049
c'DIKI_INSERT :: (Num a) => a

{-# LINE 1608 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_DELETE = 63050
c'DIKI_DELETE :: (Num a) => a

{-# LINE 1609 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_HOME = 63051
c'DIKI_HOME :: (Num a) => a

{-# LINE 1610 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_END = 63052
c'DIKI_END :: (Num a) => a

{-# LINE 1611 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_PAGE_UP = 63053
c'DIKI_PAGE_UP :: (Num a) => a

{-# LINE 1612 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_PAGE_DOWN = 63054
c'DIKI_PAGE_DOWN :: (Num a) => a

{-# LINE 1613 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_PRINT = 63055
c'DIKI_PRINT :: (Num a) => a

{-# LINE 1614 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_PAUSE = 63056
c'DIKI_PAUSE :: (Num a) => a

{-# LINE 1615 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_QUOTE_LEFT = 63057
c'DIKI_QUOTE_LEFT :: (Num a) => a

{-# LINE 1616 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_MINUS_SIGN = 63058
c'DIKI_MINUS_SIGN :: (Num a) => a

{-# LINE 1617 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_EQUALS_SIGN = 63059
c'DIKI_EQUALS_SIGN :: (Num a) => a

{-# LINE 1618 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_BRACKET_LEFT = 63060
c'DIKI_BRACKET_LEFT :: (Num a) => a

{-# LINE 1619 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_BRACKET_RIGHT = 63061
c'DIKI_BRACKET_RIGHT :: (Num a) => a

{-# LINE 1620 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_BACKSLASH = 63062
c'DIKI_BACKSLASH :: (Num a) => a

{-# LINE 1621 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_SEMICOLON = 63063
c'DIKI_SEMICOLON :: (Num a) => a

{-# LINE 1622 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_QUOTE_RIGHT = 63064
c'DIKI_QUOTE_RIGHT :: (Num a) => a

{-# LINE 1623 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_COMMA = 63065
c'DIKI_COMMA :: (Num a) => a

{-# LINE 1624 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_PERIOD = 63066
c'DIKI_PERIOD :: (Num a) => a

{-# LINE 1625 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_SLASH = 63067
c'DIKI_SLASH :: (Num a) => a

{-# LINE 1626 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_LESS_SIGN = 63068
c'DIKI_LESS_SIGN :: (Num a) => a

{-# LINE 1627 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_DIV = 63069
c'DIKI_KP_DIV :: (Num a) => a

{-# LINE 1628 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_MULT = 63070
c'DIKI_KP_MULT :: (Num a) => a

{-# LINE 1629 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_MINUS = 63071
c'DIKI_KP_MINUS :: (Num a) => a

{-# LINE 1630 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_PLUS = 63072
c'DIKI_KP_PLUS :: (Num a) => a

{-# LINE 1631 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_ENTER = 63073
c'DIKI_KP_ENTER :: (Num a) => a

{-# LINE 1632 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_SPACE = 63074
c'DIKI_KP_SPACE :: (Num a) => a

{-# LINE 1633 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_TAB = 63075
c'DIKI_KP_TAB :: (Num a) => a

{-# LINE 1634 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_F1 = 63076
c'DIKI_KP_F1 :: (Num a) => a

{-# LINE 1635 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_F2 = 63077
c'DIKI_KP_F2 :: (Num a) => a

{-# LINE 1636 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_F3 = 63078
c'DIKI_KP_F3 :: (Num a) => a

{-# LINE 1637 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_F4 = 63079
c'DIKI_KP_F4 :: (Num a) => a

{-# LINE 1638 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_EQUAL = 63080
c'DIKI_KP_EQUAL :: (Num a) => a

{-# LINE 1639 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_SEPARATOR = 63081
c'DIKI_KP_SEPARATOR :: (Num a) => a

{-# LINE 1640 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_DECIMAL = 63082
c'DIKI_KP_DECIMAL :: (Num a) => a

{-# LINE 1641 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_0 = 63083
c'DIKI_KP_0 :: (Num a) => a

{-# LINE 1642 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_1 = 63084
c'DIKI_KP_1 :: (Num a) => a

{-# LINE 1643 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_2 = 63085
c'DIKI_KP_2 :: (Num a) => a

{-# LINE 1644 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_3 = 63086
c'DIKI_KP_3 :: (Num a) => a

{-# LINE 1645 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_4 = 63087
c'DIKI_KP_4 :: (Num a) => a

{-# LINE 1646 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_5 = 63088
c'DIKI_KP_5 :: (Num a) => a

{-# LINE 1647 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_6 = 63089
c'DIKI_KP_6 :: (Num a) => a

{-# LINE 1648 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_7 = 63090
c'DIKI_KP_7 :: (Num a) => a

{-# LINE 1649 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_8 = 63091
c'DIKI_KP_8 :: (Num a) => a

{-# LINE 1650 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KP_9 = 63092
c'DIKI_KP_9 :: (Num a) => a

{-# LINE 1651 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKI_KEYDEF_END = 63093
c'DIKI_KEYDEF_END :: (Num a) => a

{-# LINE 1652 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceKeySymbol = Word32

{-# LINE 1654 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIKS_NULL = 0
c'DIKS_NULL :: (Num a) => a

{-# LINE 1656 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_BACKSPACE = 8
c'DIKS_BACKSPACE :: (Num a) => a

{-# LINE 1657 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TAB = 9
c'DIKS_TAB :: (Num a) => a

{-# LINE 1658 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_RETURN = 13
c'DIKS_RETURN :: (Num a) => a

{-# LINE 1659 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CANCEL = 24
c'DIKS_CANCEL :: (Num a) => a

{-# LINE 1660 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_ESCAPE = 27
c'DIKS_ESCAPE :: (Num a) => a

{-# LINE 1661 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SPACE = 32
c'DIKS_SPACE :: (Num a) => a

{-# LINE 1662 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_EXCLAMATION_MARK = 33
c'DIKS_EXCLAMATION_MARK :: (Num a) => a

{-# LINE 1663 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_QUOTATION = 34
c'DIKS_QUOTATION :: (Num a) => a

{-# LINE 1664 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_NUMBER_SIGN = 35
c'DIKS_NUMBER_SIGN :: (Num a) => a

{-# LINE 1665 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DOLLAR_SIGN = 36
c'DIKS_DOLLAR_SIGN :: (Num a) => a

{-# LINE 1666 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PERCENT_SIGN = 37
c'DIKS_PERCENT_SIGN :: (Num a) => a

{-# LINE 1667 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_AMPERSAND = 38
c'DIKS_AMPERSAND :: (Num a) => a

{-# LINE 1668 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_APOSTROPHE = 39
c'DIKS_APOSTROPHE :: (Num a) => a

{-# LINE 1669 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PARENTHESIS_LEFT = 40
c'DIKS_PARENTHESIS_LEFT :: (Num a) => a

{-# LINE 1670 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PARENTHESIS_RIGHT = 41
c'DIKS_PARENTHESIS_RIGHT :: (Num a) => a

{-# LINE 1671 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_ASTERISK = 42
c'DIKS_ASTERISK :: (Num a) => a

{-# LINE 1672 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PLUS_SIGN = 43
c'DIKS_PLUS_SIGN :: (Num a) => a

{-# LINE 1673 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_COMMA = 44
c'DIKS_COMMA :: (Num a) => a

{-# LINE 1674 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_MINUS_SIGN = 45
c'DIKS_MINUS_SIGN :: (Num a) => a

{-# LINE 1675 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PERIOD = 46
c'DIKS_PERIOD :: (Num a) => a

{-# LINE 1676 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SLASH = 47
c'DIKS_SLASH :: (Num a) => a

{-# LINE 1677 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_0 = 48
c'DIKS_0 :: (Num a) => a

{-# LINE 1678 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_1 = 49
c'DIKS_1 :: (Num a) => a

{-# LINE 1679 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_2 = 50
c'DIKS_2 :: (Num a) => a

{-# LINE 1680 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_3 = 51
c'DIKS_3 :: (Num a) => a

{-# LINE 1681 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_4 = 52
c'DIKS_4 :: (Num a) => a

{-# LINE 1682 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_5 = 53
c'DIKS_5 :: (Num a) => a

{-# LINE 1683 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_6 = 54
c'DIKS_6 :: (Num a) => a

{-# LINE 1684 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_7 = 55
c'DIKS_7 :: (Num a) => a

{-# LINE 1685 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_8 = 56
c'DIKS_8 :: (Num a) => a

{-# LINE 1686 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_9 = 57
c'DIKS_9 :: (Num a) => a

{-# LINE 1687 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_COLON = 58
c'DIKS_COLON :: (Num a) => a

{-# LINE 1688 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SEMICOLON = 59
c'DIKS_SEMICOLON :: (Num a) => a

{-# LINE 1689 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_LESS_THAN_SIGN = 60
c'DIKS_LESS_THAN_SIGN :: (Num a) => a

{-# LINE 1690 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_EQUALS_SIGN = 61
c'DIKS_EQUALS_SIGN :: (Num a) => a

{-# LINE 1691 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_GREATER_THAN_SIGN = 62
c'DIKS_GREATER_THAN_SIGN :: (Num a) => a

{-# LINE 1692 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_QUESTION_MARK = 63
c'DIKS_QUESTION_MARK :: (Num a) => a

{-# LINE 1693 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_AT = 64
c'DIKS_AT :: (Num a) => a

{-# LINE 1694 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_A = 65
c'DIKS_CAPITAL_A :: (Num a) => a

{-# LINE 1695 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_B = 66
c'DIKS_CAPITAL_B :: (Num a) => a

{-# LINE 1696 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_C = 67
c'DIKS_CAPITAL_C :: (Num a) => a

{-# LINE 1697 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_D = 68
c'DIKS_CAPITAL_D :: (Num a) => a

{-# LINE 1698 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_E = 69
c'DIKS_CAPITAL_E :: (Num a) => a

{-# LINE 1699 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_F = 70
c'DIKS_CAPITAL_F :: (Num a) => a

{-# LINE 1700 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_G = 71
c'DIKS_CAPITAL_G :: (Num a) => a

{-# LINE 1701 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_H = 72
c'DIKS_CAPITAL_H :: (Num a) => a

{-# LINE 1702 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_I = 73
c'DIKS_CAPITAL_I :: (Num a) => a

{-# LINE 1703 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_J = 74
c'DIKS_CAPITAL_J :: (Num a) => a

{-# LINE 1704 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_K = 75
c'DIKS_CAPITAL_K :: (Num a) => a

{-# LINE 1705 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_L = 76
c'DIKS_CAPITAL_L :: (Num a) => a

{-# LINE 1706 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_M = 77
c'DIKS_CAPITAL_M :: (Num a) => a

{-# LINE 1707 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_N = 78
c'DIKS_CAPITAL_N :: (Num a) => a

{-# LINE 1708 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_O = 79
c'DIKS_CAPITAL_O :: (Num a) => a

{-# LINE 1709 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_P = 80
c'DIKS_CAPITAL_P :: (Num a) => a

{-# LINE 1710 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_Q = 81
c'DIKS_CAPITAL_Q :: (Num a) => a

{-# LINE 1711 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_R = 82
c'DIKS_CAPITAL_R :: (Num a) => a

{-# LINE 1712 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_S = 83
c'DIKS_CAPITAL_S :: (Num a) => a

{-# LINE 1713 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_T = 84
c'DIKS_CAPITAL_T :: (Num a) => a

{-# LINE 1714 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_U = 85
c'DIKS_CAPITAL_U :: (Num a) => a

{-# LINE 1715 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_V = 86
c'DIKS_CAPITAL_V :: (Num a) => a

{-# LINE 1716 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_W = 87
c'DIKS_CAPITAL_W :: (Num a) => a

{-# LINE 1717 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_X = 88
c'DIKS_CAPITAL_X :: (Num a) => a

{-# LINE 1718 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_Y = 89
c'DIKS_CAPITAL_Y :: (Num a) => a

{-# LINE 1719 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPITAL_Z = 90
c'DIKS_CAPITAL_Z :: (Num a) => a

{-# LINE 1720 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SQUARE_BRACKET_LEFT = 91
c'DIKS_SQUARE_BRACKET_LEFT :: (Num a) => a

{-# LINE 1721 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_BACKSLASH = 92
c'DIKS_BACKSLASH :: (Num a) => a

{-# LINE 1722 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SQUARE_BRACKET_RIGHT = 93
c'DIKS_SQUARE_BRACKET_RIGHT :: (Num a) => a

{-# LINE 1723 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CIRCUMFLEX_ACCENT = 94
c'DIKS_CIRCUMFLEX_ACCENT :: (Num a) => a

{-# LINE 1724 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_UNDERSCORE = 95
c'DIKS_UNDERSCORE :: (Num a) => a

{-# LINE 1725 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_GRAVE_ACCENT = 96
c'DIKS_GRAVE_ACCENT :: (Num a) => a

{-# LINE 1726 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_A = 97
c'DIKS_SMALL_A :: (Num a) => a

{-# LINE 1727 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_B = 98
c'DIKS_SMALL_B :: (Num a) => a

{-# LINE 1728 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_C = 99
c'DIKS_SMALL_C :: (Num a) => a

{-# LINE 1729 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_D = 100
c'DIKS_SMALL_D :: (Num a) => a

{-# LINE 1730 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_E = 101
c'DIKS_SMALL_E :: (Num a) => a

{-# LINE 1731 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_F = 102
c'DIKS_SMALL_F :: (Num a) => a

{-# LINE 1732 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_G = 103
c'DIKS_SMALL_G :: (Num a) => a

{-# LINE 1733 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_H = 104
c'DIKS_SMALL_H :: (Num a) => a

{-# LINE 1734 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_I = 105
c'DIKS_SMALL_I :: (Num a) => a

{-# LINE 1735 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_J = 106
c'DIKS_SMALL_J :: (Num a) => a

{-# LINE 1736 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_K = 107
c'DIKS_SMALL_K :: (Num a) => a

{-# LINE 1737 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_L = 108
c'DIKS_SMALL_L :: (Num a) => a

{-# LINE 1738 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_M = 109
c'DIKS_SMALL_M :: (Num a) => a

{-# LINE 1739 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_N = 110
c'DIKS_SMALL_N :: (Num a) => a

{-# LINE 1740 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_O = 111
c'DIKS_SMALL_O :: (Num a) => a

{-# LINE 1741 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_P = 112
c'DIKS_SMALL_P :: (Num a) => a

{-# LINE 1742 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_Q = 113
c'DIKS_SMALL_Q :: (Num a) => a

{-# LINE 1743 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_R = 114
c'DIKS_SMALL_R :: (Num a) => a

{-# LINE 1744 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_S = 115
c'DIKS_SMALL_S :: (Num a) => a

{-# LINE 1745 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_T = 116
c'DIKS_SMALL_T :: (Num a) => a

{-# LINE 1746 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_U = 117
c'DIKS_SMALL_U :: (Num a) => a

{-# LINE 1747 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_V = 118
c'DIKS_SMALL_V :: (Num a) => a

{-# LINE 1748 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_W = 119
c'DIKS_SMALL_W :: (Num a) => a

{-# LINE 1749 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_X = 120
c'DIKS_SMALL_X :: (Num a) => a

{-# LINE 1750 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_Y = 121
c'DIKS_SMALL_Y :: (Num a) => a

{-# LINE 1751 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SMALL_Z = 122
c'DIKS_SMALL_Z :: (Num a) => a

{-# LINE 1752 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CURLY_BRACKET_LEFT = 123
c'DIKS_CURLY_BRACKET_LEFT :: (Num a) => a

{-# LINE 1753 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_VERTICAL_BAR = 124
c'DIKS_VERTICAL_BAR :: (Num a) => a

{-# LINE 1754 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CURLY_BRACKET_RIGHT = 125
c'DIKS_CURLY_BRACKET_RIGHT :: (Num a) => a

{-# LINE 1755 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TILDE = 126
c'DIKS_TILDE :: (Num a) => a

{-# LINE 1756 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DELETE = 127
c'DIKS_DELETE :: (Num a) => a

{-# LINE 1757 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_ENTER = 13
c'DIKS_ENTER :: (Num a) => a

{-# LINE 1758 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CURSOR_LEFT = 61440
c'DIKS_CURSOR_LEFT :: (Num a) => a

{-# LINE 1759 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CURSOR_RIGHT = 61441
c'DIKS_CURSOR_RIGHT :: (Num a) => a

{-# LINE 1760 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CURSOR_UP = 61442
c'DIKS_CURSOR_UP :: (Num a) => a

{-# LINE 1761 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CURSOR_DOWN = 61443
c'DIKS_CURSOR_DOWN :: (Num a) => a

{-# LINE 1762 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_INSERT = 61444
c'DIKS_INSERT :: (Num a) => a

{-# LINE 1763 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_HOME = 61445
c'DIKS_HOME :: (Num a) => a

{-# LINE 1764 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_END = 61446
c'DIKS_END :: (Num a) => a

{-# LINE 1765 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PAGE_UP = 61447
c'DIKS_PAGE_UP :: (Num a) => a

{-# LINE 1766 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PAGE_DOWN = 61448
c'DIKS_PAGE_DOWN :: (Num a) => a

{-# LINE 1767 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PRINT = 61449
c'DIKS_PRINT :: (Num a) => a

{-# LINE 1768 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PAUSE = 61450
c'DIKS_PAUSE :: (Num a) => a

{-# LINE 1769 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_OK = 61451
c'DIKS_OK :: (Num a) => a

{-# LINE 1770 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SELECT = 61452
c'DIKS_SELECT :: (Num a) => a

{-# LINE 1771 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_GOTO = 61453
c'DIKS_GOTO :: (Num a) => a

{-# LINE 1772 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CLEAR = 61454
c'DIKS_CLEAR :: (Num a) => a

{-# LINE 1773 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_POWER = 61455
c'DIKS_POWER :: (Num a) => a

{-# LINE 1774 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_POWER2 = 61456
c'DIKS_POWER2 :: (Num a) => a

{-# LINE 1775 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_OPTION = 61457
c'DIKS_OPTION :: (Num a) => a

{-# LINE 1776 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_MENU = 61458
c'DIKS_MENU :: (Num a) => a

{-# LINE 1777 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_HELP = 61459
c'DIKS_HELP :: (Num a) => a

{-# LINE 1778 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_INFO = 61460
c'DIKS_INFO :: (Num a) => a

{-# LINE 1779 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TIME = 61461
c'DIKS_TIME :: (Num a) => a

{-# LINE 1780 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_VENDOR = 61462
c'DIKS_VENDOR :: (Num a) => a

{-# LINE 1781 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_ARCHIVE = 61463
c'DIKS_ARCHIVE :: (Num a) => a

{-# LINE 1782 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PROGRAM = 61464
c'DIKS_PROGRAM :: (Num a) => a

{-# LINE 1783 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CHANNEL = 61465
c'DIKS_CHANNEL :: (Num a) => a

{-# LINE 1784 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_FAVORITES = 61466
c'DIKS_FAVORITES :: (Num a) => a

{-# LINE 1785 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_EPG = 61467
c'DIKS_EPG :: (Num a) => a

{-# LINE 1786 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PVR = 61468
c'DIKS_PVR :: (Num a) => a

{-# LINE 1787 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_MHP = 61469
c'DIKS_MHP :: (Num a) => a

{-# LINE 1788 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_LANGUAGE = 61470
c'DIKS_LANGUAGE :: (Num a) => a

{-# LINE 1789 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TITLE = 61471
c'DIKS_TITLE :: (Num a) => a

{-# LINE 1790 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SUBTITLE = 61472
c'DIKS_SUBTITLE :: (Num a) => a

{-# LINE 1791 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_ANGLE = 61473
c'DIKS_ANGLE :: (Num a) => a

{-# LINE 1792 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_ZOOM = 61474
c'DIKS_ZOOM :: (Num a) => a

{-# LINE 1793 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_MODE = 61475
c'DIKS_MODE :: (Num a) => a

{-# LINE 1794 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_KEYBOARD = 61476
c'DIKS_KEYBOARD :: (Num a) => a

{-# LINE 1795 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PC = 61477
c'DIKS_PC :: (Num a) => a

{-# LINE 1796 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SCREEN = 61478
c'DIKS_SCREEN :: (Num a) => a

{-# LINE 1797 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TV = 61479
c'DIKS_TV :: (Num a) => a

{-# LINE 1798 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TV2 = 61480
c'DIKS_TV2 :: (Num a) => a

{-# LINE 1799 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_VCR = 61481
c'DIKS_VCR :: (Num a) => a

{-# LINE 1800 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_VCR2 = 61482
c'DIKS_VCR2 :: (Num a) => a

{-# LINE 1801 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SAT = 61483
c'DIKS_SAT :: (Num a) => a

{-# LINE 1802 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SAT2 = 61484
c'DIKS_SAT2 :: (Num a) => a

{-# LINE 1803 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CD = 61485
c'DIKS_CD :: (Num a) => a

{-# LINE 1804 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TAPE = 61486
c'DIKS_TAPE :: (Num a) => a

{-# LINE 1805 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_RADIO = 61487
c'DIKS_RADIO :: (Num a) => a

{-# LINE 1806 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TUNER = 61488
c'DIKS_TUNER :: (Num a) => a

{-# LINE 1807 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PLAYER = 61489
c'DIKS_PLAYER :: (Num a) => a

{-# LINE 1808 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TEXT = 61490
c'DIKS_TEXT :: (Num a) => a

{-# LINE 1809 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DVD = 61491
c'DIKS_DVD :: (Num a) => a

{-# LINE 1810 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_AUX = 61492
c'DIKS_AUX :: (Num a) => a

{-# LINE 1811 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_MP3 = 61493
c'DIKS_MP3 :: (Num a) => a

{-# LINE 1812 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PHONE = 61494
c'DIKS_PHONE :: (Num a) => a

{-# LINE 1813 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_AUDIO = 61495
c'DIKS_AUDIO :: (Num a) => a

{-# LINE 1814 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_VIDEO = 61496
c'DIKS_VIDEO :: (Num a) => a

{-# LINE 1815 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_INTERNET = 61497
c'DIKS_INTERNET :: (Num a) => a

{-# LINE 1816 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_MAIL = 61498
c'DIKS_MAIL :: (Num a) => a

{-# LINE 1817 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_NEWS = 61499
c'DIKS_NEWS :: (Num a) => a

{-# LINE 1818 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DIRECTORY = 61500
c'DIKS_DIRECTORY :: (Num a) => a

{-# LINE 1819 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_LIST = 61501
c'DIKS_LIST :: (Num a) => a

{-# LINE 1820 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CALCULATOR = 61502
c'DIKS_CALCULATOR :: (Num a) => a

{-# LINE 1821 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_MEMO = 61503
c'DIKS_MEMO :: (Num a) => a

{-# LINE 1822 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CALENDAR = 61504
c'DIKS_CALENDAR :: (Num a) => a

{-# LINE 1823 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_EDITOR = 61505
c'DIKS_EDITOR :: (Num a) => a

{-# LINE 1824 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_RED = 61506
c'DIKS_RED :: (Num a) => a

{-# LINE 1825 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_GREEN = 61507
c'DIKS_GREEN :: (Num a) => a

{-# LINE 1826 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_YELLOW = 61508
c'DIKS_YELLOW :: (Num a) => a

{-# LINE 1827 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_BLUE = 61509
c'DIKS_BLUE :: (Num a) => a

{-# LINE 1828 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CHANNEL_UP = 61510
c'DIKS_CHANNEL_UP :: (Num a) => a

{-# LINE 1829 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CHANNEL_DOWN = 61511
c'DIKS_CHANNEL_DOWN :: (Num a) => a

{-# LINE 1830 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_BACK = 61512
c'DIKS_BACK :: (Num a) => a

{-# LINE 1831 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_FORWARD = 61513
c'DIKS_FORWARD :: (Num a) => a

{-# LINE 1832 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_FIRST = 61514
c'DIKS_FIRST :: (Num a) => a

{-# LINE 1833 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_LAST = 61515
c'DIKS_LAST :: (Num a) => a

{-# LINE 1834 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_VOLUME_UP = 61516
c'DIKS_VOLUME_UP :: (Num a) => a

{-# LINE 1835 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_VOLUME_DOWN = 61517
c'DIKS_VOLUME_DOWN :: (Num a) => a

{-# LINE 1836 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_MUTE = 61518
c'DIKS_MUTE :: (Num a) => a

{-# LINE 1837 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_AB = 61519
c'DIKS_AB :: (Num a) => a

{-# LINE 1838 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PLAYPAUSE = 61520
c'DIKS_PLAYPAUSE :: (Num a) => a

{-# LINE 1839 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PLAY = 61521
c'DIKS_PLAY :: (Num a) => a

{-# LINE 1840 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_STOP = 61522
c'DIKS_STOP :: (Num a) => a

{-# LINE 1841 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_RESTART = 61523
c'DIKS_RESTART :: (Num a) => a

{-# LINE 1842 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SLOW = 61524
c'DIKS_SLOW :: (Num a) => a

{-# LINE 1843 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_FAST = 61525
c'DIKS_FAST :: (Num a) => a

{-# LINE 1844 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_RECORD = 61526
c'DIKS_RECORD :: (Num a) => a

{-# LINE 1845 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_EJECT = 61527
c'DIKS_EJECT :: (Num a) => a

{-# LINE 1846 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SHUFFLE = 61528
c'DIKS_SHUFFLE :: (Num a) => a

{-# LINE 1847 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_REWIND = 61529
c'DIKS_REWIND :: (Num a) => a

{-# LINE 1848 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_FASTFORWARD = 61530
c'DIKS_FASTFORWARD :: (Num a) => a

{-# LINE 1849 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_PREVIOUS = 61531
c'DIKS_PREVIOUS :: (Num a) => a

{-# LINE 1850 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_NEXT = 61532
c'DIKS_NEXT :: (Num a) => a

{-# LINE 1851 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_BEGIN = 61533
c'DIKS_BEGIN :: (Num a) => a

{-# LINE 1852 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DIGITS = 61534
c'DIKS_DIGITS :: (Num a) => a

{-# LINE 1853 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TEEN = 61535
c'DIKS_TEEN :: (Num a) => a

{-# LINE 1854 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_TWEN = 61536
c'DIKS_TWEN :: (Num a) => a

{-# LINE 1855 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_BREAK = 61537
c'DIKS_BREAK :: (Num a) => a

{-# LINE 1856 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_EXIT = 61538
c'DIKS_EXIT :: (Num a) => a

{-# LINE 1857 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SETUP = 61539
c'DIKS_SETUP :: (Num a) => a

{-# LINE 1858 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CURSOR_LEFT_UP = 61540
c'DIKS_CURSOR_LEFT_UP :: (Num a) => a

{-# LINE 1859 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CURSOR_LEFT_DOWN = 61541
c'DIKS_CURSOR_LEFT_DOWN :: (Num a) => a

{-# LINE 1860 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CURSOR_UP_RIGHT = 61542
c'DIKS_CURSOR_UP_RIGHT :: (Num a) => a

{-# LINE 1861 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CURSOR_DOWN_RIGHT = 61543
c'DIKS_CURSOR_DOWN_RIGHT :: (Num a) => a

{-# LINE 1862 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F1 = 61697
c'DIKS_F1 :: (Num a) => a

{-# LINE 1863 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F2 = 61698
c'DIKS_F2 :: (Num a) => a

{-# LINE 1864 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F3 = 61699
c'DIKS_F3 :: (Num a) => a

{-# LINE 1865 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F4 = 61700
c'DIKS_F4 :: (Num a) => a

{-# LINE 1866 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F5 = 61701
c'DIKS_F5 :: (Num a) => a

{-# LINE 1867 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F6 = 61702
c'DIKS_F6 :: (Num a) => a

{-# LINE 1868 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F7 = 61703
c'DIKS_F7 :: (Num a) => a

{-# LINE 1869 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F8 = 61704
c'DIKS_F8 :: (Num a) => a

{-# LINE 1870 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F9 = 61705
c'DIKS_F9 :: (Num a) => a

{-# LINE 1871 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F10 = 61706
c'DIKS_F10 :: (Num a) => a

{-# LINE 1872 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F11 = 61707
c'DIKS_F11 :: (Num a) => a

{-# LINE 1873 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_F12 = 61708
c'DIKS_F12 :: (Num a) => a

{-# LINE 1874 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SHIFT = 61953
c'DIKS_SHIFT :: (Num a) => a

{-# LINE 1875 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CONTROL = 61954
c'DIKS_CONTROL :: (Num a) => a

{-# LINE 1876 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_ALT = 61956
c'DIKS_ALT :: (Num a) => a

{-# LINE 1877 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_ALTGR = 61960
c'DIKS_ALTGR :: (Num a) => a

{-# LINE 1878 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_META = 61968
c'DIKS_META :: (Num a) => a

{-# LINE 1879 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SUPER = 61984
c'DIKS_SUPER :: (Num a) => a

{-# LINE 1880 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_HYPER = 62016
c'DIKS_HYPER :: (Num a) => a

{-# LINE 1881 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CAPS_LOCK = 62208
c'DIKS_CAPS_LOCK :: (Num a) => a

{-# LINE 1882 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_NUM_LOCK = 62209
c'DIKS_NUM_LOCK :: (Num a) => a

{-# LINE 1883 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_SCROLL_LOCK = 62210
c'DIKS_SCROLL_LOCK :: (Num a) => a

{-# LINE 1884 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_ABOVEDOT = 62464
c'DIKS_DEAD_ABOVEDOT :: (Num a) => a

{-# LINE 1885 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_ABOVERING = 62465
c'DIKS_DEAD_ABOVERING :: (Num a) => a

{-# LINE 1886 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_ACUTE = 62466
c'DIKS_DEAD_ACUTE :: (Num a) => a

{-# LINE 1887 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_BREVE = 62467
c'DIKS_DEAD_BREVE :: (Num a) => a

{-# LINE 1888 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_CARON = 62468
c'DIKS_DEAD_CARON :: (Num a) => a

{-# LINE 1889 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_CEDILLA = 62469
c'DIKS_DEAD_CEDILLA :: (Num a) => a

{-# LINE 1890 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_CIRCUMFLEX = 62470
c'DIKS_DEAD_CIRCUMFLEX :: (Num a) => a

{-# LINE 1891 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_DIAERESIS = 62471
c'DIKS_DEAD_DIAERESIS :: (Num a) => a

{-# LINE 1892 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_DOUBLEACUTE = 62472
c'DIKS_DEAD_DOUBLEACUTE :: (Num a) => a

{-# LINE 1893 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_GRAVE = 62473
c'DIKS_DEAD_GRAVE :: (Num a) => a

{-# LINE 1894 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_IOTA = 62474
c'DIKS_DEAD_IOTA :: (Num a) => a

{-# LINE 1895 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_MACRON = 62475
c'DIKS_DEAD_MACRON :: (Num a) => a

{-# LINE 1896 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_OGONEK = 62476
c'DIKS_DEAD_OGONEK :: (Num a) => a

{-# LINE 1897 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_SEMIVOICED_SOUND = 62477
c'DIKS_DEAD_SEMIVOICED_SOUND :: (Num a) => a

{-# LINE 1898 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_TILDE = 62478
c'DIKS_DEAD_TILDE :: (Num a) => a

{-# LINE 1899 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_DEAD_VOICED_SOUND = 62479
c'DIKS_DEAD_VOICED_SOUND :: (Num a) => a

{-# LINE 1900 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM0 = 62720
c'DIKS_CUSTOM0 :: (Num a) => a

{-# LINE 1901 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM1 = 62721
c'DIKS_CUSTOM1 :: (Num a) => a

{-# LINE 1902 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM2 = 62722
c'DIKS_CUSTOM2 :: (Num a) => a

{-# LINE 1903 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM3 = 62723
c'DIKS_CUSTOM3 :: (Num a) => a

{-# LINE 1904 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM4 = 62724
c'DIKS_CUSTOM4 :: (Num a) => a

{-# LINE 1905 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM5 = 62725
c'DIKS_CUSTOM5 :: (Num a) => a

{-# LINE 1906 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM6 = 62726
c'DIKS_CUSTOM6 :: (Num a) => a

{-# LINE 1907 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM7 = 62727
c'DIKS_CUSTOM7 :: (Num a) => a

{-# LINE 1908 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM8 = 62728
c'DIKS_CUSTOM8 :: (Num a) => a

{-# LINE 1909 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM9 = 62729
c'DIKS_CUSTOM9 :: (Num a) => a

{-# LINE 1910 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM10 = 62730
c'DIKS_CUSTOM10 :: (Num a) => a

{-# LINE 1911 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM11 = 62731
c'DIKS_CUSTOM11 :: (Num a) => a

{-# LINE 1912 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM12 = 62732
c'DIKS_CUSTOM12 :: (Num a) => a

{-# LINE 1913 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM13 = 62733
c'DIKS_CUSTOM13 :: (Num a) => a

{-# LINE 1914 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM14 = 62734
c'DIKS_CUSTOM14 :: (Num a) => a

{-# LINE 1915 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM15 = 62735
c'DIKS_CUSTOM15 :: (Num a) => a

{-# LINE 1916 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM16 = 62736
c'DIKS_CUSTOM16 :: (Num a) => a

{-# LINE 1917 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM17 = 62737
c'DIKS_CUSTOM17 :: (Num a) => a

{-# LINE 1918 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM18 = 62738
c'DIKS_CUSTOM18 :: (Num a) => a

{-# LINE 1919 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM19 = 62739
c'DIKS_CUSTOM19 :: (Num a) => a

{-# LINE 1920 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM20 = 62740
c'DIKS_CUSTOM20 :: (Num a) => a

{-# LINE 1921 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM21 = 62741
c'DIKS_CUSTOM21 :: (Num a) => a

{-# LINE 1922 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM22 = 62742
c'DIKS_CUSTOM22 :: (Num a) => a

{-# LINE 1923 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM23 = 62743
c'DIKS_CUSTOM23 :: (Num a) => a

{-# LINE 1924 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM24 = 62744
c'DIKS_CUSTOM24 :: (Num a) => a

{-# LINE 1925 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM25 = 62745
c'DIKS_CUSTOM25 :: (Num a) => a

{-# LINE 1926 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM26 = 62746
c'DIKS_CUSTOM26 :: (Num a) => a

{-# LINE 1927 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM27 = 62747
c'DIKS_CUSTOM27 :: (Num a) => a

{-# LINE 1928 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM28 = 62748
c'DIKS_CUSTOM28 :: (Num a) => a

{-# LINE 1929 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM29 = 62749
c'DIKS_CUSTOM29 :: (Num a) => a

{-# LINE 1930 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM30 = 62750
c'DIKS_CUSTOM30 :: (Num a) => a

{-# LINE 1931 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM31 = 62751
c'DIKS_CUSTOM31 :: (Num a) => a

{-# LINE 1932 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM32 = 62752
c'DIKS_CUSTOM32 :: (Num a) => a

{-# LINE 1933 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM33 = 62753
c'DIKS_CUSTOM33 :: (Num a) => a

{-# LINE 1934 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM34 = 62754
c'DIKS_CUSTOM34 :: (Num a) => a

{-# LINE 1935 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM35 = 62755
c'DIKS_CUSTOM35 :: (Num a) => a

{-# LINE 1936 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM36 = 62756
c'DIKS_CUSTOM36 :: (Num a) => a

{-# LINE 1937 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM37 = 62757
c'DIKS_CUSTOM37 :: (Num a) => a

{-# LINE 1938 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM38 = 62758
c'DIKS_CUSTOM38 :: (Num a) => a

{-# LINE 1939 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM39 = 62759
c'DIKS_CUSTOM39 :: (Num a) => a

{-# LINE 1940 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM40 = 62760
c'DIKS_CUSTOM40 :: (Num a) => a

{-# LINE 1941 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM41 = 62761
c'DIKS_CUSTOM41 :: (Num a) => a

{-# LINE 1942 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM42 = 62762
c'DIKS_CUSTOM42 :: (Num a) => a

{-# LINE 1943 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM43 = 62763
c'DIKS_CUSTOM43 :: (Num a) => a

{-# LINE 1944 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM44 = 62764
c'DIKS_CUSTOM44 :: (Num a) => a

{-# LINE 1945 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM45 = 62765
c'DIKS_CUSTOM45 :: (Num a) => a

{-# LINE 1946 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM46 = 62766
c'DIKS_CUSTOM46 :: (Num a) => a

{-# LINE 1947 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM47 = 62767
c'DIKS_CUSTOM47 :: (Num a) => a

{-# LINE 1948 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM48 = 62768
c'DIKS_CUSTOM48 :: (Num a) => a

{-# LINE 1949 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM49 = 62769
c'DIKS_CUSTOM49 :: (Num a) => a

{-# LINE 1950 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM50 = 62770
c'DIKS_CUSTOM50 :: (Num a) => a

{-# LINE 1951 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM51 = 62771
c'DIKS_CUSTOM51 :: (Num a) => a

{-# LINE 1952 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM52 = 62772
c'DIKS_CUSTOM52 :: (Num a) => a

{-# LINE 1953 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM53 = 62773
c'DIKS_CUSTOM53 :: (Num a) => a

{-# LINE 1954 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM54 = 62774
c'DIKS_CUSTOM54 :: (Num a) => a

{-# LINE 1955 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM55 = 62775
c'DIKS_CUSTOM55 :: (Num a) => a

{-# LINE 1956 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM56 = 62776
c'DIKS_CUSTOM56 :: (Num a) => a

{-# LINE 1957 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM57 = 62777
c'DIKS_CUSTOM57 :: (Num a) => a

{-# LINE 1958 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM58 = 62778
c'DIKS_CUSTOM58 :: (Num a) => a

{-# LINE 1959 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM59 = 62779
c'DIKS_CUSTOM59 :: (Num a) => a

{-# LINE 1960 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM60 = 62780
c'DIKS_CUSTOM60 :: (Num a) => a

{-# LINE 1961 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM61 = 62781
c'DIKS_CUSTOM61 :: (Num a) => a

{-# LINE 1962 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM62 = 62782
c'DIKS_CUSTOM62 :: (Num a) => a

{-# LINE 1963 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM63 = 62783
c'DIKS_CUSTOM63 :: (Num a) => a

{-# LINE 1964 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM64 = 62784
c'DIKS_CUSTOM64 :: (Num a) => a

{-# LINE 1965 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM65 = 62785
c'DIKS_CUSTOM65 :: (Num a) => a

{-# LINE 1966 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM66 = 62786
c'DIKS_CUSTOM66 :: (Num a) => a

{-# LINE 1967 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM67 = 62787
c'DIKS_CUSTOM67 :: (Num a) => a

{-# LINE 1968 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM68 = 62788
c'DIKS_CUSTOM68 :: (Num a) => a

{-# LINE 1969 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM69 = 62789
c'DIKS_CUSTOM69 :: (Num a) => a

{-# LINE 1970 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM70 = 62790
c'DIKS_CUSTOM70 :: (Num a) => a

{-# LINE 1971 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM71 = 62791
c'DIKS_CUSTOM71 :: (Num a) => a

{-# LINE 1972 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM72 = 62792
c'DIKS_CUSTOM72 :: (Num a) => a

{-# LINE 1973 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM73 = 62793
c'DIKS_CUSTOM73 :: (Num a) => a

{-# LINE 1974 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM74 = 62794
c'DIKS_CUSTOM74 :: (Num a) => a

{-# LINE 1975 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM75 = 62795
c'DIKS_CUSTOM75 :: (Num a) => a

{-# LINE 1976 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM76 = 62796
c'DIKS_CUSTOM76 :: (Num a) => a

{-# LINE 1977 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM77 = 62797
c'DIKS_CUSTOM77 :: (Num a) => a

{-# LINE 1978 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM78 = 62798
c'DIKS_CUSTOM78 :: (Num a) => a

{-# LINE 1979 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM79 = 62799
c'DIKS_CUSTOM79 :: (Num a) => a

{-# LINE 1980 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM80 = 62800
c'DIKS_CUSTOM80 :: (Num a) => a

{-# LINE 1981 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM81 = 62801
c'DIKS_CUSTOM81 :: (Num a) => a

{-# LINE 1982 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM82 = 62802
c'DIKS_CUSTOM82 :: (Num a) => a

{-# LINE 1983 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM83 = 62803
c'DIKS_CUSTOM83 :: (Num a) => a

{-# LINE 1984 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM84 = 62804
c'DIKS_CUSTOM84 :: (Num a) => a

{-# LINE 1985 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM85 = 62805
c'DIKS_CUSTOM85 :: (Num a) => a

{-# LINE 1986 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM86 = 62806
c'DIKS_CUSTOM86 :: (Num a) => a

{-# LINE 1987 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM87 = 62807
c'DIKS_CUSTOM87 :: (Num a) => a

{-# LINE 1988 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM88 = 62808
c'DIKS_CUSTOM88 :: (Num a) => a

{-# LINE 1989 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM89 = 62809
c'DIKS_CUSTOM89 :: (Num a) => a

{-# LINE 1990 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM90 = 62810
c'DIKS_CUSTOM90 :: (Num a) => a

{-# LINE 1991 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM91 = 62811
c'DIKS_CUSTOM91 :: (Num a) => a

{-# LINE 1992 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM92 = 62812
c'DIKS_CUSTOM92 :: (Num a) => a

{-# LINE 1993 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM93 = 62813
c'DIKS_CUSTOM93 :: (Num a) => a

{-# LINE 1994 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM94 = 62814
c'DIKS_CUSTOM94 :: (Num a) => a

{-# LINE 1995 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM95 = 62815
c'DIKS_CUSTOM95 :: (Num a) => a

{-# LINE 1996 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM96 = 62816
c'DIKS_CUSTOM96 :: (Num a) => a

{-# LINE 1997 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM97 = 62817
c'DIKS_CUSTOM97 :: (Num a) => a

{-# LINE 1998 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM98 = 62818
c'DIKS_CUSTOM98 :: (Num a) => a

{-# LINE 1999 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKS_CUSTOM99 = 62819
c'DIKS_CUSTOM99 :: (Num a) => a

{-# LINE 2000 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceLockState = Word32

{-# LINE 2002 "src/Bindings/DirectFB/Types.hsc" #-}

c'DILS_SCROLL = 1
c'DILS_SCROLL :: (Num a) => a

{-# LINE 2004 "src/Bindings/DirectFB/Types.hsc" #-}
c'DILS_NUM = 2
c'DILS_NUM :: (Num a) => a

{-# LINE 2005 "src/Bindings/DirectFB/Types.hsc" #-}
c'DILS_CAPS = 4
c'DILS_CAPS :: (Num a) => a

{-# LINE 2006 "src/Bindings/DirectFB/Types.hsc" #-}

type C'DFBInputDeviceKeymapSymbolIndex = Word32

{-# LINE 2008 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIKSI_BASE = 0
c'DIKSI_BASE :: (Num a) => a

{-# LINE 2010 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKSI_BASE_SHIFT = 1
c'DIKSI_BASE_SHIFT :: (Num a) => a

{-# LINE 2011 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKSI_ALT = 2
c'DIKSI_ALT :: (Num a) => a

{-# LINE 2012 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKSI_ALT_SHIFT = 3
c'DIKSI_ALT_SHIFT :: (Num a) => a

{-# LINE 2013 "src/Bindings/DirectFB/Types.hsc" #-}
c'DIKSI_LAST = 3
c'DIKSI_LAST :: (Num a) => a

{-# LINE 2014 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBInputDeviceKeymapEntry = C'DFBInputDeviceKeymapEntry{
{-# LINE 2016 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBInputDeviceKeymapEntry'code :: CInt
{-# LINE 2017 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceKeymapEntry'locks :: C'DFBInputDeviceLockState
{-# LINE 2018 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceKeymapEntry'identifier :: C'DFBInputDeviceKeyIdentifier
{-# LINE 2019 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBInputDeviceKeymapEntry'symbols :: [C'DFBInputDeviceKeySymbol]
{-# LINE 2020 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBInputDeviceKeymapEntry where
  sizeOf _ = 28
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekArray 4 (plusPtr p 12)
    return $ C'DFBInputDeviceKeymapEntry v0 v1 v2 v3
  poke p (C'DFBInputDeviceKeymapEntry v0 v1 v2 v3) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeArray (plusPtr p 12) (take 4 v3)
    return ()

{-# LINE 2021 "src/Bindings/DirectFB/Types.hsc" #-}

c'DIRECTFBGL_INTERFACE_VERSION = 1
c'DIRECTFBGL_INTERFACE_VERSION :: (Num a) => a

{-# LINE 2023 "src/Bindings/DirectFB/Types.hsc" #-}

data C'DFBGLAttributes = C'DFBGLAttributes{
{-# LINE 2025 "src/Bindings/DirectFB/Types.hsc" #-}

  c'DFBGLAttributes'buffer_size :: CInt
{-# LINE 2026 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'depth_size :: CInt
{-# LINE 2027 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'stencil_size :: CInt
{-# LINE 2028 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'aux_buffers :: CInt
{-# LINE 2029 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'red_size :: CInt
{-# LINE 2030 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'green_size :: CInt
{-# LINE 2031 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'blue_size :: CInt
{-# LINE 2032 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'alpha_size :: CInt
{-# LINE 2033 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'accum_red_size :: CInt
{-# LINE 2034 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'accum_green_size :: CInt
{-# LINE 2035 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'accum_blue_size :: CInt
{-# LINE 2036 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'accum_alpha_size :: CInt
{-# LINE 2037 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'double_buffer :: C'DFBBoolean
{-# LINE 2038 "src/Bindings/DirectFB/Types.hsc" #-}
,
  c'DFBGLAttributes'stereo :: C'DFBBoolean
{-# LINE 2039 "src/Bindings/DirectFB/Types.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'DFBGLAttributes where
  sizeOf _ = 56
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 0
    v1 <- peekByteOff p 4
    v2 <- peekByteOff p 8
    v3 <- peekByteOff p 12
    v4 <- peekByteOff p 16
    v5 <- peekByteOff p 20
    v6 <- peekByteOff p 24
    v7 <- peekByteOff p 28
    v8 <- peekByteOff p 32
    v9 <- peekByteOff p 36
    v10 <- peekByteOff p 40
    v11 <- peekByteOff p 44
    v12 <- peekByteOff p 48
    v13 <- peekByteOff p 52
    return $ C'DFBGLAttributes v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13
  poke p (C'DFBGLAttributes v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12 v13) = do
    pokeByteOff p 0 v0
    pokeByteOff p 4 v1
    pokeByteOff p 8 v2
    pokeByteOff p 12 v3
    pokeByteOff p 16 v4
    pokeByteOff p 20 v5
    pokeByteOff p 24 v6
    pokeByteOff p 28 v7
    pokeByteOff p 32 v8
    pokeByteOff p 36 v9
    pokeByteOff p 40 v10
    pokeByteOff p 44 v11
    pokeByteOff p 48 v12
    pokeByteOff p 52 v13
    return ()

{-# LINE 2040 "src/Bindings/DirectFB/Types.hsc" #-}