{-# LINE 1 "Data/GI/Base/GType.hsc" #-}
-- | Basic `GType`s.
module Data.GI.Base.GType
    ( GType(..)
    , CGType

    , gtypeName

    , gtypeString
    , gtypePointer
    , gtypeInt
    , gtypeUInt
    , gtypeLong
    , gtypeULong
    , gtypeInt64
    , gtypeUInt64
    , gtypeFloat
    , gtypeDouble
    , gtypeBoolean
    , gtypeGType
    , gtypeStrv
    , gtypeBoxed
    , gtypeObject
    , gtypeVariant
    , gtypeByteArray
    , gtypeInvalid
    ) where

import Data.Word
import Foreign.C.String (CString, peekCString)



-- | A type identifier in the GLib type system. This is the low-level
-- type associated with the representation in memory, when using this
-- on the Haskell side use `GType` below.
type CGType = Word64
{-# LINE 37 "Data/GI/Base/GType.hsc" #-}

-- | A newtype for use on the haskell side.
newtype GType = GType {gtypeToCGType :: CGType}

foreign import ccall "g_type_name" g_type_name :: GType -> IO CString

-- | Get the name assigned to the given `GType`.
gtypeName :: GType -> IO String
gtypeName gtype = g_type_name gtype >>= peekCString

{-| [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 64
{-# LINE 66 "Data/GI/Base/GType.hsc" #-}

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

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

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

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

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

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

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

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

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

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

-- | `GType` corresponding to a `BoxedObject`.
gtypeBoxed :: GType
gtypeBoxed = GType 72
{-# LINE 110 "Data/GI/Base/GType.hsc" #-}

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

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

-- | The `GType` corresponding to a `GVariant`.
gtypeVariant :: GType
gtypeVariant = GType 84
{-# LINE 123 "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 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 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 g_byte_array_get_type