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

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

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

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

module Bindings.DirectFB.IDirectFBFont 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/IDirectFBFont.hsc" #-}
import Bindings.DirectFB.Types

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

  c'IDirectFBFont'GetAscender :: FunPtr (Ptr C'IDirectFBFont -> Ptr CInt -> IO C'DFBResult)
{-# LINE 13 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'GetDescender :: FunPtr (Ptr C'IDirectFBFont -> Ptr CInt -> IO C'DFBResult)
{-# LINE 15 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'GetHeight :: FunPtr (Ptr C'IDirectFBFont -> Ptr CInt -> IO C'DFBResult)
{-# LINE 17 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'GetMaxAdvance :: FunPtr (Ptr C'IDirectFBFont -> Ptr CInt -> IO C'DFBResult)
{-# LINE 19 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'GetKerning :: FunPtr (Ptr C'IDirectFBFont -> CUInt -> CUInt -> Ptr CInt -> Ptr CInt -> IO C'DFBResult)
{-# LINE 21 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'GetStringWidth :: FunPtr (Ptr C'IDirectFBFont -> Ptr CString -> CInt -> Ptr CInt -> IO C'DFBResult)
{-# LINE 23 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'GetStringExtents :: FunPtr (Ptr C'IDirectFBFont -> Ptr CString -> CInt -> Ptr C'DFBRectangle -> Ptr C'DFBRectangle -> IO C'DFBResult)
{-# LINE 26 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'GetGlyphExtents :: FunPtr (Ptr C'IDirectFBFont -> CUInt -> Ptr C'DFBRectangle -> Ptr CInt -> IO C'DFBResult)
{-# LINE 28 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'GetStringBreak :: FunPtr (Ptr C'IDirectFBFont -> Ptr CString -> CInt -> CInt -> Ptr CInt -> Ptr CInt -> Ptr CString -> IO C'DFBResult)
{-# LINE 31 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'SetEncoding :: FunPtr (Ptr C'IDirectFBFont -> C'DFBTextEncodingID -> IO C'DFBResult)
{-# LINE 33 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'EnumEncodings :: FunPtr (Ptr C'IDirectFBFont -> C'DFBTextEncodingCallback -> Ptr () -> IO C'DFBResult)
{-# LINE 35 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}
,
  c'IDirectFBFont'FindEncoding :: FunPtr (Ptr C'IDirectFBFont -> Ptr CString -> Ptr C'DFBTextEncodingID -> IO C'DFBResult)
{-# LINE 37 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}

 } deriving (Eq,Show)
instance Storable C'IDirectFBFont where
  sizeOf _ = 64
  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
    return $ C'IDirectFBFont v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11
  poke p (C'IDirectFBFont v0 v1 v2 v3 v4 v5 v6 v7 v8 v9 v10 v11) = 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
    return ()

{-# LINE 38 "src/Bindings/DirectFB/IDirectFBFont.hsc" #-}