{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.GLib.Structs.VariantDict.VariantDict' is a mutable interface to t'GVariant' dictionaries.
-- 
-- It can be used for doing a sequence of dictionary lookups in an
-- efficient way on an existing t'GVariant' dictionary or it can be used
-- to construct new dictionaries with a hashtable-like interface.  It
-- can also be used for taking existing dictionaries and modifying them
-- in order to create new ones.
-- 
-- t'GI.GLib.Structs.VariantDict.VariantDict' can only be used with @/G_VARIANT_TYPE_VARDICT/@
-- dictionaries.
-- 
-- It is possible to use t'GI.GLib.Structs.VariantDict.VariantDict' allocated on the stack or on the
-- heap.  When using a stack-allocated t'GI.GLib.Structs.VariantDict.VariantDict', you begin with a
-- call to @/g_variant_dict_init()/@ and free the resources with a call to
-- 'GI.GLib.Structs.VariantDict.variantDictClear'.
-- 
-- Heap-allocated t'GI.GLib.Structs.VariantDict.VariantDict' follows normal refcounting rules: you
-- allocate it with 'GI.GLib.Structs.VariantDict.variantDictNew' and use 'GI.GLib.Structs.VariantDict.variantDictRef'
-- and 'GI.GLib.Structs.VariantDict.variantDictUnref'.
-- 
-- 'GI.GLib.Structs.VariantDict.variantDictEnd' is used to convert the t'GI.GLib.Structs.VariantDict.VariantDict' back into a
-- dictionary-type t'GVariant'.  When used with stack-allocated instances,
-- this also implicitly frees all associated memory, but for
-- heap-allocated instances, you must still call 'GI.GLib.Structs.VariantDict.variantDictUnref'
-- afterwards.
-- 
-- You will typically want to use a heap-allocated t'GI.GLib.Structs.VariantDict.VariantDict' when
-- you expose it as part of an API.  For most other uses, the
-- stack-allocated form will be more convenient.
-- 
-- Consider the following two examples that do the same thing in each
-- style: take an existing dictionary and look up the \"count\" uint32
-- key, adding 1 to it if it is found, or returning an error if the
-- key is not found.  Each returns the new dictionary as a floating
-- t'GVariant'.
-- 
-- == Using a stack-allocated GVariantDict
-- 
-- 
-- === /C code/
-- >
-- >  GVariant *
-- >  add_to_count (GVariant  *orig,
-- >                GError   **error)
-- >  {
-- >    GVariantDict dict;
-- >    guint32 count;
-- >
-- >    g_variant_dict_init (&dict, orig);
-- >    if (!g_variant_dict_lookup (&dict, "count", "u", &count))
-- >      {
-- >        g_set_error (...);
-- >        g_variant_dict_clear (&dict);
-- >        return NULL;
-- >      }
-- >
-- >    g_variant_dict_insert (&dict, "count", "u", count + 1);
-- >
-- >    return g_variant_dict_end (&dict);
-- >  }
-- 
-- 
-- == Using heap-allocated GVariantDict
-- 
-- 
-- === /C code/
-- >
-- >  GVariant *
-- >  add_to_count (GVariant  *orig,
-- >                GError   **error)
-- >  {
-- >    GVariantDict *dict;
-- >    GVariant *result;
-- >    guint32 count;
-- >
-- >    dict = g_variant_dict_new (orig);
-- >
-- >    if (g_variant_dict_lookup (dict, "count", "u", &count))
-- >      {
-- >        g_variant_dict_insert (dict, "count", "u", count + 1);
-- >        result = g_variant_dict_end (dict);
-- >      }
-- >    else
-- >      {
-- >        g_set_error (...);
-- >        result = NULL;
-- >      }
-- >
-- >    g_variant_dict_unref (dict);
-- >
-- >    return result;
-- >  }
-- 
-- 
-- /Since: 2.40/

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.GLib.Structs.VariantDict
    ( 

-- * Exported types
    VariantDict(..)                         ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveVariantDictMethod                ,
#endif


-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    VariantDictClearMethodInfo              ,
#endif
    variantDictClear                        ,


-- ** contains #method:contains#

#if defined(ENABLE_OVERLOADING)
    VariantDictContainsMethodInfo           ,
#endif
    variantDictContains                     ,


-- ** end #method:end#

#if defined(ENABLE_OVERLOADING)
    VariantDictEndMethodInfo                ,
#endif
    variantDictEnd                          ,


-- ** insertValue #method:insertValue#

#if defined(ENABLE_OVERLOADING)
    VariantDictInsertValueMethodInfo        ,
#endif
    variantDictInsertValue                  ,


-- ** lookupValue #method:lookupValue#

#if defined(ENABLE_OVERLOADING)
    VariantDictLookupValueMethodInfo        ,
#endif
    variantDictLookupValue                  ,


-- ** new #method:new#

    variantDictNew                          ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    VariantDictRefMethodInfo                ,
#endif
    variantDictRef                          ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    VariantDictRemoveMethodInfo             ,
#endif
    variantDictRemove                       ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    VariantDictUnrefMethodInfo              ,
#endif
    variantDictUnref                        ,




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
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
import qualified GHC.OverloadedLabels as OL

import {-# SOURCE #-} qualified GI.GLib.Structs.VariantType as GLib.VariantType

-- | Memory-managed wrapper type.
newtype VariantDict = VariantDict (SP.ManagedPtr VariantDict)
    deriving (VariantDict -> VariantDict -> Bool
(VariantDict -> VariantDict -> Bool)
-> (VariantDict -> VariantDict -> Bool) -> Eq VariantDict
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariantDict -> VariantDict -> Bool
$c/= :: VariantDict -> VariantDict -> Bool
== :: VariantDict -> VariantDict -> Bool
$c== :: VariantDict -> VariantDict -> Bool
Eq)

instance SP.ManagedPtrNewtype VariantDict where
    toManagedPtr :: VariantDict -> ManagedPtr VariantDict
toManagedPtr (VariantDict ManagedPtr VariantDict
p) = ManagedPtr VariantDict
p

foreign import ccall "g_variant_dict_get_type" c_g_variant_dict_get_type :: 
    IO GType

type instance O.ParentTypes VariantDict = '[]
instance O.HasParentTypes VariantDict

instance B.Types.TypedObject VariantDict where
    glibType :: IO GType
glibType = IO GType
c_g_variant_dict_get_type

instance B.Types.GBoxed VariantDict

-- | Convert 'VariantDict' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue VariantDict where
    toGValue :: VariantDict -> IO GValue
toGValue VariantDict
o = do
        GType
gtype <- IO GType
c_g_variant_dict_get_type
        VariantDict -> (Ptr VariantDict -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr VariantDict
o (GType
-> (GValue -> Ptr VariantDict -> IO ())
-> Ptr VariantDict
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr VariantDict -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO VariantDict
fromGValue GValue
gv = do
        Ptr VariantDict
ptr <- GValue -> IO (Ptr VariantDict)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr VariantDict)
        (ManagedPtr VariantDict -> VariantDict)
-> Ptr VariantDict -> IO VariantDict
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr VariantDict -> VariantDict
VariantDict Ptr VariantDict
ptr
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList VariantDict
type instance O.AttributeList VariantDict = VariantDictAttributeList
type VariantDictAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method VariantDict::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "from_asv"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GVariant with which to initialise the\n  dictionary"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GLib" , name = "VariantDict" })
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_dict_new" g_variant_dict_new :: 
    Ptr GVariant ->                         -- from_asv : TVariant
    IO (Ptr VariantDict)

-- | Allocates and initialises a new t'GI.GLib.Structs.VariantDict.VariantDict'.
-- 
-- You should call 'GI.GLib.Structs.VariantDict.variantDictUnref' on the return value when it
-- is no longer needed.  The memory will not be automatically freed by
-- any other call.
-- 
-- In some cases it may be easier to place a t'GI.GLib.Structs.VariantDict.VariantDict' directly on
-- the stack of the calling function and initialise it with
-- @/g_variant_dict_init()/@.  This is particularly useful when you are
-- using t'GI.GLib.Structs.VariantDict.VariantDict' to construct a t'GVariant'.
-- 
-- /Since: 2.40/
variantDictNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (GVariant)
    -- ^ /@fromAsv@/: the t'GVariant' with which to initialise the
    --   dictionary
    -> m VariantDict
    -- ^ __Returns:__ a t'GI.GLib.Structs.VariantDict.VariantDict'
variantDictNew :: Maybe GVariant -> m VariantDict
variantDictNew Maybe GVariant
fromAsv = IO VariantDict -> m VariantDict
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VariantDict -> m VariantDict)
-> IO VariantDict -> m VariantDict
forall a b. (a -> b) -> a -> b
$ do
    Ptr GVariant
maybeFromAsv <- case Maybe GVariant
fromAsv of
        Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just GVariant
jFromAsv -> do
            Ptr GVariant
jFromAsv' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jFromAsv
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jFromAsv'
    Ptr VariantDict
result <- Ptr GVariant -> IO (Ptr VariantDict)
g_variant_dict_new Ptr GVariant
maybeFromAsv
    Text -> Ptr VariantDict -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"variantDictNew" Ptr VariantDict
result
    VariantDict
result' <- ((ManagedPtr VariantDict -> VariantDict)
-> Ptr VariantDict -> IO VariantDict
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr VariantDict -> VariantDict
VariantDict) Ptr VariantDict
result
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
fromAsv GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    VariantDict -> IO VariantDict
forall (m :: * -> *) a. Monad m => a -> m a
return VariantDict
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method VariantDict::clear
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dict"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantDict" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVariantDict" , 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_dict_clear" g_variant_dict_clear :: 
    Ptr VariantDict ->                      -- dict : TInterface (Name {namespace = "GLib", name = "VariantDict"})
    IO ()

-- | Releases all memory associated with a t'GI.GLib.Structs.VariantDict.VariantDict' without freeing
-- the t'GI.GLib.Structs.VariantDict.VariantDict' structure itself.
-- 
-- It typically only makes sense to do this on a stack-allocated
-- t'GI.GLib.Structs.VariantDict.VariantDict' if you want to abort building the value part-way
-- through.  This function need not be called if you call
-- 'GI.GLib.Structs.VariantDict.variantDictEnd' and it also doesn\'t need to be called on dicts
-- allocated with g_variant_dict_new (see 'GI.GLib.Structs.VariantDict.variantDictUnref' for
-- that).
-- 
-- It is valid to call this function on either an initialised
-- t'GI.GLib.Structs.VariantDict.VariantDict' or one that was previously cleared by an earlier call
-- to 'GI.GLib.Structs.VariantDict.variantDictClear' but it is not valid to call this function
-- on uninitialised memory.
-- 
-- /Since: 2.40/
variantDictClear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantDict
    -- ^ /@dict@/: a t'GI.GLib.Structs.VariantDict.VariantDict'
    -> m ()
variantDictClear :: VariantDict -> m ()
variantDictClear VariantDict
dict = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr VariantDict
dict' <- VariantDict -> IO (Ptr VariantDict)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantDict
dict
    Ptr VariantDict -> IO ()
g_variant_dict_clear Ptr VariantDict
dict'
    VariantDict -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VariantDict
dict
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VariantDictClearMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo VariantDictClearMethodInfo VariantDict signature where
    overloadedMethod = variantDictClear

#endif

-- method VariantDict::contains
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dict"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantDict" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVariantDict" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to look up in the dictionary"
--                 , 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_dict_contains" g_variant_dict_contains :: 
    Ptr VariantDict ->                      -- dict : TInterface (Name {namespace = "GLib", name = "VariantDict"})
    CString ->                              -- key : TBasicType TUTF8
    IO CInt

-- | Checks if /@key@/ exists in /@dict@/.
-- 
-- /Since: 2.40/
variantDictContains ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantDict
    -- ^ /@dict@/: a t'GI.GLib.Structs.VariantDict.VariantDict'
    -> T.Text
    -- ^ /@key@/: the key to look up in the dictionary
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@key@/ is in /@dict@/
variantDictContains :: VariantDict -> Text -> m Bool
variantDictContains VariantDict
dict Text
key = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr VariantDict
dict' <- VariantDict -> IO (Ptr VariantDict)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantDict
dict
    CString
key' <- Text -> IO CString
textToCString Text
key
    CInt
result <- Ptr VariantDict -> CString -> IO CInt
g_variant_dict_contains Ptr VariantDict
dict' CString
key'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    VariantDict -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VariantDict
dict
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data VariantDictContainsMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo VariantDictContainsMethodInfo VariantDict signature where
    overloadedMethod = variantDictContains

#endif

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

foreign import ccall "g_variant_dict_end" g_variant_dict_end :: 
    Ptr VariantDict ->                      -- dict : TInterface (Name {namespace = "GLib", name = "VariantDict"})
    IO (Ptr GVariant)

-- | Returns the current value of /@dict@/ as a t'GVariant' of type
-- @/G_VARIANT_TYPE_VARDICT/@, clearing it in the process.
-- 
-- It is not permissible to use /@dict@/ in any way after this call except
-- for reference counting operations (in the case of a heap-allocated
-- t'GI.GLib.Structs.VariantDict.VariantDict') or by reinitialising it with @/g_variant_dict_init()/@ (in
-- the case of stack-allocated).
-- 
-- /Since: 2.40/
variantDictEnd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantDict
    -- ^ /@dict@/: a t'GI.GLib.Structs.VariantDict.VariantDict'
    -> m GVariant
    -- ^ __Returns:__ a new, floating, t'GVariant'
variantDictEnd :: VariantDict -> m GVariant
variantDictEnd VariantDict
dict = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr VariantDict
dict' <- VariantDict -> IO (Ptr VariantDict)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantDict
dict
    Ptr GVariant
result <- Ptr VariantDict -> IO (Ptr GVariant)
g_variant_dict_end Ptr VariantDict
dict'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"variantDictEnd" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result
    VariantDict -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VariantDict
dict
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data VariantDictEndMethodInfo
instance (signature ~ (m GVariant), MonadIO m) => O.MethodInfo VariantDictEndMethodInfo VariantDict signature where
    overloadedMethod = variantDictEnd

#endif

-- method VariantDict::insert_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dict"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantDict" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVariantDict" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to insert a value for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value to insert"
--                 , 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_dict_insert_value" g_variant_dict_insert_value :: 
    Ptr VariantDict ->                      -- dict : TInterface (Name {namespace = "GLib", name = "VariantDict"})
    CString ->                              -- key : TBasicType TUTF8
    Ptr GVariant ->                         -- value : TVariant
    IO ()

-- | Inserts (or replaces) a key in a t'GI.GLib.Structs.VariantDict.VariantDict'.
-- 
-- /@value@/ is consumed if it is floating.
-- 
-- /Since: 2.40/
variantDictInsertValue ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantDict
    -- ^ /@dict@/: a t'GI.GLib.Structs.VariantDict.VariantDict'
    -> T.Text
    -- ^ /@key@/: the key to insert a value for
    -> GVariant
    -- ^ /@value@/: the value to insert
    -> m ()
variantDictInsertValue :: VariantDict -> Text -> GVariant -> m ()
variantDictInsertValue VariantDict
dict Text
key GVariant
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr VariantDict
dict' <- VariantDict -> IO (Ptr VariantDict)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantDict
dict
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr GVariant
value' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
value
    Ptr VariantDict -> CString -> Ptr GVariant -> IO ()
g_variant_dict_insert_value Ptr VariantDict
dict' CString
key' Ptr GVariant
value'
    VariantDict -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VariantDict
dict
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
value
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VariantDictInsertValueMethodInfo
instance (signature ~ (T.Text -> GVariant -> m ()), MonadIO m) => O.MethodInfo VariantDictInsertValueMethodInfo VariantDict signature where
    overloadedMethod = variantDictInsertValue

#endif

-- method VariantDict::lookup_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dict"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantDict" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVariantDict" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to look up in the dictionary"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "expected_type"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantType" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVariantType, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_dict_lookup_value" g_variant_dict_lookup_value :: 
    Ptr VariantDict ->                      -- dict : TInterface (Name {namespace = "GLib", name = "VariantDict"})
    CString ->                              -- key : TBasicType TUTF8
    Ptr GLib.VariantType.VariantType ->     -- expected_type : TInterface (Name {namespace = "GLib", name = "VariantType"})
    IO (Ptr GVariant)

-- | Looks up a value in a t'GI.GLib.Structs.VariantDict.VariantDict'.
-- 
-- If /@key@/ is not found in /@dictionary@/, 'P.Nothing' is returned.
-- 
-- The /@expectedType@/ string specifies what type of value is expected.
-- If the value associated with /@key@/ has a different type then 'P.Nothing' is
-- returned.
-- 
-- If the key is found and the value has the correct type, it is
-- returned.  If /@expectedType@/ was specified then any non-'P.Nothing' return
-- value will have this type.
-- 
-- /Since: 2.40/
variantDictLookupValue ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantDict
    -- ^ /@dict@/: a t'GI.GLib.Structs.VariantDict.VariantDict'
    -> T.Text
    -- ^ /@key@/: the key to look up in the dictionary
    -> Maybe (GLib.VariantType.VariantType)
    -- ^ /@expectedType@/: a t'GI.GLib.Structs.VariantType.VariantType', or 'P.Nothing'
    -> m GVariant
    -- ^ __Returns:__ the value of the dictionary key, or 'P.Nothing'
variantDictLookupValue :: VariantDict -> Text -> Maybe VariantType -> m GVariant
variantDictLookupValue VariantDict
dict Text
key Maybe VariantType
expectedType = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr VariantDict
dict' <- VariantDict -> IO (Ptr VariantDict)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantDict
dict
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr VariantType
maybeExpectedType <- case Maybe VariantType
expectedType of
        Maybe VariantType
Nothing -> Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
forall a. Ptr a
nullPtr
        Just VariantType
jExpectedType -> do
            Ptr VariantType
jExpectedType' <- VariantType -> IO (Ptr VariantType)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantType
jExpectedType
            Ptr VariantType -> IO (Ptr VariantType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr VariantType
jExpectedType'
    Ptr GVariant
result <- Ptr VariantDict -> CString -> Ptr VariantType -> IO (Ptr GVariant)
g_variant_dict_lookup_value Ptr VariantDict
dict' CString
key' Ptr VariantType
maybeExpectedType
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"variantDictLookupValue" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
    VariantDict -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VariantDict
dict
    Maybe VariantType -> (VariantType -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe VariantType
expectedType VariantType -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data VariantDictLookupValueMethodInfo
instance (signature ~ (T.Text -> Maybe (GLib.VariantType.VariantType) -> m GVariant), MonadIO m) => O.MethodInfo VariantDictLookupValueMethodInfo VariantDict signature where
    overloadedMethod = variantDictLookupValue

#endif

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

foreign import ccall "g_variant_dict_ref" g_variant_dict_ref :: 
    Ptr VariantDict ->                      -- dict : TInterface (Name {namespace = "GLib", name = "VariantDict"})
    IO (Ptr VariantDict)

-- | Increases the reference count on /@dict@/.
-- 
-- Don\'t call this on stack-allocated t'GI.GLib.Structs.VariantDict.VariantDict' instances or bad
-- things will happen.
-- 
-- /Since: 2.40/
variantDictRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantDict
    -- ^ /@dict@/: a heap-allocated t'GI.GLib.Structs.VariantDict.VariantDict'
    -> m VariantDict
    -- ^ __Returns:__ a new reference to /@dict@/
variantDictRef :: VariantDict -> m VariantDict
variantDictRef VariantDict
dict = IO VariantDict -> m VariantDict
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VariantDict -> m VariantDict)
-> IO VariantDict -> m VariantDict
forall a b. (a -> b) -> a -> b
$ do
    Ptr VariantDict
dict' <- VariantDict -> IO (Ptr VariantDict)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantDict
dict
    Ptr VariantDict
result <- Ptr VariantDict -> IO (Ptr VariantDict)
g_variant_dict_ref Ptr VariantDict
dict'
    Text -> Ptr VariantDict -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"variantDictRef" Ptr VariantDict
result
    VariantDict
result' <- ((ManagedPtr VariantDict -> VariantDict)
-> Ptr VariantDict -> IO VariantDict
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr VariantDict -> VariantDict
VariantDict) Ptr VariantDict
result
    VariantDict -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VariantDict
dict
    VariantDict -> IO VariantDict
forall (m :: * -> *) a. Monad m => a -> m a
return VariantDict
result'

#if defined(ENABLE_OVERLOADING)
data VariantDictRefMethodInfo
instance (signature ~ (m VariantDict), MonadIO m) => O.MethodInfo VariantDictRefMethodInfo VariantDict signature where
    overloadedMethod = variantDictRef

#endif

-- method VariantDict::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dict"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantDict" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVariantDict" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to remove" , 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_dict_remove" g_variant_dict_remove :: 
    Ptr VariantDict ->                      -- dict : TInterface (Name {namespace = "GLib", name = "VariantDict"})
    CString ->                              -- key : TBasicType TUTF8
    IO CInt

-- | Removes a key and its associated value from a t'GI.GLib.Structs.VariantDict.VariantDict'.
-- 
-- /Since: 2.40/
variantDictRemove ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantDict
    -- ^ /@dict@/: a t'GI.GLib.Structs.VariantDict.VariantDict'
    -> T.Text
    -- ^ /@key@/: the key to remove
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the key was found and removed
variantDictRemove :: VariantDict -> Text -> m Bool
variantDictRemove VariantDict
dict Text
key = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr VariantDict
dict' <- VariantDict -> IO (Ptr VariantDict)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VariantDict
dict
    CString
key' <- Text -> IO CString
textToCString Text
key
    CInt
result <- Ptr VariantDict -> CString -> IO CInt
g_variant_dict_remove Ptr VariantDict
dict' CString
key'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    VariantDict -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VariantDict
dict
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data VariantDictRemoveMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo VariantDictRemoveMethodInfo VariantDict signature where
    overloadedMethod = variantDictRemove

#endif

-- method VariantDict::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "dict"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "VariantDict" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a heap-allocated #GVariantDict"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_dict_unref" g_variant_dict_unref :: 
    Ptr VariantDict ->                      -- dict : TInterface (Name {namespace = "GLib", name = "VariantDict"})
    IO ()

-- | Decreases the reference count on /@dict@/.
-- 
-- In the event that there are no more references, releases all memory
-- associated with the t'GI.GLib.Structs.VariantDict.VariantDict'.
-- 
-- Don\'t call this on stack-allocated t'GI.GLib.Structs.VariantDict.VariantDict' instances or bad
-- things will happen.
-- 
-- /Since: 2.40/
variantDictUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VariantDict
    -- ^ /@dict@/: a heap-allocated t'GI.GLib.Structs.VariantDict.VariantDict'
    -> m ()
variantDictUnref :: VariantDict -> m ()
variantDictUnref VariantDict
dict = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr VariantDict
dict' <- VariantDict -> IO (Ptr VariantDict)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed VariantDict
dict
    Ptr VariantDict -> IO ()
g_variant_dict_unref Ptr VariantDict
dict'
    VariantDict -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VariantDict
dict
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VariantDictUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo VariantDictUnrefMethodInfo VariantDict signature where
    overloadedMethod = variantDictUnref

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveVariantDictMethod (t :: Symbol) (o :: *) :: * where
    ResolveVariantDictMethod "clear" o = VariantDictClearMethodInfo
    ResolveVariantDictMethod "contains" o = VariantDictContainsMethodInfo
    ResolveVariantDictMethod "end" o = VariantDictEndMethodInfo
    ResolveVariantDictMethod "insertValue" o = VariantDictInsertValueMethodInfo
    ResolveVariantDictMethod "lookupValue" o = VariantDictLookupValueMethodInfo
    ResolveVariantDictMethod "ref" o = VariantDictRefMethodInfo
    ResolveVariantDictMethod "remove" o = VariantDictRemoveMethodInfo
    ResolveVariantDictMethod "unref" o = VariantDictUnrefMethodInfo
    ResolveVariantDictMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveVariantDictMethod t VariantDict, O.MethodInfo info VariantDict p) => OL.IsLabel t (VariantDict -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif