{-# LINE 1 "src/Data/GI/Base/BasicTypes.hsc" #-}
{-# LANGUAGE ConstraintKinds, FlexibleContexts, FlexibleInstances,
{-# LINE 2 "src/Data/GI/Base/BasicTypes.hsc" #-}
  DeriveDataTypeable #-}
-- | Basic types used in the bindings.
module Data.GI.Base.BasicTypes
    (
      -- * GType related
      GType(..)
    , CGType

    , gtypeName

    , gtypeString
    , gtypePointer
    , gtypeInt32
    , gtypeUInt32
    , gtypeInt64
    , gtypeUInt64
    , gtypeFloat
    , gtypeDouble
    , gtypeBoolean
    , gtypeGType
    , gtypeStrv
    , gtypeBoxed
    , gtypeObject

     -- * Memory management

    , ForeignPtrNewtype
    , BoxedObject(..)
    , BoxedEnum(..)
    , GObject(..)
    , UnexpectedNullPointerReturn(..)

    -- * Basic GLib \/ GObject types
    , GVariant(..)
    , GParamSpec(..)

    , GArray(..)
    , GPtrArray(..)
    , GByteArray(..)
    , GHashTable(..)
    , GList(..)
    , g_list_free
    , GSList(..)
    , g_slist_free

    , IsGFlag

    , PtrWrapped(..)
    , GDestroyNotify
    ) where

import Control.Exception (Exception)
import Data.Coerce (Coercible)
import qualified Data.Text as T
import Data.Typeable (Typeable)
import Data.Word
import Foreign.Ptr (Ptr, FunPtr)
import Foreign.ForeignPtr (ForeignPtr)
import Foreign.C.String (CString, peekCString)


{-# LINE 63 "src/Data/GI/Base/BasicTypes.hsc" #-}

-- | 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 68 "src/Data/GI/Base/BasicTypes.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

-- | `GType` of strings.
gtypeString :: GType
gtypeString = GType 64
{-# LINE 81 "src/Data/GI/Base/BasicTypes.hsc" #-}

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

-- | `GType` for signed integers.
gtypeInt32 :: GType
gtypeInt32 = GType 24
{-# LINE 89 "src/Data/GI/Base/BasicTypes.hsc" #-}

-- | `GType` for unsigned integers.
gtypeUInt32 :: GType
gtypeUInt32 = GType 28
{-# LINE 93 "src/Data/GI/Base/BasicTypes.hsc" #-}

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

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

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

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

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

-- | `GType` corresponding to a `GType` itself.
gtypeGType :: GType
gtypeGType = GType 26335536
{-# LINE 117 "src/Data/GI/Base/BasicTypes.hsc" #-}

-- | `GType` for a NULL terminated array of strings.
gtypeStrv :: GType
gtypeStrv = GType 26340688
{-# LINE 121 "src/Data/GI/Base/BasicTypes.hsc" #-}

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

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

-- | A constraint ensuring that the given type is coercible to a
-- ForeignPtr. It will hold for newtypes of the form
--
-- > newtype Foo = Foo (ForeignPtr Foo)
--
-- which is the typical shape of wrapped 'GObject's.
type ForeignPtrNewtype a = Coercible a (ForeignPtr ())
-- Notice that the Coercible here is to ForeignPtr (), instead of
-- "ForeignPtr a", which would be the most natural thing. Both are
-- representationally equivalent, so this is not a big deal. This is
-- to work around a problem in ghc 7.10:
-- https://ghc.haskell.org/trac/ghc/ticket/10715

-- | Wrapped boxed structures, identified by their `GType`.
class ForeignPtrNewtype a => BoxedObject a where
    boxedType :: a -> IO GType -- This should not use the value of its
                               -- argument.

-- | Enums with an associated `GType`.
class BoxedEnum a where
    boxedEnumType :: a -> IO GType

-- | A wrapped `GObject`.
class ForeignPtrNewtype a => GObject a where
    -- | Whether the `GObject` is a descendent of <https://developer.gnome.org/gobject/stable/gobject-The-Base-Object-Type.html#GInitiallyUnowned GInitiallyUnowned>.
    gobjectIsInitiallyUnowned :: a -> Bool
    -- | The `GType` for this object.
    gobjectType :: a -> IO GType

-- | A common omission in the introspection data is missing (nullable)
-- annotations for return types, when they clearly are nullable. (A
-- common idiom is "Returns: valid value, or %NULL if something went
-- wrong.")
--
-- Haskell wrappers will raise this exception if the return value is
-- an unexpected `Foreign.Ptr.nullPtr`.
data UnexpectedNullPointerReturn =
    UnexpectedNullPointerReturn { nullPtrErrorMsg :: T.Text }
                                deriving (Show, Typeable)

instance Exception UnexpectedNullPointerReturn

-- | A <https://developer.gnome.org/glib/stable/glib-GVariant.html GVariant>. See "Data.GI.Base.GVariant" for further methods.
newtype GVariant = GVariant (ForeignPtr GVariant)

-- | A <https://developer.gnome.org/gobject/stable/gobject-GParamSpec.html GParamSpec>. See "Data.GI.Base.GParamSpec" for further methods.
newtype GParamSpec = GParamSpec (ForeignPtr GParamSpec)

-- | An enum usable as a flag for a function.
class Enum a => IsGFlag a

-- | A <https://developer.gnome.org/glib/stable/glib-Arrays.html GArray>. Marshalling for this type is done in "Data.GI.Base.BasicConversions", it is mapped to a list on the Haskell side.
data GArray a = GArray (Ptr (GArray a))

-- | A <https://developer.gnome.org/glib/stable/glib-Pointer-Arrays.html GPtrArray>. Marshalling for this type is done in "Data.GI.Base.BasicConversions", it is mapped to a list on the Haskell side.
data GPtrArray a = GPtrArray (Ptr (GPtrArray a))

-- | A <https://developer.gnome.org/glib/stable/glib-Byte-Arrays.html GByteArray>. Marshalling for this type is done in "Data.GI.Base.BasicConversions", it is packed to a 'Data.ByteString.ByteString' on the Haskell side.
data GByteArray = GByteArray (Ptr GByteArray)

-- | A <https://developer.gnome.org/glib/stable/glib-Hash-Tables.html GHashTable>. It is mapped to a 'Data.Map.Map' on the Haskell side.
data GHashTable a b = GHashTable (Ptr (GHashTable a b))

-- | A <https://developer.gnome.org/glib/stable/glib-Doubly-Linked-Lists.html GList>, mapped to a list on the Haskell side. Marshalling is done in "Data.GI.Base.BasicConversions".
data GList a = GList (Ptr (GList a))

-- | A <https://developer.gnome.org/glib/stable/glib-Singly-Linked-Lists.html GSList>, mapped to a list on the Haskell side. Marshalling is done in "Data.GI.Base.BasicConversions".
data GSList a = GSList (Ptr (GSList a))

-- | Some APIs, such as `GHashTable`, pass around scalar types
-- wrapped into a pointer. We encode such a type as follows.
newtype PtrWrapped a = PtrWrapped {unwrapPtr :: Ptr a}

-- | Destroy the memory associated with a given pointer.
type GDestroyNotify a = FunPtr (Ptr a -> IO ())

-- | Free the given 'GList'.
foreign import ccall "g_list_free" g_list_free ::
    Ptr (GList a) -> IO ()

-- | Free the given 'GSList'.
foreign import ccall "g_slist_free" g_slist_free ::
    Ptr (GSList a) -> IO ()