{-# LINE 1 "Data/GI/Base/GType.hsc" #-}
{-# LANGUAGE OverloadedStrings #-}

-- | Basic `GType`s.
module Data.GI.Base.GType
    ( gtypeString
    , gtypePointer
    , gtypeInt
    , gtypeUInt
    , gtypeLong
    , gtypeULong
    , gtypeInt64
    , gtypeUInt64
    , gtypeFloat
    , gtypeDouble
    , gtypeBoolean
    , gtypeError
    , gtypeGType
    , gtypeStrv
    , gtypeBoxed
    , gtypeObject
    , gtypeVariant
    , gtypeByteArray
    , gtypeInvalid
    , gtypeParam

    , gtypeStablePtr
    , gtypeHValue
    ) where

import Data.GI.Base.BasicTypes (GType(..), CGType)



{-| [Note: compile-time vs run-time GTypes]

Notice that there are two types of GType's: the fundamental ones,
which are created with G_TYPE_MAKE_FUNDAMENTAL(n) and always have the
same runtime representation, and the ones that are registered in the
GObject type system at runtime, and whose `CGType` may change for each
program run (and generally does).

For the first type it is safe to use hsc to read the numerical values
of the CGType at compile type, but for the second type it is essential
to call the corresponding _get_type() function at runtime, and not use
the value of the corresponding "constant" at compile time via hsc.
-}

{- Fundamental types -}

-- | `GType` of strings.
gtypeString :: GType
gtypeString :: GType
gtypeString = CGType -> GType
GType CGType
64
{-# LINE 53 "Data/GI/Base/GType.hsc" #-}

-- | `GType` of pointers.
gtypePointer :: GType
gtypePointer :: GType
gtypePointer = CGType -> GType
GType CGType
68
{-# LINE 57 "Data/GI/Base/GType.hsc" #-}

-- | `GType` for signed integers (@gint@ or @gint32@).
gtypeInt :: GType
gtypeInt :: GType
gtypeInt = CGType -> GType
GType CGType
24
{-# LINE 61 "Data/GI/Base/GType.hsc" #-}

-- | `GType` for unsigned integers (@guint@ or @guint32@).
gtypeUInt :: GType
gtypeUInt :: GType
gtypeUInt = CGType -> GType
GType CGType
28
{-# LINE 65 "Data/GI/Base/GType.hsc" #-}

-- | `GType` for @glong@.
gtypeLong :: GType
gtypeLong :: GType
gtypeLong = CGType -> GType
GType CGType
32
{-# LINE 69 "Data/GI/Base/GType.hsc" #-}

-- | `GType` for @gulong@.
gtypeULong :: GType
gtypeULong :: GType
gtypeULong = CGType -> GType
GType CGType
36
{-# LINE 73 "Data/GI/Base/GType.hsc" #-}

-- | `GType` for signed 64 bit integers.
gtypeInt64 :: GType
gtypeInt64 :: GType
gtypeInt64 = CGType -> GType
GType CGType
40
{-# LINE 77 "Data/GI/Base/GType.hsc" #-}

-- | `GType` for unsigned 64 bit integers.
gtypeUInt64 :: GType
gtypeUInt64 :: GType
gtypeUInt64 = CGType -> GType
GType CGType
44
{-# LINE 81 "Data/GI/Base/GType.hsc" #-}

-- | `GType` for floating point values.
gtypeFloat :: GType
gtypeFloat :: GType
gtypeFloat = CGType -> GType
GType CGType
56
{-# LINE 85 "Data/GI/Base/GType.hsc" #-}

-- | `GType` for gdouble.
gtypeDouble :: GType
gtypeDouble :: GType
gtypeDouble = CGType -> GType
GType CGType
60
{-# LINE 89 "Data/GI/Base/GType.hsc" #-}

-- | `GType` corresponding to gboolean.
gtypeBoolean :: GType
gtypeBoolean :: GType
gtypeBoolean = CGType -> GType
GType CGType
20
{-# LINE 93 "Data/GI/Base/GType.hsc" #-}

-- | `GType` corresponding to a boxed object.
gtypeBoxed :: GType
gtypeBoxed :: GType
gtypeBoxed = CGType -> GType
GType CGType
72
{-# LINE 97 "Data/GI/Base/GType.hsc" #-}

-- | `GType` corresponding to a @GObject@.
gtypeObject :: GType
gtypeObject :: GType
gtypeObject = CGType -> GType
GType CGType
80
{-# LINE 101 "Data/GI/Base/GType.hsc" #-}

-- | An invalid `GType` used as error return value in some functions
-- which return a `GType`.
gtypeInvalid :: GType
gtypeInvalid :: GType
gtypeInvalid = CGType -> GType
GType CGType
0
{-# LINE 106 "Data/GI/Base/GType.hsc" #-}

-- | The `GType` corresponding to a @GVariant@.
gtypeVariant :: GType
gtypeVariant :: GType
gtypeVariant = CGType -> GType
GType CGType
84
{-# LINE 110 "Data/GI/Base/GType.hsc" #-}

-- | The `GType` corresponding to 'Data.GI.Base.BasicTypes.GParamSpec'.
gtypeParam :: GType
gtypeParam :: GType
gtypeParam = CGType -> GType
GType CGType
76
{-# LINE 114 "Data/GI/Base/GType.hsc" #-}

{- Run-time types -}

foreign import ccall "g_gtype_get_type" g_gtype_get_type :: CGType

-- | `GType` corresponding to a `GType` itself.
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

-- | `GType` for a NULL terminated array of strings.
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

-- | `GType` for a boxed type holding a @GByteArray@.
gtypeByteArray :: GType
gtypeByteArray :: GType
gtypeByteArray = CGType -> GType
GType CGType
g_byte_array_get_type

foreign import ccall haskell_gi_StablePtr_get_type :: CGType

-- | The `GType` for boxed `StablePtr`s.
gtypeStablePtr :: GType
gtypeStablePtr :: GType
gtypeStablePtr = CGType -> GType
GType CGType
haskell_gi_StablePtr_get_type

foreign import ccall haskell_gi_HaskellValue_get_type :: CGType

-- | The `GType` for a generic Haskell value.
gtypeHValue :: GType
gtypeHValue :: GType
gtypeHValue = CGType -> GType
GType CGType
haskell_gi_HaskellValue_get_type

foreign import ccall "g_error_get_type" g_error_get_type :: CGType

-- | The `GType` corresponding to 'Data.GI.Base.GError.GError'.
gtypeError :: GType
gtypeError :: GType
gtypeError = CGType -> GType
GType CGType
g_error_get_type