{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Dazzle.Structs.FuzzyMutableIndex
    ( 

-- * Exported types
    FuzzyMutableIndex(..)                   ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [beginBulkInsert]("GI.Dazzle.Structs.FuzzyMutableIndex#g:method:beginBulkInsert"), [contains]("GI.Dazzle.Structs.FuzzyMutableIndex#g:method:contains"), [endBulkInsert]("GI.Dazzle.Structs.FuzzyMutableIndex#g:method:endBulkInsert"), [insert]("GI.Dazzle.Structs.FuzzyMutableIndex#g:method:insert"), [match]("GI.Dazzle.Structs.FuzzyMutableIndex#g:method:match"), [ref]("GI.Dazzle.Structs.FuzzyMutableIndex#g:method:ref"), [remove]("GI.Dazzle.Structs.FuzzyMutableIndex#g:method:remove"), [unref]("GI.Dazzle.Structs.FuzzyMutableIndex#g:method:unref").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- [setFreeFunc]("GI.Dazzle.Structs.FuzzyMutableIndex#g:method:setFreeFunc").

#if defined(ENABLE_OVERLOADING)
    ResolveFuzzyMutableIndexMethod          ,
#endif

-- ** beginBulkInsert #method:beginBulkInsert#

#if defined(ENABLE_OVERLOADING)
    FuzzyMutableIndexBeginBulkInsertMethodInfo,
#endif
    fuzzyMutableIndexBeginBulkInsert        ,


-- ** contains #method:contains#

#if defined(ENABLE_OVERLOADING)
    FuzzyMutableIndexContainsMethodInfo     ,
#endif
    fuzzyMutableIndexContains               ,


-- ** endBulkInsert #method:endBulkInsert#

#if defined(ENABLE_OVERLOADING)
    FuzzyMutableIndexEndBulkInsertMethodInfo,
#endif
    fuzzyMutableIndexEndBulkInsert          ,


-- ** insert #method:insert#

#if defined(ENABLE_OVERLOADING)
    FuzzyMutableIndexInsertMethodInfo       ,
#endif
    fuzzyMutableIndexInsert                 ,


-- ** match #method:match#

#if defined(ENABLE_OVERLOADING)
    FuzzyMutableIndexMatchMethodInfo        ,
#endif
    fuzzyMutableIndexMatch                  ,


-- ** new #method:new#

    fuzzyMutableIndexNew                    ,


-- ** newWithFreeFunc #method:newWithFreeFunc#

    fuzzyMutableIndexNewWithFreeFunc        ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    FuzzyMutableIndexRefMethodInfo          ,
#endif
    fuzzyMutableIndexRef                    ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    FuzzyMutableIndexRemoveMethodInfo       ,
#endif
    fuzzyMutableIndexRemove                 ,


-- ** setFreeFunc #method:setFreeFunc#

#if defined(ENABLE_OVERLOADING)
    FuzzyMutableIndexSetFreeFuncMethodInfo  ,
#endif
    fuzzyMutableIndexSetFreeFunc            ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    FuzzyMutableIndexUnrefMethodInfo        ,
#endif
    fuzzyMutableIndexUnref                  ,




    ) 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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import {-# SOURCE #-} qualified GI.Dazzle.Structs.FuzzyMutableIndexMatch as Dazzle.FuzzyMutableIndexMatch
import qualified GI.GLib.Callbacks as GLib.Callbacks

#else
import {-# SOURCE #-} qualified GI.Dazzle.Structs.FuzzyMutableIndexMatch as Dazzle.FuzzyMutableIndexMatch
import qualified GI.GLib.Callbacks as GLib.Callbacks

#endif

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

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

foreign import ccall "dzl_fuzzy_mutable_index_get_type" c_dzl_fuzzy_mutable_index_get_type :: 
    IO GType

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

instance B.Types.TypedObject FuzzyMutableIndex where
    glibType :: IO GType
glibType = IO GType
c_dzl_fuzzy_mutable_index_get_type

instance B.Types.GBoxed FuzzyMutableIndex

-- | Convert 'FuzzyMutableIndex' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe FuzzyMutableIndex) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_fuzzy_mutable_index_get_type
    gvalueSet_ :: Ptr GValue -> Maybe FuzzyMutableIndex -> IO ()
gvalueSet_ Ptr GValue
gv Maybe FuzzyMutableIndex
P.Nothing = Ptr GValue -> Ptr FuzzyMutableIndex -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr FuzzyMutableIndex
forall a. Ptr a
FP.nullPtr :: FP.Ptr FuzzyMutableIndex)
    gvalueSet_ Ptr GValue
gv (P.Just FuzzyMutableIndex
obj) = FuzzyMutableIndex -> (Ptr FuzzyMutableIndex -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FuzzyMutableIndex
obj (Ptr GValue -> Ptr FuzzyMutableIndex -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe FuzzyMutableIndex)
gvalueGet_ Ptr GValue
gv = do
        Ptr FuzzyMutableIndex
ptr <- Ptr GValue -> IO (Ptr FuzzyMutableIndex)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr FuzzyMutableIndex)
        if Ptr FuzzyMutableIndex
ptr Ptr FuzzyMutableIndex -> Ptr FuzzyMutableIndex -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr FuzzyMutableIndex
forall a. Ptr a
FP.nullPtr
        then FuzzyMutableIndex -> Maybe FuzzyMutableIndex
forall a. a -> Maybe a
P.Just (FuzzyMutableIndex -> Maybe FuzzyMutableIndex)
-> IO FuzzyMutableIndex -> IO (Maybe FuzzyMutableIndex)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr FuzzyMutableIndex -> FuzzyMutableIndex)
-> Ptr FuzzyMutableIndex -> IO FuzzyMutableIndex
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr FuzzyMutableIndex -> FuzzyMutableIndex
FuzzyMutableIndex Ptr FuzzyMutableIndex
ptr
        else Maybe FuzzyMutableIndex -> IO (Maybe FuzzyMutableIndex)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FuzzyMutableIndex
forall a. Maybe a
P.Nothing
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FuzzyMutableIndex
type instance O.AttributeList FuzzyMutableIndex = FuzzyMutableIndexAttributeList
type FuzzyMutableIndexAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

-- method FuzzyMutableIndex::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "case_sensitive"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE if case should be preserved."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Dazzle" , name = "FuzzyMutableIndex" })
-- throws : False
-- Skip return : False

foreign import ccall "dzl_fuzzy_mutable_index_new" dzl_fuzzy_mutable_index_new :: 
    CInt ->                                 -- case_sensitive : TBasicType TBoolean
    IO (Ptr FuzzyMutableIndex)

-- | Create a new @/Fuzzy/@ for fuzzy matching strings.
fuzzyMutableIndexNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bool
    -- ^ /@caseSensitive@/: 'P.True' if case should be preserved.
    -> m FuzzyMutableIndex
    -- ^ __Returns:__ A newly allocated @/Fuzzy/@ that should be freed with 'GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexUnref'.
fuzzyMutableIndexNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bool -> m FuzzyMutableIndex
fuzzyMutableIndexNew Bool
caseSensitive = IO FuzzyMutableIndex -> m FuzzyMutableIndex
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FuzzyMutableIndex -> m FuzzyMutableIndex)
-> IO FuzzyMutableIndex -> m FuzzyMutableIndex
forall a b. (a -> b) -> a -> b
$ do
    let caseSensitive' :: CInt
caseSensitive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
caseSensitive
    Ptr FuzzyMutableIndex
result <- CInt -> IO (Ptr FuzzyMutableIndex)
dzl_fuzzy_mutable_index_new CInt
caseSensitive'
    Text -> Ptr FuzzyMutableIndex -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fuzzyMutableIndexNew" Ptr FuzzyMutableIndex
result
    FuzzyMutableIndex
result' <- ((ManagedPtr FuzzyMutableIndex -> FuzzyMutableIndex)
-> Ptr FuzzyMutableIndex -> IO FuzzyMutableIndex
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FuzzyMutableIndex -> FuzzyMutableIndex
FuzzyMutableIndex) Ptr FuzzyMutableIndex
result
    FuzzyMutableIndex -> IO FuzzyMutableIndex
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FuzzyMutableIndex
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method FuzzyMutableIndex::new_with_free_func
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "case_sensitive"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "free_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Dazzle" , name = "FuzzyMutableIndex" })
-- throws : False
-- Skip return : False

foreign import ccall "dzl_fuzzy_mutable_index_new_with_free_func" dzl_fuzzy_mutable_index_new_with_free_func :: 
    CInt ->                                 -- case_sensitive : TBasicType TBoolean
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO (Ptr FuzzyMutableIndex)

-- | /No description available in the introspection data./
fuzzyMutableIndexNewWithFreeFunc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bool
    -> GLib.Callbacks.DestroyNotify
    -> m FuzzyMutableIndex
fuzzyMutableIndexNewWithFreeFunc :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bool -> IO () -> m FuzzyMutableIndex
fuzzyMutableIndexNewWithFreeFunc Bool
caseSensitive IO ()
freeFunc = IO FuzzyMutableIndex -> m FuzzyMutableIndex
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FuzzyMutableIndex -> m FuzzyMutableIndex)
-> IO FuzzyMutableIndex -> m FuzzyMutableIndex
forall a b. (a -> b) -> a -> b
$ do
    let caseSensitive' :: CInt
caseSensitive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
caseSensitive
    Ptr (FunPtr C_DestroyNotify)
ptrfreeFunc <- IO (Ptr (FunPtr C_DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
    FunPtr C_DestroyNotify
freeFunc' <- C_DestroyNotify -> IO (FunPtr C_DestroyNotify)
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr C_DestroyNotify))
-> C_DestroyNotify -> C_DestroyNotify
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr C_DestroyNotify)
-> Maybe (Ptr (FunPtr C_DestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr C_DestroyNotify)
ptrfreeFunc) (IO () -> C_DestroyNotify
GLib.Callbacks.drop_closures_DestroyNotify IO ()
freeFunc))
    Ptr (FunPtr C_DestroyNotify) -> FunPtr C_DestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_DestroyNotify)
ptrfreeFunc FunPtr C_DestroyNotify
freeFunc'
    Ptr FuzzyMutableIndex
result <- CInt -> FunPtr C_DestroyNotify -> IO (Ptr FuzzyMutableIndex)
dzl_fuzzy_mutable_index_new_with_free_func CInt
caseSensitive' FunPtr C_DestroyNotify
freeFunc'
    Text -> Ptr FuzzyMutableIndex -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fuzzyMutableIndexNewWithFreeFunc" Ptr FuzzyMutableIndex
result
    FuzzyMutableIndex
result' <- ((ManagedPtr FuzzyMutableIndex -> FuzzyMutableIndex)
-> Ptr FuzzyMutableIndex -> IO FuzzyMutableIndex
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FuzzyMutableIndex -> FuzzyMutableIndex
FuzzyMutableIndex) Ptr FuzzyMutableIndex
result
    FuzzyMutableIndex -> IO FuzzyMutableIndex
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FuzzyMutableIndex
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method FuzzyMutableIndex::begin_bulk_insert
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fuzzy"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "FuzzyMutableIndex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #Fuzzy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_fuzzy_mutable_index_begin_bulk_insert" dzl_fuzzy_mutable_index_begin_bulk_insert :: 
    Ptr FuzzyMutableIndex ->                -- fuzzy : TInterface (Name {namespace = "Dazzle", name = "FuzzyMutableIndex"})
    IO ()

-- | Start a bulk insertion. /@fuzzy@/ is not ready for searching until
-- 'GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexEndBulkInsert' has been called.
-- 
-- This allows for inserting large numbers of strings and deferring
-- the final sort until 'GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexEndBulkInsert'.
fuzzyMutableIndexBeginBulkInsert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FuzzyMutableIndex
    -- ^ /@fuzzy@/: A @/Fuzzy/@.
    -> m ()
fuzzyMutableIndexBeginBulkInsert :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FuzzyMutableIndex -> m ()
fuzzyMutableIndexBeginBulkInsert FuzzyMutableIndex
fuzzy = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FuzzyMutableIndex
fuzzy' <- FuzzyMutableIndex -> IO (Ptr FuzzyMutableIndex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FuzzyMutableIndex
fuzzy
    Ptr FuzzyMutableIndex -> IO ()
dzl_fuzzy_mutable_index_begin_bulk_insert Ptr FuzzyMutableIndex
fuzzy'
    FuzzyMutableIndex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FuzzyMutableIndex
fuzzy
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FuzzyMutableIndexBeginBulkInsertMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod FuzzyMutableIndexBeginBulkInsertMethodInfo FuzzyMutableIndex signature where
    overloadedMethod = fuzzyMutableIndexBeginBulkInsert

instance O.OverloadedMethodInfo FuzzyMutableIndexBeginBulkInsertMethodInfo FuzzyMutableIndex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexBeginBulkInsert",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Structs-FuzzyMutableIndex.html#v:fuzzyMutableIndexBeginBulkInsert"
        })


#endif

-- method FuzzyMutableIndex::contains
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fuzzy"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "FuzzyMutableIndex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dzl_fuzzy_mutable_index_contains" dzl_fuzzy_mutable_index_contains :: 
    Ptr FuzzyMutableIndex ->                -- fuzzy : TInterface (Name {namespace = "Dazzle", name = "FuzzyMutableIndex"})
    CString ->                              -- key : TBasicType TUTF8
    IO CInt

-- | /No description available in the introspection data./
fuzzyMutableIndexContains ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FuzzyMutableIndex
    -> T.Text
    -> m Bool
fuzzyMutableIndexContains :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FuzzyMutableIndex -> Text -> m Bool
fuzzyMutableIndexContains FuzzyMutableIndex
fuzzy Text
key = IO Bool -> m Bool
forall a. IO a -> m a
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 FuzzyMutableIndex
fuzzy' <- FuzzyMutableIndex -> IO (Ptr FuzzyMutableIndex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FuzzyMutableIndex
fuzzy
    CString
key' <- Text -> IO CString
textToCString Text
key
    CInt
result <- Ptr FuzzyMutableIndex -> CString -> IO CInt
dzl_fuzzy_mutable_index_contains Ptr FuzzyMutableIndex
fuzzy' CString
key'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    FuzzyMutableIndex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FuzzyMutableIndex
fuzzy
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FuzzyMutableIndexContainsMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.OverloadedMethod FuzzyMutableIndexContainsMethodInfo FuzzyMutableIndex signature where
    overloadedMethod = fuzzyMutableIndexContains

instance O.OverloadedMethodInfo FuzzyMutableIndexContainsMethodInfo FuzzyMutableIndex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexContains",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Structs-FuzzyMutableIndex.html#v:fuzzyMutableIndexContains"
        })


#endif

-- method FuzzyMutableIndex::end_bulk_insert
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fuzzy"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "FuzzyMutableIndex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #Fuzzy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_fuzzy_mutable_index_end_bulk_insert" dzl_fuzzy_mutable_index_end_bulk_insert :: 
    Ptr FuzzyMutableIndex ->                -- fuzzy : TInterface (Name {namespace = "Dazzle", name = "FuzzyMutableIndex"})
    IO ()

-- | Complete a bulk insert and resort the index.
fuzzyMutableIndexEndBulkInsert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FuzzyMutableIndex
    -- ^ /@fuzzy@/: A @/Fuzzy/@.
    -> m ()
fuzzyMutableIndexEndBulkInsert :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FuzzyMutableIndex -> m ()
fuzzyMutableIndexEndBulkInsert FuzzyMutableIndex
fuzzy = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FuzzyMutableIndex
fuzzy' <- FuzzyMutableIndex -> IO (Ptr FuzzyMutableIndex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FuzzyMutableIndex
fuzzy
    Ptr FuzzyMutableIndex -> IO ()
dzl_fuzzy_mutable_index_end_bulk_insert Ptr FuzzyMutableIndex
fuzzy'
    FuzzyMutableIndex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FuzzyMutableIndex
fuzzy
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FuzzyMutableIndexEndBulkInsertMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod FuzzyMutableIndexEndBulkInsertMethodInfo FuzzyMutableIndex signature where
    overloadedMethod = fuzzyMutableIndexEndBulkInsert

instance O.OverloadedMethodInfo FuzzyMutableIndexEndBulkInsertMethodInfo FuzzyMutableIndex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexEndBulkInsert",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Structs-FuzzyMutableIndex.html#v:fuzzyMutableIndexEndBulkInsert"
        })


#endif

-- method FuzzyMutableIndex::insert
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fuzzy"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "FuzzyMutableIndex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #Fuzzy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A UTF-8 encoded string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A value to associate with key."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_fuzzy_mutable_index_insert" dzl_fuzzy_mutable_index_insert :: 
    Ptr FuzzyMutableIndex ->                -- fuzzy : TInterface (Name {namespace = "Dazzle", name = "FuzzyMutableIndex"})
    CString ->                              -- key : TBasicType TUTF8
    Ptr () ->                               -- value : TBasicType TPtr
    IO ()

-- | Inserts a string into the fuzzy matcher.
fuzzyMutableIndexInsert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FuzzyMutableIndex
    -- ^ /@fuzzy@/: A @/Fuzzy/@.
    -> T.Text
    -- ^ /@key@/: A UTF-8 encoded string.
    -> Ptr ()
    -- ^ /@value@/: A value to associate with key.
    -> m ()
fuzzyMutableIndexInsert :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FuzzyMutableIndex -> Text -> Ptr () -> m ()
fuzzyMutableIndexInsert FuzzyMutableIndex
fuzzy Text
key Ptr ()
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FuzzyMutableIndex
fuzzy' <- FuzzyMutableIndex -> IO (Ptr FuzzyMutableIndex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FuzzyMutableIndex
fuzzy
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr FuzzyMutableIndex -> CString -> C_DestroyNotify
dzl_fuzzy_mutable_index_insert Ptr FuzzyMutableIndex
fuzzy' CString
key' Ptr ()
value
    FuzzyMutableIndex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FuzzyMutableIndex
fuzzy
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FuzzyMutableIndexInsertMethodInfo
instance (signature ~ (T.Text -> Ptr () -> m ()), MonadIO m) => O.OverloadedMethod FuzzyMutableIndexInsertMethodInfo FuzzyMutableIndex signature where
    overloadedMethod = fuzzyMutableIndexInsert

instance O.OverloadedMethodInfo FuzzyMutableIndexInsertMethodInfo FuzzyMutableIndex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexInsert",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Structs-FuzzyMutableIndex.html#v:fuzzyMutableIndexInsert"
        })


#endif

-- method FuzzyMutableIndex::match
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fuzzy"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "FuzzyMutableIndex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #Fuzzy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "needle"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The needle to fuzzy search for."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "max_matches"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The max number of matches to return."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGArray
--                  (TInterface
--                     Name { namespace = "Dazzle" , name = "FuzzyMutableIndexMatch" }))
-- throws : False
-- Skip return : False

foreign import ccall "dzl_fuzzy_mutable_index_match" dzl_fuzzy_mutable_index_match :: 
    Ptr FuzzyMutableIndex ->                -- fuzzy : TInterface (Name {namespace = "Dazzle", name = "FuzzyMutableIndex"})
    CString ->                              -- needle : TBasicType TUTF8
    FCT.CSize ->                            -- max_matches : TBasicType TSize
    IO (Ptr (GArray (Ptr Dazzle.FuzzyMutableIndexMatch.FuzzyMutableIndexMatch)))

-- | DzlFuzzyMutableIndex searches within /@fuzzy@/ for strings that fuzzy match /@needle@/.
-- Only up to /@maxMatches@/ will be returned.
-- 
-- TODO: max_matches is not yet respected.
fuzzyMutableIndexMatch ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FuzzyMutableIndex
    -- ^ /@fuzzy@/: A @/Fuzzy/@.
    -> T.Text
    -- ^ /@needle@/: The needle to fuzzy search for.
    -> FCT.CSize
    -- ^ /@maxMatches@/: The max number of matches to return.
    -> m [Dazzle.FuzzyMutableIndexMatch.FuzzyMutableIndexMatch]
    -- ^ __Returns:__ A newly allocated
    --   t'GI.GLib.Structs.Array.Array' containing @/FuzzyMatch/@ elements. This should be freed when
    --   the caller is done with it using @/g_array_unref()/@.
    --   It is a programming error to keep the structure around longer than
    --   the /@fuzzy@/ instance.
fuzzyMutableIndexMatch :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FuzzyMutableIndex -> Text -> CSize -> m [FuzzyMutableIndexMatch]
fuzzyMutableIndexMatch FuzzyMutableIndex
fuzzy Text
needle CSize
maxMatches = IO [FuzzyMutableIndexMatch] -> m [FuzzyMutableIndexMatch]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [FuzzyMutableIndexMatch] -> m [FuzzyMutableIndexMatch])
-> IO [FuzzyMutableIndexMatch] -> m [FuzzyMutableIndexMatch]
forall a b. (a -> b) -> a -> b
$ do
    Ptr FuzzyMutableIndex
fuzzy' <- FuzzyMutableIndex -> IO (Ptr FuzzyMutableIndex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FuzzyMutableIndex
fuzzy
    CString
needle' <- Text -> IO CString
textToCString Text
needle
    Ptr (GArray (Ptr FuzzyMutableIndexMatch))
result <- Ptr FuzzyMutableIndex
-> CString
-> CSize
-> IO (Ptr (GArray (Ptr FuzzyMutableIndexMatch)))
dzl_fuzzy_mutable_index_match Ptr FuzzyMutableIndex
fuzzy' CString
needle' CSize
maxMatches
    Text -> Ptr (GArray (Ptr FuzzyMutableIndexMatch)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fuzzyMutableIndexMatch" Ptr (GArray (Ptr FuzzyMutableIndexMatch))
result
    [Ptr FuzzyMutableIndexMatch]
result' <- Ptr (GArray (Ptr FuzzyMutableIndexMatch))
-> IO [Ptr FuzzyMutableIndexMatch]
forall a. Storable a => Ptr (GArray a) -> IO [a]
unpackGArray Ptr (GArray (Ptr FuzzyMutableIndexMatch))
result
    [FuzzyMutableIndexMatch]
result'' <- (Ptr FuzzyMutableIndexMatch -> IO FuzzyMutableIndexMatch)
-> [Ptr FuzzyMutableIndexMatch] -> IO [FuzzyMutableIndexMatch]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr FuzzyMutableIndexMatch -> FuzzyMutableIndexMatch)
-> Ptr FuzzyMutableIndexMatch -> IO FuzzyMutableIndexMatch
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr FuzzyMutableIndexMatch -> FuzzyMutableIndexMatch
Dazzle.FuzzyMutableIndexMatch.FuzzyMutableIndexMatch) [Ptr FuzzyMutableIndexMatch]
result'
    Ptr (GArray (Ptr FuzzyMutableIndexMatch)) -> IO ()
forall a. Ptr (GArray a) -> IO ()
unrefGArray Ptr (GArray (Ptr FuzzyMutableIndexMatch))
result
    FuzzyMutableIndex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FuzzyMutableIndex
fuzzy
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
needle'
    [FuzzyMutableIndexMatch] -> IO [FuzzyMutableIndexMatch]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [FuzzyMutableIndexMatch]
result''

#if defined(ENABLE_OVERLOADING)
data FuzzyMutableIndexMatchMethodInfo
instance (signature ~ (T.Text -> FCT.CSize -> m [Dazzle.FuzzyMutableIndexMatch.FuzzyMutableIndexMatch]), MonadIO m) => O.OverloadedMethod FuzzyMutableIndexMatchMethodInfo FuzzyMutableIndex signature where
    overloadedMethod = fuzzyMutableIndexMatch

instance O.OverloadedMethodInfo FuzzyMutableIndexMatchMethodInfo FuzzyMutableIndex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexMatch",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Structs-FuzzyMutableIndex.html#v:fuzzyMutableIndexMatch"
        })


#endif

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

foreign import ccall "dzl_fuzzy_mutable_index_ref" dzl_fuzzy_mutable_index_ref :: 
    Ptr FuzzyMutableIndex ->                -- fuzzy : TInterface (Name {namespace = "Dazzle", name = "FuzzyMutableIndex"})
    IO (Ptr FuzzyMutableIndex)

-- | /No description available in the introspection data./
fuzzyMutableIndexRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FuzzyMutableIndex
    -> m FuzzyMutableIndex
fuzzyMutableIndexRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FuzzyMutableIndex -> m FuzzyMutableIndex
fuzzyMutableIndexRef FuzzyMutableIndex
fuzzy = IO FuzzyMutableIndex -> m FuzzyMutableIndex
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FuzzyMutableIndex -> m FuzzyMutableIndex)
-> IO FuzzyMutableIndex -> m FuzzyMutableIndex
forall a b. (a -> b) -> a -> b
$ do
    Ptr FuzzyMutableIndex
fuzzy' <- FuzzyMutableIndex -> IO (Ptr FuzzyMutableIndex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FuzzyMutableIndex
fuzzy
    Ptr FuzzyMutableIndex
result <- Ptr FuzzyMutableIndex -> IO (Ptr FuzzyMutableIndex)
dzl_fuzzy_mutable_index_ref Ptr FuzzyMutableIndex
fuzzy'
    Text -> Ptr FuzzyMutableIndex -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fuzzyMutableIndexRef" Ptr FuzzyMutableIndex
result
    FuzzyMutableIndex
result' <- ((ManagedPtr FuzzyMutableIndex -> FuzzyMutableIndex)
-> Ptr FuzzyMutableIndex -> IO FuzzyMutableIndex
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FuzzyMutableIndex -> FuzzyMutableIndex
FuzzyMutableIndex) Ptr FuzzyMutableIndex
result
    FuzzyMutableIndex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FuzzyMutableIndex
fuzzy
    FuzzyMutableIndex -> IO FuzzyMutableIndex
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FuzzyMutableIndex
result'

#if defined(ENABLE_OVERLOADING)
data FuzzyMutableIndexRefMethodInfo
instance (signature ~ (m FuzzyMutableIndex), MonadIO m) => O.OverloadedMethod FuzzyMutableIndexRefMethodInfo FuzzyMutableIndex signature where
    overloadedMethod = fuzzyMutableIndexRef

instance O.OverloadedMethodInfo FuzzyMutableIndexRefMethodInfo FuzzyMutableIndex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Structs-FuzzyMutableIndex.html#v:fuzzyMutableIndexRef"
        })


#endif

-- method FuzzyMutableIndex::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fuzzy"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "FuzzyMutableIndex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_fuzzy_mutable_index_remove" dzl_fuzzy_mutable_index_remove :: 
    Ptr FuzzyMutableIndex ->                -- fuzzy : TInterface (Name {namespace = "Dazzle", name = "FuzzyMutableIndex"})
    CString ->                              -- key : TBasicType TUTF8
    IO ()

-- | /No description available in the introspection data./
fuzzyMutableIndexRemove ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FuzzyMutableIndex
    -> T.Text
    -> m ()
fuzzyMutableIndexRemove :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FuzzyMutableIndex -> Text -> m ()
fuzzyMutableIndexRemove FuzzyMutableIndex
fuzzy Text
key = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FuzzyMutableIndex
fuzzy' <- FuzzyMutableIndex -> IO (Ptr FuzzyMutableIndex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FuzzyMutableIndex
fuzzy
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr FuzzyMutableIndex -> CString -> IO ()
dzl_fuzzy_mutable_index_remove Ptr FuzzyMutableIndex
fuzzy' CString
key'
    FuzzyMutableIndex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FuzzyMutableIndex
fuzzy
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FuzzyMutableIndexRemoveMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod FuzzyMutableIndexRemoveMethodInfo FuzzyMutableIndex signature where
    overloadedMethod = fuzzyMutableIndexRemove

instance O.OverloadedMethodInfo FuzzyMutableIndexRemoveMethodInfo FuzzyMutableIndex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexRemove",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Structs-FuzzyMutableIndex.html#v:fuzzyMutableIndexRemove"
        })


#endif

-- method FuzzyMutableIndex::set_free_func
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fuzzy"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "FuzzyMutableIndex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "free_func"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_fuzzy_mutable_index_set_free_func" dzl_fuzzy_mutable_index_set_free_func :: 
    Ptr FuzzyMutableIndex ->                -- fuzzy : TInterface (Name {namespace = "Dazzle", name = "FuzzyMutableIndex"})
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- free_func : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | /No description available in the introspection data./
fuzzyMutableIndexSetFreeFunc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FuzzyMutableIndex
    -> GLib.Callbacks.DestroyNotify
    -> m ()
fuzzyMutableIndexSetFreeFunc :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FuzzyMutableIndex -> IO () -> m ()
fuzzyMutableIndexSetFreeFunc FuzzyMutableIndex
fuzzy IO ()
freeFunc = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FuzzyMutableIndex
fuzzy' <- FuzzyMutableIndex -> IO (Ptr FuzzyMutableIndex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FuzzyMutableIndex
fuzzy
    Ptr (FunPtr C_DestroyNotify)
ptrfreeFunc <- IO (Ptr (FunPtr C_DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
    FunPtr C_DestroyNotify
freeFunc' <- C_DestroyNotify -> IO (FunPtr C_DestroyNotify)
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr C_DestroyNotify))
-> C_DestroyNotify -> C_DestroyNotify
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr C_DestroyNotify)
-> Maybe (Ptr (FunPtr C_DestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr C_DestroyNotify)
ptrfreeFunc) (IO () -> C_DestroyNotify
GLib.Callbacks.drop_closures_DestroyNotify IO ()
freeFunc))
    Ptr (FunPtr C_DestroyNotify) -> FunPtr C_DestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_DestroyNotify)
ptrfreeFunc FunPtr C_DestroyNotify
freeFunc'
    Ptr FuzzyMutableIndex -> FunPtr C_DestroyNotify -> IO ()
dzl_fuzzy_mutable_index_set_free_func Ptr FuzzyMutableIndex
fuzzy' FunPtr C_DestroyNotify
freeFunc'
    FuzzyMutableIndex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FuzzyMutableIndex
fuzzy
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FuzzyMutableIndexSetFreeFuncMethodInfo
instance (signature ~ (GLib.Callbacks.DestroyNotify -> m ()), MonadIO m) => O.OverloadedMethod FuzzyMutableIndexSetFreeFuncMethodInfo FuzzyMutableIndex signature where
    overloadedMethod = fuzzyMutableIndexSetFreeFunc

instance O.OverloadedMethodInfo FuzzyMutableIndexSetFreeFuncMethodInfo FuzzyMutableIndex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexSetFreeFunc",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Structs-FuzzyMutableIndex.html#v:fuzzyMutableIndexSetFreeFunc"
        })


#endif

-- method FuzzyMutableIndex::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fuzzy"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "FuzzyMutableIndex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #Fuzzy." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_fuzzy_mutable_index_unref" dzl_fuzzy_mutable_index_unref :: 
    Ptr FuzzyMutableIndex ->                -- fuzzy : TInterface (Name {namespace = "Dazzle", name = "FuzzyMutableIndex"})
    IO ()

-- | Decrements the reference count of fuzzy by one. When the reference count
-- reaches zero, the structure will be freed.
fuzzyMutableIndexUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FuzzyMutableIndex
    -- ^ /@fuzzy@/: A @/Fuzzy/@.
    -> m ()
fuzzyMutableIndexUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FuzzyMutableIndex -> m ()
fuzzyMutableIndexUnref FuzzyMutableIndex
fuzzy = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FuzzyMutableIndex
fuzzy' <- FuzzyMutableIndex -> IO (Ptr FuzzyMutableIndex)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FuzzyMutableIndex
fuzzy
    Ptr FuzzyMutableIndex -> IO ()
dzl_fuzzy_mutable_index_unref Ptr FuzzyMutableIndex
fuzzy'
    FuzzyMutableIndex -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FuzzyMutableIndex
fuzzy
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FuzzyMutableIndexUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod FuzzyMutableIndexUnrefMethodInfo FuzzyMutableIndex signature where
    overloadedMethod = fuzzyMutableIndexUnref

instance O.OverloadedMethodInfo FuzzyMutableIndexUnrefMethodInfo FuzzyMutableIndex where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Structs.FuzzyMutableIndex.fuzzyMutableIndexUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Structs-FuzzyMutableIndex.html#v:fuzzyMutableIndexUnref"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveFuzzyMutableIndexMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveFuzzyMutableIndexMethod "beginBulkInsert" o = FuzzyMutableIndexBeginBulkInsertMethodInfo
    ResolveFuzzyMutableIndexMethod "contains" o = FuzzyMutableIndexContainsMethodInfo
    ResolveFuzzyMutableIndexMethod "endBulkInsert" o = FuzzyMutableIndexEndBulkInsertMethodInfo
    ResolveFuzzyMutableIndexMethod "insert" o = FuzzyMutableIndexInsertMethodInfo
    ResolveFuzzyMutableIndexMethod "match" o = FuzzyMutableIndexMatchMethodInfo
    ResolveFuzzyMutableIndexMethod "ref" o = FuzzyMutableIndexRefMethodInfo
    ResolveFuzzyMutableIndexMethod "remove" o = FuzzyMutableIndexRemoveMethodInfo
    ResolveFuzzyMutableIndexMethod "unref" o = FuzzyMutableIndexUnrefMethodInfo
    ResolveFuzzyMutableIndexMethod "setFreeFunc" o = FuzzyMutableIndexSetFreeFuncMethodInfo
    ResolveFuzzyMutableIndexMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveFuzzyMutableIndexMethod t FuzzyMutableIndex, O.OverloadedMethod info FuzzyMutableIndex p, R.HasField t FuzzyMutableIndex p) => R.HasField t FuzzyMutableIndex p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveFuzzyMutableIndexMethod t FuzzyMutableIndex, O.OverloadedMethodInfo info FuzzyMutableIndex) => OL.IsLabel t (O.MethodProxy info FuzzyMutableIndex) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif