{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

This section introduces the GVariant type system. It is based, in
large part, on the D-Bus type system, with two major changes and
some minor lifting of restrictions. The
[D-Bus specification](http://dbus.freedesktop.org/doc/dbus-specification.html),
therefore, provides a significant amount of
information that is useful when working with GVariant.

The first major change with respect to the D-Bus type system is the
introduction of maybe (or "nullable") types.  Any type in GVariant can be
converted to a maybe type, in which case, "nothing" (or "null") becomes a
valid value.  Maybe types have been added by introducing the
character "m" to type strings.

The second major change is that the GVariant type system supports the
concept of "indefinite types" -- types that are less specific than
the normal types found in D-Bus.  For example, it is possible to speak
of "an array of any type" in GVariant, where the D-Bus type system
would require you to speak of "an array of integers" or "an array of
strings".  Indefinite types have been added by introducing the
characters "*", "?" and "r" to type strings.

Finally, all arbitrary restrictions relating to the complexity of
types are lifted along with the restriction that dictionary entries
may only appear nested inside of arrays.

Just as in D-Bus, GVariant types are described with strings ("type
strings").  Subject to the differences mentioned above, these strings
are of the same form as those found in DBus.  Note, however: D-Bus
always works in terms of messages and therefore individual type
strings appear nowhere in its interface.  Instead, "signatures"
are a concatenation of the strings of the type of each argument in a
message.  GVariant deals with single values directly so GVariant type
strings always describe the type of exactly one value.  This means
that a D-Bus signature string is generally not a valid GVariant type
string -- except in the case that it is the signature of a message
containing exactly one argument.

An indefinite type is similar in spirit to what may be called an
abstract type in other type systems.  No value can exist that has an
indefinite type as its type, but values can exist that have types
that are subtypes of indefinite types.  That is to say,
g_variant_get_type() will never return an indefinite type, but
calling g_variant_is_of_type() with an indefinite type may return
%TRUE.  For example, you cannot have a value that represents "an
array of no particular type", but you can have an "array of integers"
which certainly matches the type of "an array of no particular type",
since "array of integers" is a subtype of "array of no particular
type".

This is similar to how instances of abstract classes may not
directly exist in other type systems, but instances of their
non-abstract subtypes may.  For example, in GTK, no object that has
the type of #GtkBin can exist (since #GtkBin is an abstract class),
but a #GtkWindow can certainly be instantiated, and you would say
that the #GtkWindow is a #GtkBin (since #GtkWindow is a subclass of
#GtkBin).

## GVariant Type Strings

A GVariant type string can be any of the following:

- any basic type string (listed below)

- "v", "r" or "*"

- one of the characters 'a' or 'm', followed by another type string

- the character '(', followed by a concatenation of zero or more other
  type strings, followed by the character ')'

- the character '{', followed by a basic type string (see below),
  followed by another type string, followed by the character '}'

A basic type string describes a basic type (as per
g_variant_type_is_basic()) and is always a single character in length.
The valid basic type strings are "b", "y", "n", "q", "i", "u", "x", "t",
"h", "d", "s", "o", "g" and "?".

The above definition is recursive to arbitrary depth. "aaaaai" and
"(ui(nq((y)))s)" are both valid type strings, as is
"a(aa(ui)(qna{ya(yd)}))".

The meaning of each of the characters is as follows:
- `b`: the type string of %G_VARIANT_TYPE_BOOLEAN; a boolean value.
- `y`: the type string of %G_VARIANT_TYPE_BYTE; a byte.
- `n`: the type string of %G_VARIANT_TYPE_INT16; a signed 16 bit integer.
- `q`: the type string of %G_VARIANT_TYPE_UINT16; an unsigned 16 bit integer.
- `i`: the type string of %G_VARIANT_TYPE_INT32; a signed 32 bit integer.
- `u`: the type string of %G_VARIANT_TYPE_UINT32; an unsigned 32 bit integer.
- `x`: the type string of %G_VARIANT_TYPE_INT64; a signed 64 bit integer.
- `t`: the type string of %G_VARIANT_TYPE_UINT64; an unsigned 64 bit integer.
- `h`: the type string of %G_VARIANT_TYPE_HANDLE; a signed 32 bit value
  that, by convention, is used as an index into an array of file
  descriptors that are sent alongside a D-Bus message.
- `d`: the type string of %G_VARIANT_TYPE_DOUBLE; a double precision
  floating point value.
- `s`: the type string of %G_VARIANT_TYPE_STRING; a string.
- `o`: the type string of %G_VARIANT_TYPE_OBJECT_PATH; a string in the form
  of a D-Bus object path.
- `g`: the type string of %G_VARIANT_TYPE_STRING; a string in the form of
  a D-Bus type signature.
- `?`: the type string of %G_VARIANT_TYPE_BASIC; an indefinite type that
  is a supertype of any of the basic types.
- `v`: the type string of %G_VARIANT_TYPE_VARIANT; a container type that
  contain any other type of value.
- `a`: used as a prefix on another type string to mean an array of that
  type; the type string "ai", for example, is the type of an array of
  signed 32-bit integers.
- `m`: used as a prefix on another type string to mean a "maybe", or
  "nullable", version of that type; the type string "ms", for example,
  is the type of a value that maybe contains a string, or maybe contains
  nothing.
- `()`: used to enclose zero or more other concatenated type strings to
  create a tuple type; the type string "(is)", for example, is the type of
  a pair of an integer and a string.
- `r`: the type string of %G_VARIANT_TYPE_TUPLE; an indefinite type that is
  a supertype of any tuple type, regardless of the number of items.
- `{}`: used to enclose a basic type string concatenated with another type
  string to create a dictionary entry type, which usually appears inside of
  an array to form a dictionary; the type string "a{sd}", for example, is
  the type of a dictionary that maps strings to double precision floating
  point values.

  The first type (the basic type) is the key type and the second type is
  the value type. The reason that the first type is restricted to being a
  basic type is so that it can easily be hashed.
- `*`: the type string of %G_VARIANT_TYPE_ANY; the indefinite type that is
  a supertype of all types.  Note that, as with all type strings, this
  character represents exactly one type. It cannot be used inside of tuples
  to mean "any number of items".

Any type string of a container that contains an indefinite type is,
itself, an indefinite type. For example, the type string "a*"
(corresponding to %G_VARIANT_TYPE_ARRAY) is an indefinite type
that is a supertype of every array type. "(*s)" is a supertype
of all tuples that contain exactly two items where the second
item is a string.

"a{?*}" is an indefinite type that is a supertype of all arrays
containing dictionary entries where the key is any basic type and
the value is any type at all.  This is, by definition, a dictionary,
so this type string corresponds to %G_VARIANT_TYPE_DICTIONARY. Note
that, due to the restriction that the key of a dictionary entry must
be a basic type, "{**}" is not a valid type string.
-}

module GI.GLib.Structs.VariantType
    ( 

-- * Exported types
    VariantType(..)                         ,
    noVariantType                           ,


 -- * Methods
-- ** variantTypeCopy
    variantTypeCopy                         ,


-- ** variantTypeDupString
    variantTypeDupString                    ,


-- ** variantTypeElement
    variantTypeElement                      ,


-- ** variantTypeEqual
    variantTypeEqual                        ,


-- ** variantTypeFirst
    variantTypeFirst                        ,


-- ** variantTypeFree
    variantTypeFree                         ,


-- ** variantTypeGetStringLength
    variantTypeGetStringLength              ,


-- ** variantTypeHash
    variantTypeHash                         ,


-- ** variantTypeIsArray
    variantTypeIsArray                      ,


-- ** variantTypeIsBasic
    variantTypeIsBasic                      ,


-- ** variantTypeIsContainer
    variantTypeIsContainer                  ,


-- ** variantTypeIsDefinite
    variantTypeIsDefinite                   ,


-- ** variantTypeIsDictEntry
    variantTypeIsDictEntry                  ,


-- ** variantTypeIsMaybe
    variantTypeIsMaybe                      ,


-- ** variantTypeIsSubtypeOf
    variantTypeIsSubtypeOf                  ,


-- ** variantTypeIsTuple
    variantTypeIsTuple                      ,


-- ** variantTypeIsVariant
    variantTypeIsVariant                    ,


-- ** variantTypeKey
    variantTypeKey                          ,


-- ** variantTypeNItems
    variantTypeNItems                       ,


-- ** variantTypeNew
    variantTypeNew                          ,


-- ** variantTypeNewArray
    variantTypeNewArray                     ,


-- ** variantTypeNewDictEntry
    variantTypeNewDictEntry                 ,


-- ** variantTypeNewMaybe
    variantTypeNewMaybe                     ,


-- ** variantTypeNewTuple
    variantTypeNewTuple                     ,


-- ** variantTypeNext
    variantTypeNext                         ,


-- ** variantTypeValue
    variantTypeValue                        ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.GLib.Types
import GI.GLib.Callbacks

newtype VariantType = VariantType (ForeignPtr VariantType)
foreign import ccall "g_variant_type_get_gtype" c_g_variant_type_get_gtype :: 
    IO GType

instance BoxedObject VariantType where
    boxedType _ = c_g_variant_type_get_gtype

noVariantType :: Maybe VariantType
noVariantType = Nothing

-- method VariantType::new
-- method type : Constructor
-- Args : [Arg {argName = "type_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "type_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_new" g_variant_type_new :: 
    CString ->                              -- type_string : TBasicType TUTF8
    IO (Ptr VariantType)


variantTypeNew ::
    (MonadIO m) =>
    T.Text ->                               -- type_string
    m VariantType
variantTypeNew type_string = liftIO $ do
    type_string' <- textToCString type_string
    result <- g_variant_type_new type_string'
    checkUnexpectedReturnNULL "g_variant_type_new" result
    result' <- (wrapBoxed VariantType) result
    freeMem type_string'
    return result'

-- method VariantType::new_array
-- method type : Constructor
-- Args : [Arg {argName = "element", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "element", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_new_array" g_variant_type_new_array :: 
    Ptr VariantType ->                      -- element : TInterface "GLib" "VariantType"
    IO (Ptr VariantType)


variantTypeNewArray ::
    (MonadIO m) =>
    VariantType ->                          -- element
    m VariantType
variantTypeNewArray element = liftIO $ do
    let element' = unsafeManagedPtrGetPtr element
    result <- g_variant_type_new_array element'
    checkUnexpectedReturnNULL "g_variant_type_new_array" result
    result' <- (wrapBoxed VariantType) result
    touchManagedPtr element
    return result'

-- method VariantType::new_dict_entry
-- method type : Constructor
-- Args : [Arg {argName = "key", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "key", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_new_dict_entry" g_variant_type_new_dict_entry :: 
    Ptr VariantType ->                      -- key : TInterface "GLib" "VariantType"
    Ptr VariantType ->                      -- value : TInterface "GLib" "VariantType"
    IO (Ptr VariantType)


variantTypeNewDictEntry ::
    (MonadIO m) =>
    VariantType ->                          -- key
    VariantType ->                          -- value
    m VariantType
variantTypeNewDictEntry key value = liftIO $ do
    let key' = unsafeManagedPtrGetPtr key
    let value' = unsafeManagedPtrGetPtr value
    result <- g_variant_type_new_dict_entry key' value'
    checkUnexpectedReturnNULL "g_variant_type_new_dict_entry" result
    result' <- (wrapBoxed VariantType) result
    touchManagedPtr key
    touchManagedPtr value
    return result'

-- method VariantType::new_maybe
-- method type : Constructor
-- Args : [Arg {argName = "element", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "element", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_new_maybe" g_variant_type_new_maybe :: 
    Ptr VariantType ->                      -- element : TInterface "GLib" "VariantType"
    IO (Ptr VariantType)


variantTypeNewMaybe ::
    (MonadIO m) =>
    VariantType ->                          -- element
    m VariantType
variantTypeNewMaybe element = liftIO $ do
    let element' = unsafeManagedPtrGetPtr element
    result <- g_variant_type_new_maybe element'
    checkUnexpectedReturnNULL "g_variant_type_new_maybe" result
    result' <- (wrapBoxed VariantType) result
    touchManagedPtr element
    return result'

-- method VariantType::new_tuple
-- method type : Constructor
-- Args : [Arg {argName = "items", argType = TCArray False (-1) 1 (TInterface "GLib" "VariantType"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "items", argType = TCArray False (-1) 1 (TInterface "GLib" "VariantType"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_new_tuple" g_variant_type_new_tuple :: 
    Ptr (Ptr VariantType) ->                -- items : TCArray False (-1) 1 (TInterface "GLib" "VariantType")
    Int32 ->                                -- length : TBasicType TInt32
    IO (Ptr VariantType)


variantTypeNewTuple ::
    (MonadIO m) =>
    [VariantType] ->                        -- items
    m VariantType
variantTypeNewTuple items = liftIO $ do
    let length_ = fromIntegral $ length items
    let items' = map unsafeManagedPtrGetPtr items
    items'' <- packPtrArray items'
    result <- g_variant_type_new_tuple items'' length_
    checkUnexpectedReturnNULL "g_variant_type_new_tuple" result
    result' <- (wrapBoxed VariantType) result
    mapM_ touchManagedPtr items
    freeMem items''
    return result'

-- method VariantType::copy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_copy" g_variant_type_copy :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO (Ptr VariantType)


variantTypeCopy ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m VariantType
variantTypeCopy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_copy _obj'
    checkUnexpectedReturnNULL "g_variant_type_copy" result
    result' <- (wrapBoxed VariantType) result
    touchManagedPtr _obj
    return result'

-- method VariantType::dup_string
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_dup_string" g_variant_type_dup_string :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO CString


variantTypeDupString ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m T.Text
variantTypeDupString _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_dup_string _obj'
    checkUnexpectedReturnNULL "g_variant_type_dup_string" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method VariantType::element
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_element" g_variant_type_element :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO (Ptr VariantType)


variantTypeElement ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m VariantType
variantTypeElement _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_element _obj'
    checkUnexpectedReturnNULL "g_variant_type_element" result
    result' <- (newBoxed VariantType) result
    touchManagedPtr _obj
    return result'

-- method VariantType::equal
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type2", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "type2", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_equal" g_variant_type_equal :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    Ptr VariantType ->                      -- type2 : TInterface "GLib" "VariantType"
    IO CInt


variantTypeEqual ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    VariantType ->                          -- type2
    m Bool
variantTypeEqual _obj type2 = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let type2' = unsafeManagedPtrGetPtr type2
    result <- g_variant_type_equal _obj' type2'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr type2
    return result'

-- method VariantType::first
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_first" g_variant_type_first :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO (Ptr VariantType)


variantTypeFirst ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m VariantType
variantTypeFirst _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_first _obj'
    checkUnexpectedReturnNULL "g_variant_type_first" result
    result' <- (newBoxed VariantType) result
    touchManagedPtr _obj
    return result'

-- method VariantType::free
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_free" g_variant_type_free :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO ()


variantTypeFree ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m ()
variantTypeFree _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    g_variant_type_free _obj'
    touchManagedPtr _obj
    return ()

-- method VariantType::get_string_length
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_get_string_length" g_variant_type_get_string_length :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO Word64


variantTypeGetStringLength ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Word64
variantTypeGetStringLength _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_get_string_length _obj'
    touchManagedPtr _obj
    return result

-- method VariantType::hash
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_hash" g_variant_type_hash :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO Word32


variantTypeHash ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Word32
variantTypeHash _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_hash _obj'
    touchManagedPtr _obj
    return result

-- method VariantType::is_array
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_array" g_variant_type_is_array :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO CInt


variantTypeIsArray ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Bool
variantTypeIsArray _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_is_array _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method VariantType::is_basic
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_basic" g_variant_type_is_basic :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO CInt


variantTypeIsBasic ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Bool
variantTypeIsBasic _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_is_basic _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method VariantType::is_container
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_container" g_variant_type_is_container :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO CInt


variantTypeIsContainer ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Bool
variantTypeIsContainer _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_is_container _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method VariantType::is_definite
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_definite" g_variant_type_is_definite :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO CInt


variantTypeIsDefinite ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Bool
variantTypeIsDefinite _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_is_definite _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method VariantType::is_dict_entry
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_dict_entry" g_variant_type_is_dict_entry :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO CInt


variantTypeIsDictEntry ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Bool
variantTypeIsDictEntry _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_is_dict_entry _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method VariantType::is_maybe
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_maybe" g_variant_type_is_maybe :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO CInt


variantTypeIsMaybe ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Bool
variantTypeIsMaybe _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_is_maybe _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method VariantType::is_subtype_of
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "supertype", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "supertype", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_subtype_of" g_variant_type_is_subtype_of :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    Ptr VariantType ->                      -- supertype : TInterface "GLib" "VariantType"
    IO CInt


variantTypeIsSubtypeOf ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    VariantType ->                          -- supertype
    m Bool
variantTypeIsSubtypeOf _obj supertype = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let supertype' = unsafeManagedPtrGetPtr supertype
    result <- g_variant_type_is_subtype_of _obj' supertype'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr supertype
    return result'

-- method VariantType::is_tuple
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_tuple" g_variant_type_is_tuple :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO CInt


variantTypeIsTuple ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Bool
variantTypeIsTuple _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_is_tuple _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method VariantType::is_variant
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_variant" g_variant_type_is_variant :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO CInt


variantTypeIsVariant ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Bool
variantTypeIsVariant _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_is_variant _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method VariantType::key
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_key" g_variant_type_key :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO (Ptr VariantType)


variantTypeKey ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m VariantType
variantTypeKey _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_key _obj'
    checkUnexpectedReturnNULL "g_variant_type_key" result
    result' <- (newBoxed VariantType) result
    touchManagedPtr _obj
    return result'

-- method VariantType::n_items
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_n_items" g_variant_type_n_items :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO Word64


variantTypeNItems ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m Word64
variantTypeNItems _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_n_items _obj'
    touchManagedPtr _obj
    return result

-- method VariantType::next
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_next" g_variant_type_next :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO (Ptr VariantType)


variantTypeNext ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m VariantType
variantTypeNext _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_next _obj'
    checkUnexpectedReturnNULL "g_variant_type_next" result
    result' <- (newBoxed VariantType) result
    touchManagedPtr _obj
    return result'

-- method VariantType::value
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_value" g_variant_type_value :: 
    Ptr VariantType ->                      -- _obj : TInterface "GLib" "VariantType"
    IO (Ptr VariantType)


variantTypeValue ::
    (MonadIO m) =>
    VariantType ->                          -- _obj
    m VariantType
variantTypeValue _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_variant_type_value _obj'
    checkUnexpectedReturnNULL "g_variant_type_value" result
    result' <- (newBoxed VariantType) result
    touchManagedPtr _obj
    return result'