{-# 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
, gtypeError
, gtypeGType
, gtypeStrv
, gtypeBoxed
, gtypeObject
, gtypeVariant
, gtypeByteArray
, gtypeInvalid
, gtypeStablePtr
) where
import Data.GI.Base.BasicTypes (GType(..), CGType)
gtypeString :: GType
gtypeString :: GType
gtypeString = CGType -> GType
GType CGType
64
{-# LINE 51 "Data/GI/Base/GType.hsc" #-}
gtypePointer :: GType
gtypePointer :: GType
gtypePointer = CGType -> GType
GType CGType
68
{-# LINE 55 "Data/GI/Base/GType.hsc" #-}
gtypeInt :: GType
gtypeInt :: GType
gtypeInt = CGType -> GType
GType CGType
24
{-# LINE 59 "Data/GI/Base/GType.hsc" #-}
gtypeUInt :: GType
gtypeUInt :: GType
gtypeUInt = CGType -> GType
GType CGType
28
{-# LINE 63 "Data/GI/Base/GType.hsc" #-}
gtypeLong :: GType
gtypeLong :: GType
gtypeLong = CGType -> GType
GType CGType
32
{-# LINE 67 "Data/GI/Base/GType.hsc" #-}
gtypeULong :: GType
gtypeULong :: GType
gtypeULong = CGType -> GType
GType CGType
36
{-# LINE 71 "Data/GI/Base/GType.hsc" #-}
gtypeInt64 :: GType
gtypeInt64 :: GType
gtypeInt64 = CGType -> GType
GType CGType
40
{-# LINE 75 "Data/GI/Base/GType.hsc" #-}
gtypeUInt64 :: GType
gtypeUInt64 :: GType
gtypeUInt64 = CGType -> GType
GType CGType
44
{-# LINE 79 "Data/GI/Base/GType.hsc" #-}
gtypeFloat :: GType
gtypeFloat :: GType
gtypeFloat = CGType -> GType
GType CGType
56
{-# LINE 83 "Data/GI/Base/GType.hsc" #-}
gtypeDouble :: GType
gtypeDouble :: GType
gtypeDouble = CGType -> GType
GType CGType
60
{-# LINE 87 "Data/GI/Base/GType.hsc" #-}
gtypeBoolean :: GType
gtypeBoolean :: GType
gtypeBoolean = CGType -> GType
GType CGType
20
{-# LINE 91 "Data/GI/Base/GType.hsc" #-}
gtypeBoxed :: GType
gtypeBoxed :: GType
gtypeBoxed = CGType -> GType
GType CGType
72
{-# LINE 95 "Data/GI/Base/GType.hsc" #-}
gtypeObject :: GType
gtypeObject :: GType
gtypeObject = CGType -> GType
GType CGType
80
{-# LINE 99 "Data/GI/Base/GType.hsc" #-}
gtypeInvalid :: GType
gtypeInvalid :: GType
gtypeInvalid = CGType -> GType
GType CGType
0
{-# LINE 104 "Data/GI/Base/GType.hsc" #-}
gtypeVariant :: GType
gtypeVariant :: GType
gtypeVariant = CGType -> GType
GType CGType
84
{-# LINE 108 "Data/GI/Base/GType.hsc" #-}
gtypeError :: GType
gtypeError :: GType
gtypeError = CGType -> GType
GType CGType
23236976
{-# LINE 112 "Data/GI/Base/GType.hsc" #-}
foreign import ccall "g_gtype_get_type" g_gtype_get_type :: CGType
gtypeGType :: GType
gtypeGType :: GType
gtypeGType = CGType -> GType
GType CGType
g_gtype_get_type
foreign import ccall "g_strv_get_type" g_strv_get_type :: CGType
gtypeStrv :: GType
gtypeStrv :: GType
gtypeStrv = CGType -> GType
GType CGType
g_strv_get_type
foreign import ccall "g_byte_array_get_type" g_byte_array_get_type :: CGType
gtypeByteArray :: GType
gtypeByteArray :: GType
gtypeByteArray = CGType -> GType
GType CGType
g_byte_array_get_type
foreign import ccall haskell_gi_StablePtr_get_type :: CGType
gtypeStablePtr :: GType
gtypeStablePtr :: GType
gtypeStablePtr = CGType -> GType
GType CGType
haskell_gi_StablePtr_get_type