{-# LINE 1 "src/Bindings/GObject/GTypePlugin.hsc" #-}

{-# LINE 2 "src/Bindings/GObject/GTypePlugin.hsc" #-}

{-# LINE 3 "src/Bindings/GObject/GTypePlugin.hsc" #-}

-- | <http://library.gnome.org/devel/gobject/stable/GTypePlugin.html>

module Bindings.GObject.GTypePlugin 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/GObject/GTypePlugin.hsc" #-}
import Bindings.GObject.TypeInformation

data C'GTypePluginClass = C'GTypePluginClass{
{-# LINE 11 "src/Bindings/GObject/GTypePlugin.hsc" #-}

  c'GTypePluginClass'use_plugin :: C'GTypePluginUse
{-# LINE 12 "src/Bindings/GObject/GTypePlugin.hsc" #-}
,
  c'GTypePluginClass'unuse_plugin :: C'GTypePluginUnuse
{-# LINE 13 "src/Bindings/GObject/GTypePlugin.hsc" #-}
,
  c'GTypePluginClass'complete_type_info :: C'GTypePluginCompleteTypeInfo
{-# LINE 14 "src/Bindings/GObject/GTypePlugin.hsc" #-}
,
  c'GTypePluginClass'complete_interface_info :: C'GTypePluginCompleteInterfaceInfo
{-# LINE 15 "src/Bindings/GObject/GTypePlugin.hsc" #-}

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

{-# LINE 16 "src/Bindings/GObject/GTypePlugin.hsc" #-}

type C'GTypePluginUse = FunPtr (Ptr C'GTypePlugin -> IO ())
foreign import ccall "wrapper" mk'GTypePluginUse
  :: (Ptr C'GTypePlugin -> IO ()) -> IO C'GTypePluginUse
foreign import ccall "dynamic" mK'GTypePluginUse
  :: C'GTypePluginUse -> (Ptr C'GTypePlugin -> IO ())

{-# LINE 18 "src/Bindings/GObject/GTypePlugin.hsc" #-}
type C'GTypePluginUnuse = FunPtr (Ptr C'GTypePlugin -> IO ())
foreign import ccall "wrapper" mk'GTypePluginUnuse
  :: (Ptr C'GTypePlugin -> IO ()) -> IO C'GTypePluginUnuse
foreign import ccall "dynamic" mK'GTypePluginUnuse
  :: C'GTypePluginUnuse -> (Ptr C'GTypePlugin -> IO ())

{-# LINE 19 "src/Bindings/GObject/GTypePlugin.hsc" #-}
type C'GTypePluginCompleteTypeInfo = FunPtr (Ptr C'GTypePlugin -> C'GType -> Ptr C'GTypeInfo -> Ptr C'GTypeValueTable -> IO ())
foreign import ccall "wrapper" mk'GTypePluginCompleteTypeInfo
  :: (Ptr C'GTypePlugin -> C'GType -> Ptr C'GTypeInfo -> Ptr C'GTypeValueTable -> IO ()) -> IO C'GTypePluginCompleteTypeInfo
foreign import ccall "dynamic" mK'GTypePluginCompleteTypeInfo
  :: C'GTypePluginCompleteTypeInfo -> (Ptr C'GTypePlugin -> C'GType -> Ptr C'GTypeInfo -> Ptr C'GTypeValueTable -> IO ())

{-# LINE 21 "src/Bindings/GObject/GTypePlugin.hsc" #-}
type C'GTypePluginCompleteInterfaceInfo = FunPtr (Ptr C'GTypePlugin -> C'GType -> C'GType -> Ptr C'GInterfaceInfo -> IO ())
foreign import ccall "wrapper" mk'GTypePluginCompleteInterfaceInfo
  :: (Ptr C'GTypePlugin -> C'GType -> C'GType -> Ptr C'GInterfaceInfo -> IO ()) -> IO C'GTypePluginCompleteInterfaceInfo
foreign import ccall "dynamic" mK'GTypePluginCompleteInterfaceInfo
  :: C'GTypePluginCompleteInterfaceInfo -> (Ptr C'GTypePlugin -> C'GType -> C'GType -> Ptr C'GInterfaceInfo -> IO ())

{-# LINE 23 "src/Bindings/GObject/GTypePlugin.hsc" #-}