{- |
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
<http://dbus.freedesktop.org/doc/dbus-specification.html D-Bus specification>,
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,
'GI.GLib.Structs.Variant.variantGetType' will never return an indefinite type, but
calling 'GI.GLib.Structs.Variant.variantIsOfType' 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
'GI.GLib.Structs.VariantType.variantTypeIsBasic') 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
-- ** checked_ #method:checked_#
    variantTypeChecked_                     ,


-- ** copy #method:copy#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeCopyMethodInfo               ,
#endif
    variantTypeCopy                         ,


-- ** dupString #method:dupString#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeDupStringMethodInfo          ,
#endif
    variantTypeDupString                    ,


-- ** element #method:element#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeElementMethodInfo            ,
#endif
    variantTypeElement                      ,


-- ** equal #method:equal#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeEqualMethodInfo              ,
#endif
    variantTypeEqual                        ,


-- ** first #method:first#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeFirstMethodInfo              ,
#endif
    variantTypeFirst                        ,


-- ** free #method:free#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeFreeMethodInfo               ,
#endif
    variantTypeFree                         ,


-- ** getStringLength #method:getStringLength#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeGetStringLengthMethodInfo    ,
#endif
    variantTypeGetStringLength              ,


-- ** hash #method:hash#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeHashMethodInfo               ,
#endif
    variantTypeHash                         ,


-- ** isArray #method:isArray#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeIsArrayMethodInfo            ,
#endif
    variantTypeIsArray                      ,


-- ** isBasic #method:isBasic#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeIsBasicMethodInfo            ,
#endif
    variantTypeIsBasic                      ,


-- ** isContainer #method:isContainer#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeIsContainerMethodInfo        ,
#endif
    variantTypeIsContainer                  ,


-- ** isDefinite #method:isDefinite#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeIsDefiniteMethodInfo         ,
#endif
    variantTypeIsDefinite                   ,


-- ** isDictEntry #method:isDictEntry#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeIsDictEntryMethodInfo        ,
#endif
    variantTypeIsDictEntry                  ,


-- ** isMaybe #method:isMaybe#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeIsMaybeMethodInfo            ,
#endif
    variantTypeIsMaybe                      ,


-- ** isSubtypeOf #method:isSubtypeOf#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeIsSubtypeOfMethodInfo        ,
#endif
    variantTypeIsSubtypeOf                  ,


-- ** isTuple #method:isTuple#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeIsTupleMethodInfo            ,
#endif
    variantTypeIsTuple                      ,


-- ** isVariant #method:isVariant#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeIsVariantMethodInfo          ,
#endif
    variantTypeIsVariant                    ,


-- ** key #method:key#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeKeyMethodInfo                ,
#endif
    variantTypeKey                          ,


-- ** nItems #method:nItems#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeNItemsMethodInfo             ,
#endif
    variantTypeNItems                       ,


-- ** new #method:new#
    variantTypeNew                          ,


-- ** newArray #method:newArray#
    variantTypeNewArray                     ,


-- ** newDictEntry #method:newDictEntry#
    variantTypeNewDictEntry                 ,


-- ** newMaybe #method:newMaybe#
    variantTypeNewMaybe                     ,


-- ** newTuple #method:newTuple#
    variantTypeNewTuple                     ,


-- ** next #method:next#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeNextMethodInfo               ,
#endif
    variantTypeNext                         ,


-- ** stringIsValid #method:stringIsValid#
    variantTypeStringIsValid                ,


-- ** stringScan #method:stringScan#
    variantTypeStringScan                   ,


-- ** value #method:value#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    VariantTypeValueMethodInfo              ,
#endif
    variantTypeValue                        ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP


newtype VariantType = VariantType (ManagedPtr 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


#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
instance O.HasAttributeList VariantType
type instance O.AttributeList VariantType = VariantTypeAttributeList
type VariantTypeAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method VariantType::new
-- method type : Constructor
-- Args : [Arg {argCName = "type_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a valid GVariant type string", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "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)

{- |
Creates a new 'GI.GLib.Structs.VariantType.VariantType' corresponding to the type string given
by /@typeString@/.  It is appropriate to call 'GI.GLib.Structs.VariantType.variantTypeFree' on
the return value.

It is a programmer error to call this function with an invalid type
string.  Use 'GI.GLib.Functions.variantTypeStringIsValid' if you are unsure.

@since 2.24
-}
variantTypeNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    {- ^ /@typeString@/: a valid GVariant type string -}
    -> m VariantType
    {- ^ __Returns:__ a new 'GI.GLib.Structs.VariantType.VariantType' -}
variantTypeNew typeString = liftIO $ do
    typeString' <- textToCString typeString
    result <- g_variant_type_new typeString'
    checkUnexpectedReturnNULL "variantTypeNew" result
    result' <- (wrapBoxed VariantType) result
    freeMem typeString'
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method VariantType::new_array
-- method type : Constructor
-- Args : [Arg {argCName = "element", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "VariantType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_new_array" g_variant_type_new_array :: 
    Ptr VariantType ->                      -- element : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr VariantType)

{- |
Constructs the type corresponding to an array of elements of the
type /@type@/.

It is appropriate to call 'GI.GLib.Structs.VariantType.variantTypeFree' on the return value.
-}
variantTypeNewArray ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@element@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m VariantType
    {- ^ __Returns:__ a new array 'GI.GLib.Structs.VariantType.VariantType'

Since 2.24 -}
variantTypeNewArray element = liftIO $ do
    element' <- unsafeManagedPtrGetPtr element
    result <- g_variant_type_new_array element'
    checkUnexpectedReturnNULL "variantTypeNewArray" result
    result' <- (wrapBoxed VariantType) result
    touchManagedPtr element
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method VariantType::new_dict_entry
-- method type : Constructor
-- Args : [Arg {argCName = "key", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a basic #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "value", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "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 (Name {namespace = "GLib", name = "VariantType"})
    Ptr VariantType ->                      -- value : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr VariantType)

{- |
Constructs the type corresponding to a dictionary entry with a key
of type /@key@/ and a value of type /@value@/.

It is appropriate to call 'GI.GLib.Structs.VariantType.variantTypeFree' on the return value.
-}
variantTypeNewDictEntry ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@key@/: a basic 'GI.GLib.Structs.VariantType.VariantType' -}
    -> VariantType
    {- ^ /@value@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m VariantType
    {- ^ __Returns:__ a new dictionary entry 'GI.GLib.Structs.VariantType.VariantType'

Since 2.24 -}
variantTypeNewDictEntry key value = liftIO $ do
    key' <- unsafeManagedPtrGetPtr key
    value' <- unsafeManagedPtrGetPtr value
    result <- g_variant_type_new_dict_entry key' value'
    checkUnexpectedReturnNULL "variantTypeNewDictEntry" result
    result' <- (wrapBoxed VariantType) result
    touchManagedPtr key
    touchManagedPtr value
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method VariantType::new_maybe
-- method type : Constructor
-- Args : [Arg {argCName = "element", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "VariantType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_new_maybe" g_variant_type_new_maybe :: 
    Ptr VariantType ->                      -- element : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr VariantType)

{- |
Constructs the type corresponding to a maybe instance containing
type /@type@/ or Nothing.

It is appropriate to call 'GI.GLib.Structs.VariantType.variantTypeFree' on the return value.
-}
variantTypeNewMaybe ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@element@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m VariantType
    {- ^ __Returns:__ a new maybe 'GI.GLib.Structs.VariantType.VariantType'

Since 2.24 -}
variantTypeNewMaybe element = liftIO $ do
    element' <- unsafeManagedPtrGetPtr element
    result <- g_variant_type_new_maybe element'
    checkUnexpectedReturnNULL "variantTypeNewMaybe" result
    result' <- (wrapBoxed VariantType) result
    touchManagedPtr element
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method VariantType::new_tuple
-- method type : Constructor
-- Args : [Arg {argCName = "items", argType = TCArray False (-1) 1 (TInterface (Name {namespace = "GLib", name = "VariantType"})), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "an array of #GVariantTypes, one for each item", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "length", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the length of @items, or -1", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : [Arg {argCName = "length", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the length of @items, or -1", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "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 (Name {namespace = "GLib", name = "VariantType"}))
    Int32 ->                                -- length : TBasicType TInt
    IO (Ptr VariantType)

{- |
Constructs a new tuple type, from /@items@/.

/@length@/ is the number of items in /@items@/, or -1 to indicate that
/@items@/ is 'Nothing'-terminated.

It is appropriate to call 'GI.GLib.Structs.VariantType.variantTypeFree' on the return value.
-}
variantTypeNewTuple ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [VariantType]
    {- ^ /@items@/: an array of @/GVariantTypes/@, one for each item -}
    -> m VariantType
    {- ^ __Returns:__ a new tuple 'GI.GLib.Structs.VariantType.VariantType'

Since 2.24 -}
variantTypeNewTuple items = liftIO $ do
    let length_ = fromIntegral $ length items
    items' <- mapM unsafeManagedPtrGetPtr items
    items'' <- packPtrArray items'
    result <- g_variant_type_new_tuple items'' length_
    checkUnexpectedReturnNULL "variantTypeNewTuple" result
    result' <- (wrapBoxed VariantType) result
    mapM_ touchManagedPtr items
    freeMem items''
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method VariantType::copy
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "VariantType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_copy" g_variant_type_copy :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr VariantType)

{- |
Makes a copy of a 'GI.GLib.Structs.VariantType.VariantType'.  It is appropriate to call
'GI.GLib.Structs.VariantType.variantTypeFree' on the return value.  /@type@/ may not be 'Nothing'.
-}
variantTypeCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m VariantType
    {- ^ __Returns:__ a new 'GI.GLib.Structs.VariantType.VariantType'

Since 2.24 -}
variantTypeCopy type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_copy type_'
    checkUnexpectedReturnNULL "variantTypeCopy" result
    result' <- (wrapBoxed VariantType) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeCopyMethodInfo
instance (signature ~ (m VariantType), MonadIO m) => O.MethodInfo VariantTypeCopyMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeCopy

#endif

-- method VariantType::dup_string
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_dup_string" g_variant_type_dup_string :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CString

{- |
Returns a newly-allocated copy of the type string corresponding to
/@type@/.  The returned string is nul-terminated.  It is appropriate to
call 'GI.GLib.Functions.free' on the return value.
-}
variantTypeDupString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m T.Text
    {- ^ __Returns:__ the corresponding type string

Since 2.24 -}
variantTypeDupString type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_dup_string type_'
    checkUnexpectedReturnNULL "variantTypeDupString" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeDupStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo VariantTypeDupStringMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeDupString

#endif

-- method VariantType::element
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "an array or maybe #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "VariantType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_element" g_variant_type_element :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr VariantType)

{- |
Determines the element type of an array or maybe type.

This function may only be used with array or maybe types.
-}
variantTypeElement ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: an array or maybe 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m VariantType
    {- ^ __Returns:__ the element type of /@type@/

Since 2.24 -}
variantTypeElement type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_element type_'
    checkUnexpectedReturnNULL "variantTypeElement" result
    result' <- (newBoxed VariantType) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeElementMethodInfo
instance (signature ~ (m VariantType), MonadIO m) => O.MethodInfo VariantTypeElementMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeElement

#endif

-- method VariantType::equal
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type1", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "type2", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_equal" g_variant_type_equal :: 
    Ptr VariantType ->                      -- type1 : TInterface (Name {namespace = "GLib", name = "VariantType"})
    Ptr VariantType ->                      -- type2 : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CInt

{- |
Compares /@type1@/ and /@type2@/ for equality.

Only returns 'True' if the types are exactly equal.  Even if one type
is an indefinite type and the other is a subtype of it, 'False' will
be returned if they are not exactly equal.  If you want to check for
subtypes, use 'GI.GLib.Structs.VariantType.variantTypeIsSubtypeOf'.

The argument types of /@type1@/ and /@type2@/ are only @/gconstpointer/@ to
allow use with 'GI.GLib.Structs.HashTable.HashTable' without function pointer casting.  For
both arguments, a valid 'GI.GLib.Structs.VariantType.VariantType' must be provided.
-}
variantTypeEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type1@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> VariantType
    {- ^ /@type2@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@type1@/ and /@type2@/ are exactly equal

Since 2.24 -}
variantTypeEqual type1 type2 = liftIO $ do
    type1' <- unsafeManagedPtrGetPtr type1
    type2' <- unsafeManagedPtrGetPtr type2
    result <- g_variant_type_equal type1' type2'
    let result' = (/= 0) result
    touchManagedPtr type1
    touchManagedPtr type2
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeEqualMethodInfo
instance (signature ~ (VariantType -> m Bool), MonadIO m) => O.MethodInfo VariantTypeEqualMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeEqual

#endif

-- method VariantType::first
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a tuple or dictionary entry #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "VariantType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_first" g_variant_type_first :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr VariantType)

{- |
Determines the first item type of a tuple or dictionary entry
type.

This function may only be used with tuple or dictionary entry types,
but must not be used with the generic tuple type
@/G_VARIANT_TYPE_TUPLE/@.

In the case of a dictionary entry type, this returns the type of
the key.

'Nothing' is returned in case of /@type@/ being @/G_VARIANT_TYPE_UNIT/@.

This call, together with 'GI.GLib.Structs.VariantType.variantTypeNext' provides an iterator
interface over tuple and dictionary entry types.
-}
variantTypeFirst ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a tuple or dictionary entry 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m VariantType
    {- ^ __Returns:__ the first item type of /@type@/, or 'Nothing'

Since 2.24 -}
variantTypeFirst type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_first type_'
    checkUnexpectedReturnNULL "variantTypeFirst" result
    result' <- (newBoxed VariantType) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeFirstMethodInfo
instance (signature ~ (m VariantType), MonadIO m) => O.MethodInfo VariantTypeFirstMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeFirst

#endif

-- method VariantType::free
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType, or %NULL", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_free" g_variant_type_free :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO ()

{- |
Frees a 'GI.GLib.Structs.VariantType.VariantType' that was allocated with
'GI.GLib.Structs.VariantType.variantTypeCopy', 'GI.GLib.Structs.VariantType.variantTypeNew' or one of the container
type constructor functions.

In the case that /@type@/ is 'Nothing', this function does nothing.

Since 2.24
-}
variantTypeFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType', or 'Nothing' -}
    -> m ()
variantTypeFree type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    g_variant_type_free type_'
    touchManagedPtr type_
    return ()

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo VariantTypeFreeMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeFree

#endif

-- method VariantType::get_string_length
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_get_string_length" g_variant_type_get_string_length :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO Word64

{- |
Returns the length of the type string corresponding to the given
/@type@/.  This function must be used to determine the valid extent of
the memory region returned by @/g_variant_type_peek_string()/@.
-}
variantTypeGetStringLength ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Word64
    {- ^ __Returns:__ the length of the corresponding type string

Since 2.24 -}
variantTypeGetStringLength type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_get_string_length type_'
    touchManagedPtr type_
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeGetStringLengthMethodInfo
instance (signature ~ (m Word64), MonadIO m) => O.MethodInfo VariantTypeGetStringLengthMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeGetStringLength

#endif

-- method VariantType::hash
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_hash" g_variant_type_hash :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO Word32

{- |
Hashes /@type@/.

The argument type of /@type@/ is only @/gconstpointer/@ to allow use with
'GI.GLib.Structs.HashTable.HashTable' without function pointer casting.  A valid
'GI.GLib.Structs.VariantType.VariantType' must be provided.
-}
variantTypeHash ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Word32
    {- ^ __Returns:__ the hash value

Since 2.24 -}
variantTypeHash type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_hash type_'
    touchManagedPtr type_
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeHashMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo VariantTypeHashMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeHash

#endif

-- method VariantType::is_array
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_array" g_variant_type_is_array :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CInt

{- |
Determines if the given /@type@/ is an array type.  This is true if the
type string for /@type@/ starts with an \'a\'.

This function returns 'True' for any indefinite type for which every
definite subtype is an array type -- @/G_VARIANT_TYPE_ARRAY/@, for
example.
-}
variantTypeIsArray ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@type@/ is an array type

Since 2.24 -}
variantTypeIsArray type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_is_array type_'
    let result' = (/= 0) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeIsArrayMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo VariantTypeIsArrayMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeIsArray

#endif

-- method VariantType::is_basic
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_basic" g_variant_type_is_basic :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CInt

{- |
Determines if the given /@type@/ is a basic type.

Basic types are booleans, bytes, integers, doubles, strings, object
paths and signatures.

Only a basic type may be used as the key of a dictionary entry.

This function returns 'False' for all indefinite types except
@/G_VARIANT_TYPE_BASIC/@.
-}
variantTypeIsBasic ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@type@/ is a basic type

Since 2.24 -}
variantTypeIsBasic type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_is_basic type_'
    let result' = (/= 0) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeIsBasicMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo VariantTypeIsBasicMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeIsBasic

#endif

-- method VariantType::is_container
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_container" g_variant_type_is_container :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CInt

{- |
Determines if the given /@type@/ is a container type.

Container types are any array, maybe, tuple, or dictionary
entry types plus the variant type.

This function returns 'True' for any indefinite type for which every
definite subtype is a container -- @/G_VARIANT_TYPE_ARRAY/@, for
example.
-}
variantTypeIsContainer ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@type@/ is a container type

Since 2.24 -}
variantTypeIsContainer type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_is_container type_'
    let result' = (/= 0) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeIsContainerMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo VariantTypeIsContainerMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeIsContainer

#endif

-- method VariantType::is_definite
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_definite" g_variant_type_is_definite :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CInt

{- |
Determines if the given /@type@/ is definite (ie: not indefinite).

A type is definite if its type string does not contain any indefinite
type characters (\'*\', \'?\', or \'r\').

A 'GVariant' instance may not have an indefinite type, so calling
this function on the result of 'GI.GLib.Structs.Variant.variantGetType' will always
result in 'True' being returned.  Calling this function on an
indefinite type like @/G_VARIANT_TYPE_ARRAY/@, however, will result in
'False' being returned.
-}
variantTypeIsDefinite ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@type@/ is definite

Since 2.24 -}
variantTypeIsDefinite type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_is_definite type_'
    let result' = (/= 0) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeIsDefiniteMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo VariantTypeIsDefiniteMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeIsDefinite

#endif

-- method VariantType::is_dict_entry
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_dict_entry" g_variant_type_is_dict_entry :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CInt

{- |
Determines if the given /@type@/ is a dictionary entry type.  This is
true if the type string for /@type@/ starts with a \'{\'.

This function returns 'True' for any indefinite type for which every
definite subtype is a dictionary entry type --
@/G_VARIANT_TYPE_DICT_ENTRY/@, for example.
-}
variantTypeIsDictEntry ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@type@/ is a dictionary entry type

Since 2.24 -}
variantTypeIsDictEntry type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_is_dict_entry type_'
    let result' = (/= 0) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeIsDictEntryMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo VariantTypeIsDictEntryMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeIsDictEntry

#endif

-- method VariantType::is_maybe
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_maybe" g_variant_type_is_maybe :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CInt

{- |
Determines if the given /@type@/ is a maybe type.  This is true if the
type string for /@type@/ starts with an \'m\'.

This function returns 'True' for any indefinite type for which every
definite subtype is a maybe type -- @/G_VARIANT_TYPE_MAYBE/@, for
example.
-}
variantTypeIsMaybe ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@type@/ is a maybe type

Since 2.24 -}
variantTypeIsMaybe type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_is_maybe type_'
    let result' = (/= 0) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeIsMaybeMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo VariantTypeIsMaybeMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeIsMaybe

#endif

-- method VariantType::is_subtype_of
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "supertype", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_subtype_of" g_variant_type_is_subtype_of :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    Ptr VariantType ->                      -- supertype : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CInt

{- |
Checks if /@type@/ is a subtype of /@supertype@/.

This function returns 'True' if /@type@/ is a subtype of /@supertype@/.  All
types are considered to be subtypes of themselves.  Aside from that,
only indefinite types can have subtypes.
-}
variantTypeIsSubtypeOf ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> VariantType
    {- ^ /@supertype@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@type@/ is a subtype of /@supertype@/

Since 2.24 -}
variantTypeIsSubtypeOf type_ supertype = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    supertype' <- unsafeManagedPtrGetPtr supertype
    result <- g_variant_type_is_subtype_of type_' supertype'
    let result' = (/= 0) result
    touchManagedPtr type_
    touchManagedPtr supertype
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeIsSubtypeOfMethodInfo
instance (signature ~ (VariantType -> m Bool), MonadIO m) => O.MethodInfo VariantTypeIsSubtypeOfMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeIsSubtypeOf

#endif

-- method VariantType::is_tuple
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_tuple" g_variant_type_is_tuple :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CInt

{- |
Determines if the given /@type@/ is a tuple type.  This is true if the
type string for /@type@/ starts with a \'(\' or if /@type@/ is
@/G_VARIANT_TYPE_TUPLE/@.

This function returns 'True' for any indefinite type for which every
definite subtype is a tuple type -- @/G_VARIANT_TYPE_TUPLE/@, for
example.
-}
variantTypeIsTuple ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@type@/ is a tuple type

Since 2.24 -}
variantTypeIsTuple type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_is_tuple type_'
    let result' = (/= 0) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeIsTupleMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo VariantTypeIsTupleMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeIsTuple

#endif

-- method VariantType::is_variant
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_is_variant" g_variant_type_is_variant :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO CInt

{- |
Determines if the given /@type@/ is the variant type.
-}
variantTypeIsVariant ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@type@/ is the variant type

Since 2.24 -}
variantTypeIsVariant type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_is_variant type_'
    let result' = (/= 0) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeIsVariantMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo VariantTypeIsVariantMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeIsVariant

#endif

-- method VariantType::key
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a dictionary entry #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "VariantType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_key" g_variant_type_key :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr VariantType)

{- |
Determines the key type of a dictionary entry type.

This function may only be used with a dictionary entry type.  Other
than the additional restriction, this call is equivalent to
'GI.GLib.Structs.VariantType.variantTypeFirst'.
-}
variantTypeKey ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a dictionary entry 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m VariantType
    {- ^ __Returns:__ the key type of the dictionary entry

Since 2.24 -}
variantTypeKey type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_key type_'
    checkUnexpectedReturnNULL "variantTypeKey" result
    result' <- (newBoxed VariantType) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeKeyMethodInfo
instance (signature ~ (m VariantType), MonadIO m) => O.MethodInfo VariantTypeKeyMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeKey

#endif

-- method VariantType::n_items
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a tuple or dictionary entry #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_n_items" g_variant_type_n_items :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO Word64

{- |
Determines the number of items contained in a tuple or
dictionary entry type.

This function may only be used with tuple or dictionary entry types,
but must not be used with the generic tuple type
@/G_VARIANT_TYPE_TUPLE/@.

In the case of a dictionary entry type, this function will always
return 2.
-}
variantTypeNItems ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a tuple or dictionary entry 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m Word64
    {- ^ __Returns:__ the number of items in /@type@/

Since 2.24 -}
variantTypeNItems type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_n_items type_'
    touchManagedPtr type_
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeNItemsMethodInfo
instance (signature ~ (m Word64), MonadIO m) => O.MethodInfo VariantTypeNItemsMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeNItems

#endif

-- method VariantType::next
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GVariantType from a previous call", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "VariantType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_next" g_variant_type_next :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr VariantType)

{- |
Determines the next item type of a tuple or dictionary entry
type.

/@type@/ must be the result of a previous call to
'GI.GLib.Structs.VariantType.variantTypeFirst' or 'GI.GLib.Structs.VariantType.variantTypeNext'.

If called on the key type of a dictionary entry then this call
returns the value type.  If called on the value type of a dictionary
entry then this call returns 'Nothing'.

For tuples, 'Nothing' is returned when /@type@/ is the last item in a tuple.
-}
variantTypeNext ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a 'GI.GLib.Structs.VariantType.VariantType' from a previous call -}
    -> m VariantType
    {- ^ __Returns:__ the next 'GI.GLib.Structs.VariantType.VariantType' after /@type@/, or 'Nothing'

Since 2.24 -}
variantTypeNext type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_next type_'
    checkUnexpectedReturnNULL "variantTypeNext" result
    result' <- (newBoxed VariantType) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeNextMethodInfo
instance (signature ~ (m VariantType), MonadIO m) => O.MethodInfo VariantTypeNextMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeNext

#endif

-- method VariantType::value
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "type", argType = TInterface (Name {namespace = "GLib", name = "VariantType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a dictionary entry #GVariantType", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "VariantType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_value" g_variant_type_value :: 
    Ptr VariantType ->                      -- type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr VariantType)

{- |
Determines the value type of a dictionary entry type.

This function may only be used with a dictionary entry type.
-}
variantTypeValue ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantType
    {- ^ /@type@/: a dictionary entry 'GI.GLib.Structs.VariantType.VariantType' -}
    -> m VariantType
    {- ^ __Returns:__ the value type of the dictionary entry

Since 2.24 -}
variantTypeValue type_ = liftIO $ do
    type_' <- unsafeManagedPtrGetPtr type_
    result <- g_variant_type_value type_'
    checkUnexpectedReturnNULL "variantTypeValue" result
    result' <- (newBoxed VariantType) result
    touchManagedPtr type_
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data VariantTypeValueMethodInfo
instance (signature ~ (m VariantType), MonadIO m) => O.MethodInfo VariantTypeValueMethodInfo VariantType signature where
    overloadedMethod _ = variantTypeValue

#endif

-- method VariantType::checked_
-- method type : MemberFunction
-- Args : [Arg {argCName = "arg0", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "VariantType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_checked_" g_variant_type_checked_ :: 
    CString ->                              -- arg0 : TBasicType TUTF8
    IO (Ptr VariantType)

{- |
/No description available in the introspection data./
-}
variantTypeChecked_ ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -> m VariantType
variantTypeChecked_ arg0 = liftIO $ do
    arg0' <- textToCString arg0
    result <- g_variant_type_checked_ arg0'
    checkUnexpectedReturnNULL "variantTypeChecked_" result
    result' <- (newBoxed VariantType) result
    freeMem arg0'
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method VariantType::string_is_valid
-- method type : MemberFunction
-- Args : [Arg {argCName = "type_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a pointer to any string", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_string_is_valid" g_variant_type_string_is_valid :: 
    CString ->                              -- type_string : TBasicType TUTF8
    IO CInt

{- |
Checks if /@typeString@/ is a valid GVariant type string.  This call is
equivalent to calling 'GI.GLib.Functions.variantTypeStringScan' and confirming
that the following character is a nul terminator.
-}
variantTypeStringIsValid ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    {- ^ /@typeString@/: a pointer to any string -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@typeString@/ is exactly one valid type string

Since 2.24 -}
variantTypeStringIsValid typeString = liftIO $ do
    typeString' <- textToCString typeString
    result <- g_variant_type_string_is_valid typeString'
    let result' = (/= 0) result
    freeMem typeString'
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method VariantType::string_scan
-- method type : MemberFunction
-- Args : [Arg {argCName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a pointer to any string", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "limit", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "the end of @string, or %NULL", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "endptr", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "location to store the end pointer, or %NULL", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_string_scan" g_variant_type_string_scan :: 
    CString ->                              -- string : TBasicType TUTF8
    CString ->                              -- limit : TBasicType TUTF8
    Ptr CString ->                          -- endptr : TBasicType TUTF8
    IO CInt

{- |
Scan for a single complete and valid GVariant type string in /@string@/.
The memory pointed to by /@limit@/ (or bytes beyond it) is never
accessed.

If a valid type string is found, /@endptr@/ is updated to point to the
first character past the end of the string that was found and 'True'
is returned.

If there is no valid type string starting at /@string@/, or if the type
string does not end before /@limit@/ then 'False' is returned.

For the simple case of checking if a string is a valid type string,
see 'GI.GLib.Functions.variantTypeStringIsValid'.

@since 2.24
-}
variantTypeStringScan ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    {- ^ /@string@/: a pointer to any string -}
    -> Maybe (T.Text)
    {- ^ /@limit@/: the end of /@string@/, or 'Nothing' -}
    -> m ((Bool, T.Text))
    {- ^ __Returns:__ 'True' if a valid type string was found -}
variantTypeStringScan string limit = liftIO $ do
    string' <- textToCString string
    maybeLimit <- case limit of
        Nothing -> return nullPtr
        Just jLimit -> do
            jLimit' <- textToCString jLimit
            return jLimit'
    endptr <- allocMem :: IO (Ptr CString)
    result <- g_variant_type_string_scan string' maybeLimit endptr
    let result' = (/= 0) result
    endptr' <- peek endptr
    endptr'' <- cstringToText endptr'
    freeMem endptr'
    freeMem string'
    freeMem maybeLimit
    freeMem endptr
    return (result', endptr'')

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
type family ResolveVariantTypeMethod (t :: Symbol) (o :: *) :: * where
    ResolveVariantTypeMethod "copy" o = VariantTypeCopyMethodInfo
    ResolveVariantTypeMethod "dupString" o = VariantTypeDupStringMethodInfo
    ResolveVariantTypeMethod "element" o = VariantTypeElementMethodInfo
    ResolveVariantTypeMethod "equal" o = VariantTypeEqualMethodInfo
    ResolveVariantTypeMethod "first" o = VariantTypeFirstMethodInfo
    ResolveVariantTypeMethod "free" o = VariantTypeFreeMethodInfo
    ResolveVariantTypeMethod "hash" o = VariantTypeHashMethodInfo
    ResolveVariantTypeMethod "isArray" o = VariantTypeIsArrayMethodInfo
    ResolveVariantTypeMethod "isBasic" o = VariantTypeIsBasicMethodInfo
    ResolveVariantTypeMethod "isContainer" o = VariantTypeIsContainerMethodInfo
    ResolveVariantTypeMethod "isDefinite" o = VariantTypeIsDefiniteMethodInfo
    ResolveVariantTypeMethod "isDictEntry" o = VariantTypeIsDictEntryMethodInfo
    ResolveVariantTypeMethod "isMaybe" o = VariantTypeIsMaybeMethodInfo
    ResolveVariantTypeMethod "isSubtypeOf" o = VariantTypeIsSubtypeOfMethodInfo
    ResolveVariantTypeMethod "isTuple" o = VariantTypeIsTupleMethodInfo
    ResolveVariantTypeMethod "isVariant" o = VariantTypeIsVariantMethodInfo
    ResolveVariantTypeMethod "key" o = VariantTypeKeyMethodInfo
    ResolveVariantTypeMethod "nItems" o = VariantTypeNItemsMethodInfo
    ResolveVariantTypeMethod "next" o = VariantTypeNextMethodInfo
    ResolveVariantTypeMethod "value" o = VariantTypeValueMethodInfo
    ResolveVariantTypeMethod "getStringLength" o = VariantTypeGetStringLengthMethodInfo
    ResolveVariantTypeMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveVariantTypeMethod t VariantType, O.MethodInfo info VariantType p) => O.IsLabelProxy t (VariantType -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveVariantTypeMethod t VariantType, O.MethodInfo info VariantType p) => O.IsLabel t (VariantType -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif

#endif