{-# LINE 1 "Data/GI/Base/GType.hsc" #-}
{-# LANGUAGE OverloadedStrings #-}
module Data.GI.Base.GType
( gtypeString
, gtypePointer
, gtypeInt
, gtypeUInt
, gtypeLong
, gtypeULong
, gtypeInt64
, gtypeUInt64
, gtypeFloat
, gtypeDouble
, gtypeBoolean
, gtypeGType
, gtypeStrv
, gtypeBoxed
, gtypeObject
, gtypeVariant
, gtypeByteArray
, gtypeInvalid
, gtypeStablePtr
) where
import Control.Monad ((>=>))
import Foreign.C.String (CString)
import Foreign.Ptr (FunPtr)
import Foreign.StablePtr (StablePtr, newStablePtr, deRefStablePtr)
import Data.GI.Base.BasicConversions (withTextCString)
import Data.GI.Base.BasicTypes (GType(..), CGType)
gtypeString :: GType
gtypeString = GType 64
{-# LINE 57 "Data/GI/Base/GType.hsc" #-}
gtypePointer :: GType
gtypePointer = GType 68
{-# LINE 61 "Data/GI/Base/GType.hsc" #-}
gtypeInt :: GType
gtypeInt = GType 24
{-# LINE 65 "Data/GI/Base/GType.hsc" #-}
gtypeUInt :: GType
gtypeUInt = GType 28
{-# LINE 69 "Data/GI/Base/GType.hsc" #-}
gtypeLong :: GType
gtypeLong = GType 32
{-# LINE 73 "Data/GI/Base/GType.hsc" #-}
gtypeULong :: GType
gtypeULong = GType 36
{-# LINE 77 "Data/GI/Base/GType.hsc" #-}
gtypeInt64 :: GType
gtypeInt64 = GType 40
{-# LINE 81 "Data/GI/Base/GType.hsc" #-}
gtypeUInt64 :: GType
gtypeUInt64 = GType 44
{-# LINE 85 "Data/GI/Base/GType.hsc" #-}
gtypeFloat :: GType
gtypeFloat = GType 56
{-# LINE 89 "Data/GI/Base/GType.hsc" #-}
gtypeDouble :: GType
gtypeDouble = GType 60
{-# LINE 93 "Data/GI/Base/GType.hsc" #-}
gtypeBoolean :: GType
gtypeBoolean = GType 20
{-# LINE 97 "Data/GI/Base/GType.hsc" #-}
gtypeBoxed :: GType
gtypeBoxed = GType 72
{-# LINE 101 "Data/GI/Base/GType.hsc" #-}
gtypeObject :: GType
gtypeObject = GType 80
{-# LINE 105 "Data/GI/Base/GType.hsc" #-}
gtypeInvalid :: GType
gtypeInvalid = GType 0
{-# LINE 110 "Data/GI/Base/GType.hsc" #-}
gtypeVariant :: GType
gtypeVariant = GType 84
{-# LINE 114 "Data/GI/Base/GType.hsc" #-}
foreign import ccall "g_gtype_get_type" g_gtype_get_type :: CGType
gtypeGType :: GType
gtypeGType = GType g_gtype_get_type
foreign import ccall "g_strv_get_type" g_strv_get_type :: CGType
gtypeStrv :: GType
gtypeStrv = GType g_strv_get_type
foreign import ccall "g_byte_array_get_type" g_byte_array_get_type :: CGType
gtypeByteArray :: GType
gtypeByteArray = GType g_byte_array_get_type
duplicateStablePtr :: StablePtr a -> IO (StablePtr a)
duplicateStablePtr = deRefStablePtr >=> newStablePtr
foreign import ccall "wrapper"
mkStablePtrDuplicator :: (StablePtr a -> IO (StablePtr a)) ->
IO (FunPtr (StablePtr a -> IO (StablePtr a)))
foreign import ccall haskell_gi_register_Boxed_HsStablePtr ::
CString -> FunPtr (StablePtr a -> IO (StablePtr a)) -> IO GType
foreign import ccall haskell_gi_Boxed_StablePtr_GType :: IO CGType
gtypeStablePtr :: IO GType
gtypeStablePtr = withTextCString "Boxed-HsStablePtr" $ \cTypeName -> do
cgtype <- haskell_gi_Boxed_StablePtr_GType
if cgtype /= 0
then return (GType cgtype)
else do
duplicator <- mkStablePtrDuplicator duplicateStablePtr
haskell_gi_register_Boxed_HsStablePtr cTypeName duplicator