{-# LINE 1 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}

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

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

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

module Bindings.DirectFB.IDirectFBInputDevice where
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.Alloc (alloca)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word

{-# LINE 8 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
import Bindings.DirectFB.Types
import Bindings.DirectFB.IDirectFBEventBuffer

data C'IDirectFBInputDevice = C'IDirectFBInputDevice{
{-# LINE 12 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}

  c'IDirectFBInputDevice'GetID :: FunPtr (Ptr C'IDirectFBInputDevice -> Ptr C'DFBInputDeviceID -> IO C'DFBResult)
{-# LINE 14 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'GetDescription :: FunPtr (Ptr C'IDirectFBInputDevice -> Ptr C'DFBInputDeviceDescription -> IO C'DFBResult)
{-# LINE 16 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'GetKeymapEntry :: FunPtr (Ptr C'IDirectFBInputDevice -> CInt -> Ptr C'DFBInputDeviceKeymapEntry -> IO C'DFBResult)
{-# LINE 18 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
-- #field SetKeymapEntry , FunPtr (Ptr <IDirectFBInputDevice> -> \
--     CInt -> Ptr <DFBInputDeviceKeymapEntry> -> IO <DFBResult>)
-- #field LoadKeymap , FunPtr (Ptr <IDirectFBInputDevice> -> \
--     CString -> IO <DFBResult>)
,
  c'IDirectFBInputDevice'CreateEventBuffer :: FunPtr (Ptr C'IDirectFBInputDevice -> Ptr (Ptr C'IDirectFBEventBuffer) -> IO C'DFBResult)
{-# LINE 24 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'AttachEventBuffer :: FunPtr (Ptr C'IDirectFBInputDevice -> Ptr C'IDirectFBEventBuffer -> IO C'DFBResult)
{-# LINE 26 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'DetachEventBuffer :: FunPtr (Ptr C'IDirectFBInputDevice -> Ptr C'IDirectFBEventBuffer -> IO C'DFBResult)
{-# LINE 28 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'GetKeyState :: FunPtr (Ptr C'IDirectFBInputDevice -> C'DFBInputDeviceKeyIdentifier -> Ptr C'DFBInputDeviceKeyState -> IO C'DFBResult)
{-# LINE 31 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'GetModifiers :: FunPtr (Ptr C'IDirectFBInputDevice -> Ptr C'DFBInputDeviceModifierMask -> IO C'DFBResult)
{-# LINE 33 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'GetLockState :: FunPtr (Ptr C'IDirectFBInputDevice -> Ptr C'DFBInputDeviceLockState -> IO C'DFBResult)
{-# LINE 35 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'GetButtons :: FunPtr (Ptr C'IDirectFBInputDevice -> Ptr C'DFBInputDeviceButtonMask -> IO C'DFBResult)
{-# LINE 37 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'GetButtonState :: FunPtr (Ptr C'IDirectFBInputDevice -> C'DFBInputDeviceButtonIdentifier -> Ptr C'DFBInputDeviceButtonState -> IO C'DFBResult)
{-# LINE 40 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'GetAxis :: FunPtr (Ptr C'IDirectFBInputDevice -> C'DFBInputDeviceAxisIdentifier -> Ptr CInt -> IO C'DFBResult)
{-# LINE 42 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}
,
  c'IDirectFBInputDevice'GetXY :: FunPtr (Ptr C'IDirectFBInputDevice -> Ptr CInt -> Ptr CInt -> IO C'DFBResult)
{-# LINE 44 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'IDirectFBInputDevice where
  sizeOf _ = 68
  alignment = sizeOf
  peek p = do
    v0 <- peekByteOff p 16
    v1 <- peekByteOff p 20
    v2 <- peekByteOff p 24
    v3 <- peekByteOff p 28
    v4 <- peekByteOff p 32
    v5 <- peekByteOff p 36
    v6 <- peekByteOff p 40
    v7 <- peekByteOff p 44
    v8 <- peekByteOff p 48
    v9 <- peekByteOff p 52
    v10 <- peekByteOff p 56
    v11 <- peekByteOff p 60
    v12 <- peekByteOff p 64
    return $ C'IDirectFBInputDevice v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12
  poke p (C'IDirectFBInputDevice v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11 v12) = do
    pokeByteOff p 16 v0
    pokeByteOff p 20 v1
    pokeByteOff p 24 v2
    pokeByteOff p 28 v3
    pokeByteOff p 32 v4
    pokeByteOff p 36 v5
    pokeByteOff p 40 v6
    pokeByteOff p 44 v7
    pokeByteOff p 48 v8
    pokeByteOff p 52 v9
    pokeByteOff p 56 v10
    pokeByteOff p 60 v11
    pokeByteOff p 64 v12
    return ()

{-# LINE 45 "src/Bindings/DirectFB/IDirectFBInputDevice.hsc" #-}