{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkEntryCompletion@ is an auxiliary object to provide completion functionality
-- for @GtkEntry@.
-- 
-- It implements the t'GI.Gtk.Interfaces.CellLayout.CellLayout' interface, to allow the user
-- to add extra cells to the @GtkTreeView@ with completion matches.
-- 
-- “Completion functionality” means that when the user modifies the text
-- in the entry, @GtkEntryCompletion@ checks which rows in the model match
-- the current content of the entry, and displays a list of matches.
-- By default, the matching is done by comparing the entry text
-- case-insensitively against the text column of the model (see
-- 'GI.Gtk.Objects.EntryCompletion.entryCompletionSetTextColumn'), but this can be overridden
-- with a custom match function (see 'GI.Gtk.Objects.EntryCompletion.entryCompletionSetMatchFunc').
-- 
-- When the user selects a completion, the content of the entry is
-- updated. By default, the content of the entry is replaced by the
-- text column of the model, but this can be overridden by connecting
-- to the [EntryCompletion::matchSelected]("GI.Gtk.Objects.EntryCompletion#g:signal:matchSelected") signal and updating the
-- entry in the signal handler. Note that you should return 'P.True' from
-- the signal handler to suppress the default behaviour.
-- 
-- To add completion functionality to an entry, use
-- 'GI.Gtk.Objects.Entry.entrySetCompletion'.
-- 
-- @GtkEntryCompletion@ uses a t'GI.Gtk.Objects.TreeModelFilter.TreeModelFilter' model to
-- represent the subset of the entire model that is currently matching.
-- While the @GtkEntryCompletion@ signals
-- [EntryCompletion::matchSelected]("GI.Gtk.Objects.EntryCompletion#g:signal:matchSelected") and
-- [EntryCompletion::cursorOnMatch]("GI.Gtk.Objects.EntryCompletion#g:signal:cursorOnMatch") take the original model
-- and an iter pointing to that model as arguments, other callbacks and
-- signals (such as @GtkCellLayoutDataFunc@ or
-- [signal/@gtk@/.CellArea[applyAttributes](#g:signal:applyAttributes))]
-- will generally take the filter model as argument. As long as you are
-- only calling t'GI.Gtk.Interfaces.TreeModel.TreeModel'.@/get/@(), this will make no difference to
-- you. If for some reason, you need the original model, use
-- 'GI.Gtk.Objects.TreeModelFilter.treeModelFilterGetModel'. Don’t forget to use
-- 'GI.Gtk.Objects.TreeModelFilter.treeModelFilterConvertIterToChildIter' to obtain a
-- matching iter.

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

module GI.Gtk.Objects.EntryCompletion
    ( 

-- * Exported types
    EntryCompletion(..)                     ,
    IsEntryCompletion                       ,
    toEntryCompletion                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addAttribute]("GI.Gtk.Interfaces.CellLayout#g:method:addAttribute"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [clear]("GI.Gtk.Interfaces.CellLayout#g:method:clear"), [clearAttributes]("GI.Gtk.Interfaces.CellLayout#g:method:clearAttributes"), [complete]("GI.Gtk.Objects.EntryCompletion#g:method:complete"), [computePrefix]("GI.Gtk.Objects.EntryCompletion#g:method:computePrefix"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [insertPrefix]("GI.Gtk.Objects.EntryCompletion#g:method:insertPrefix"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [packEnd]("GI.Gtk.Interfaces.CellLayout#g:method:packEnd"), [packStart]("GI.Gtk.Interfaces.CellLayout#g:method:packStart"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [reorder]("GI.Gtk.Interfaces.CellLayout#g:method:reorder"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getArea]("GI.Gtk.Interfaces.CellLayout#g:method:getArea"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCells]("GI.Gtk.Interfaces.CellLayout#g:method:getCells"), [getCompletionPrefix]("GI.Gtk.Objects.EntryCompletion#g:method:getCompletionPrefix"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getEntry]("GI.Gtk.Objects.EntryCompletion#g:method:getEntry"), [getInlineCompletion]("GI.Gtk.Objects.EntryCompletion#g:method:getInlineCompletion"), [getInlineSelection]("GI.Gtk.Objects.EntryCompletion#g:method:getInlineSelection"), [getMinimumKeyLength]("GI.Gtk.Objects.EntryCompletion#g:method:getMinimumKeyLength"), [getModel]("GI.Gtk.Objects.EntryCompletion#g:method:getModel"), [getPopupCompletion]("GI.Gtk.Objects.EntryCompletion#g:method:getPopupCompletion"), [getPopupSetWidth]("GI.Gtk.Objects.EntryCompletion#g:method:getPopupSetWidth"), [getPopupSingleMatch]("GI.Gtk.Objects.EntryCompletion#g:method:getPopupSingleMatch"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getTextColumn]("GI.Gtk.Objects.EntryCompletion#g:method:getTextColumn").
-- 
-- ==== Setters
-- [setCellDataFunc]("GI.Gtk.Interfaces.CellLayout#g:method:setCellDataFunc"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setInlineCompletion]("GI.Gtk.Objects.EntryCompletion#g:method:setInlineCompletion"), [setInlineSelection]("GI.Gtk.Objects.EntryCompletion#g:method:setInlineSelection"), [setMatchFunc]("GI.Gtk.Objects.EntryCompletion#g:method:setMatchFunc"), [setMinimumKeyLength]("GI.Gtk.Objects.EntryCompletion#g:method:setMinimumKeyLength"), [setModel]("GI.Gtk.Objects.EntryCompletion#g:method:setModel"), [setPopupCompletion]("GI.Gtk.Objects.EntryCompletion#g:method:setPopupCompletion"), [setPopupSetWidth]("GI.Gtk.Objects.EntryCompletion#g:method:setPopupSetWidth"), [setPopupSingleMatch]("GI.Gtk.Objects.EntryCompletion#g:method:setPopupSingleMatch"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setTextColumn]("GI.Gtk.Objects.EntryCompletion#g:method:setTextColumn").

#if defined(ENABLE_OVERLOADING)
    ResolveEntryCompletionMethod            ,
#endif

-- ** complete #method:complete#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionCompleteMethodInfo       ,
#endif
    entryCompletionComplete                 ,


-- ** computePrefix #method:computePrefix#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionComputePrefixMethodInfo  ,
#endif
    entryCompletionComputePrefix            ,


-- ** getCompletionPrefix #method:getCompletionPrefix#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionGetCompletionPrefixMethodInfo,
#endif
    entryCompletionGetCompletionPrefix      ,


-- ** getEntry #method:getEntry#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionGetEntryMethodInfo       ,
#endif
    entryCompletionGetEntry                 ,


-- ** getInlineCompletion #method:getInlineCompletion#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionGetInlineCompletionMethodInfo,
#endif
    entryCompletionGetInlineCompletion      ,


-- ** getInlineSelection #method:getInlineSelection#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionGetInlineSelectionMethodInfo,
#endif
    entryCompletionGetInlineSelection       ,


-- ** getMinimumKeyLength #method:getMinimumKeyLength#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionGetMinimumKeyLengthMethodInfo,
#endif
    entryCompletionGetMinimumKeyLength      ,


-- ** getModel #method:getModel#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionGetModelMethodInfo       ,
#endif
    entryCompletionGetModel                 ,


-- ** getPopupCompletion #method:getPopupCompletion#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionGetPopupCompletionMethodInfo,
#endif
    entryCompletionGetPopupCompletion       ,


-- ** getPopupSetWidth #method:getPopupSetWidth#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionGetPopupSetWidthMethodInfo,
#endif
    entryCompletionGetPopupSetWidth         ,


-- ** getPopupSingleMatch #method:getPopupSingleMatch#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionGetPopupSingleMatchMethodInfo,
#endif
    entryCompletionGetPopupSingleMatch      ,


-- ** getTextColumn #method:getTextColumn#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionGetTextColumnMethodInfo  ,
#endif
    entryCompletionGetTextColumn            ,


-- ** insertPrefix #method:insertPrefix#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionInsertPrefixMethodInfo   ,
#endif
    entryCompletionInsertPrefix             ,


-- ** new #method:new#

    entryCompletionNew                      ,


-- ** newWithArea #method:newWithArea#

    entryCompletionNewWithArea              ,


-- ** setInlineCompletion #method:setInlineCompletion#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionSetInlineCompletionMethodInfo,
#endif
    entryCompletionSetInlineCompletion      ,


-- ** setInlineSelection #method:setInlineSelection#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionSetInlineSelectionMethodInfo,
#endif
    entryCompletionSetInlineSelection       ,


-- ** setMatchFunc #method:setMatchFunc#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionSetMatchFuncMethodInfo   ,
#endif
    entryCompletionSetMatchFunc             ,


-- ** setMinimumKeyLength #method:setMinimumKeyLength#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionSetMinimumKeyLengthMethodInfo,
#endif
    entryCompletionSetMinimumKeyLength      ,


-- ** setModel #method:setModel#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionSetModelMethodInfo       ,
#endif
    entryCompletionSetModel                 ,


-- ** setPopupCompletion #method:setPopupCompletion#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionSetPopupCompletionMethodInfo,
#endif
    entryCompletionSetPopupCompletion       ,


-- ** setPopupSetWidth #method:setPopupSetWidth#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionSetPopupSetWidthMethodInfo,
#endif
    entryCompletionSetPopupSetWidth         ,


-- ** setPopupSingleMatch #method:setPopupSingleMatch#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionSetPopupSingleMatchMethodInfo,
#endif
    entryCompletionSetPopupSingleMatch      ,


-- ** setTextColumn #method:setTextColumn#

#if defined(ENABLE_OVERLOADING)
    EntryCompletionSetTextColumnMethodInfo  ,
#endif
    entryCompletionSetTextColumn            ,




 -- * Properties


-- ** cellArea #attr:cellArea#
-- | The @GtkCellArea@ used to layout cell renderers in the treeview column.
-- 
-- If no area is specified when creating the entry completion with
-- 'GI.Gtk.Objects.EntryCompletion.entryCompletionNewWithArea', a horizontally oriented
-- t'GI.Gtk.Objects.CellAreaBox.CellAreaBox' will be used.

#if defined(ENABLE_OVERLOADING)
    EntryCompletionCellAreaPropertyInfo     ,
#endif
    constructEntryCompletionCellArea        ,
#if defined(ENABLE_OVERLOADING)
    entryCompletionCellArea                 ,
#endif
    getEntryCompletionCellArea              ,


-- ** inlineCompletion #attr:inlineCompletion#
-- | Determines whether the common prefix of the possible completions
-- should be inserted automatically in the entry.
-- 
-- Note that this requires text-column to be set, even if you are
-- using a custom match function.

#if defined(ENABLE_OVERLOADING)
    EntryCompletionInlineCompletionPropertyInfo,
#endif
    constructEntryCompletionInlineCompletion,
#if defined(ENABLE_OVERLOADING)
    entryCompletionInlineCompletion         ,
#endif
    getEntryCompletionInlineCompletion      ,
    setEntryCompletionInlineCompletion      ,


-- ** inlineSelection #attr:inlineSelection#
-- | Determines whether the possible completions on the popup
-- will appear in the entry as you navigate through them.

#if defined(ENABLE_OVERLOADING)
    EntryCompletionInlineSelectionPropertyInfo,
#endif
    constructEntryCompletionInlineSelection ,
#if defined(ENABLE_OVERLOADING)
    entryCompletionInlineSelection          ,
#endif
    getEntryCompletionInlineSelection       ,
    setEntryCompletionInlineSelection       ,


-- ** minimumKeyLength #attr:minimumKeyLength#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    EntryCompletionMinimumKeyLengthPropertyInfo,
#endif
    constructEntryCompletionMinimumKeyLength,
#if defined(ENABLE_OVERLOADING)
    entryCompletionMinimumKeyLength         ,
#endif
    getEntryCompletionMinimumKeyLength      ,
    setEntryCompletionMinimumKeyLength      ,


-- ** model #attr:model#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    EntryCompletionModelPropertyInfo        ,
#endif
    clearEntryCompletionModel               ,
    constructEntryCompletionModel           ,
#if defined(ENABLE_OVERLOADING)
    entryCompletionModel                    ,
#endif
    getEntryCompletionModel                 ,
    setEntryCompletionModel                 ,


-- ** popupCompletion #attr:popupCompletion#
-- | Determines whether the possible completions should be
-- shown in a popup window.

#if defined(ENABLE_OVERLOADING)
    EntryCompletionPopupCompletionPropertyInfo,
#endif
    constructEntryCompletionPopupCompletion ,
#if defined(ENABLE_OVERLOADING)
    entryCompletionPopupCompletion          ,
#endif
    getEntryCompletionPopupCompletion       ,
    setEntryCompletionPopupCompletion       ,


-- ** popupSetWidth #attr:popupSetWidth#
-- | Determines whether the completions popup window will be
-- resized to the width of the entry.

#if defined(ENABLE_OVERLOADING)
    EntryCompletionPopupSetWidthPropertyInfo,
#endif
    constructEntryCompletionPopupSetWidth   ,
#if defined(ENABLE_OVERLOADING)
    entryCompletionPopupSetWidth            ,
#endif
    getEntryCompletionPopupSetWidth         ,
    setEntryCompletionPopupSetWidth         ,


-- ** popupSingleMatch #attr:popupSingleMatch#
-- | Determines whether the completions popup window will shown
-- for a single possible completion.
-- 
-- You probably want to set this to 'P.False' if you are using
-- [EntryCompletion:inlineCompletion]("GI.Gtk.Objects.EntryCompletion#g:attr:inlineCompletion").

#if defined(ENABLE_OVERLOADING)
    EntryCompletionPopupSingleMatchPropertyInfo,
#endif
    constructEntryCompletionPopupSingleMatch,
#if defined(ENABLE_OVERLOADING)
    entryCompletionPopupSingleMatch         ,
#endif
    getEntryCompletionPopupSingleMatch      ,
    setEntryCompletionPopupSingleMatch      ,


-- ** textColumn #attr:textColumn#
-- | The column of the model containing the strings.
-- 
-- Note that the strings must be UTF-8.

#if defined(ENABLE_OVERLOADING)
    EntryCompletionTextColumnPropertyInfo   ,
#endif
    constructEntryCompletionTextColumn      ,
#if defined(ENABLE_OVERLOADING)
    entryCompletionTextColumn               ,
#endif
    getEntryCompletionTextColumn            ,
    setEntryCompletionTextColumn            ,




 -- * Signals


-- ** cursorOnMatch #signal:cursorOnMatch#

    EntryCompletionCursorOnMatchCallback    ,
#if defined(ENABLE_OVERLOADING)
    EntryCompletionCursorOnMatchSignalInfo  ,
#endif
    afterEntryCompletionCursorOnMatch       ,
    onEntryCompletionCursorOnMatch          ,


-- ** insertPrefix #signal:insertPrefix#

    EntryCompletionInsertPrefixCallback     ,
#if defined(ENABLE_OVERLOADING)
    EntryCompletionInsertPrefixSignalInfo   ,
#endif
    afterEntryCompletionInsertPrefix        ,
    onEntryCompletionInsertPrefix           ,


-- ** matchSelected #signal:matchSelected#

    EntryCompletionMatchSelectedCallback    ,
#if defined(ENABLE_OVERLOADING)
    EntryCompletionMatchSelectedSignalInfo  ,
#endif
    afterEntryCompletionMatchSelected       ,
    onEntryCompletionMatchSelected          ,


-- ** noMatches #signal:noMatches#

    EntryCompletionNoMatchesCallback        ,
#if defined(ENABLE_OVERLOADING)
    EntryCompletionNoMatchesSignalInfo      ,
#endif
    afterEntryCompletionNoMatches           ,
    onEntryCompletionNoMatches              ,




    ) 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 GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.CellLayout as Gtk.CellLayout
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.TreeModel as Gtk.TreeModel
import {-# SOURCE #-} qualified GI.Gtk.Objects.CellArea as Gtk.CellArea
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Structs.TreeIter as Gtk.TreeIter

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

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

foreign import ccall "gtk_entry_completion_get_type"
    c_gtk_entry_completion_get_type :: IO B.Types.GType

instance B.Types.TypedObject EntryCompletion where
    glibType :: IO GType
glibType = IO GType
c_gtk_entry_completion_get_type

instance B.Types.GObject EntryCompletion

-- | Type class for types which can be safely cast to `EntryCompletion`, for instance with `toEntryCompletion`.
class (SP.GObject o, O.IsDescendantOf EntryCompletion o) => IsEntryCompletion o
instance (SP.GObject o, O.IsDescendantOf EntryCompletion o) => IsEntryCompletion o

instance O.HasParentTypes EntryCompletion
type instance O.ParentTypes EntryCompletion = '[GObject.Object.Object, Gtk.Buildable.Buildable, Gtk.CellLayout.CellLayout]

-- | Cast to `EntryCompletion`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toEntryCompletion :: (MIO.MonadIO m, IsEntryCompletion o) => o -> m EntryCompletion
toEntryCompletion :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m EntryCompletion
toEntryCompletion = IO EntryCompletion -> m EntryCompletion
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO EntryCompletion -> m EntryCompletion)
-> (o -> IO EntryCompletion) -> o -> m EntryCompletion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr EntryCompletion -> EntryCompletion)
-> o -> IO EntryCompletion
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr EntryCompletion -> EntryCompletion
EntryCompletion

-- | Convert 'EntryCompletion' 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 EntryCompletion) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_entry_completion_get_type
    gvalueSet_ :: Ptr GValue -> Maybe EntryCompletion -> IO ()
gvalueSet_ Ptr GValue
gv Maybe EntryCompletion
P.Nothing = Ptr GValue -> Ptr EntryCompletion -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr EntryCompletion
forall a. Ptr a
FP.nullPtr :: FP.Ptr EntryCompletion)
    gvalueSet_ Ptr GValue
gv (P.Just EntryCompletion
obj) = EntryCompletion -> (Ptr EntryCompletion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EntryCompletion
obj (Ptr GValue -> Ptr EntryCompletion -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe EntryCompletion)
gvalueGet_ Ptr GValue
gv = do
        Ptr EntryCompletion
ptr <- Ptr GValue -> IO (Ptr EntryCompletion)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr EntryCompletion)
        if Ptr EntryCompletion
ptr Ptr EntryCompletion -> Ptr EntryCompletion -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr EntryCompletion
forall a. Ptr a
FP.nullPtr
        then EntryCompletion -> Maybe EntryCompletion
forall a. a -> Maybe a
P.Just (EntryCompletion -> Maybe EntryCompletion)
-> IO EntryCompletion -> IO (Maybe EntryCompletion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr EntryCompletion -> EntryCompletion)
-> Ptr EntryCompletion -> IO EntryCompletion
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr EntryCompletion -> EntryCompletion
EntryCompletion Ptr EntryCompletion
ptr
        else Maybe EntryCompletion -> IO (Maybe EntryCompletion)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe EntryCompletion
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveEntryCompletionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveEntryCompletionMethod "addAttribute" o = Gtk.CellLayout.CellLayoutAddAttributeMethodInfo
    ResolveEntryCompletionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveEntryCompletionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveEntryCompletionMethod "clear" o = Gtk.CellLayout.CellLayoutClearMethodInfo
    ResolveEntryCompletionMethod "clearAttributes" o = Gtk.CellLayout.CellLayoutClearAttributesMethodInfo
    ResolveEntryCompletionMethod "complete" o = EntryCompletionCompleteMethodInfo
    ResolveEntryCompletionMethod "computePrefix" o = EntryCompletionComputePrefixMethodInfo
    ResolveEntryCompletionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveEntryCompletionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveEntryCompletionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveEntryCompletionMethod "insertPrefix" o = EntryCompletionInsertPrefixMethodInfo
    ResolveEntryCompletionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveEntryCompletionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveEntryCompletionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveEntryCompletionMethod "packEnd" o = Gtk.CellLayout.CellLayoutPackEndMethodInfo
    ResolveEntryCompletionMethod "packStart" o = Gtk.CellLayout.CellLayoutPackStartMethodInfo
    ResolveEntryCompletionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveEntryCompletionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveEntryCompletionMethod "reorder" o = Gtk.CellLayout.CellLayoutReorderMethodInfo
    ResolveEntryCompletionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveEntryCompletionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveEntryCompletionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveEntryCompletionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveEntryCompletionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveEntryCompletionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveEntryCompletionMethod "getArea" o = Gtk.CellLayout.CellLayoutGetAreaMethodInfo
    ResolveEntryCompletionMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveEntryCompletionMethod "getCells" o = Gtk.CellLayout.CellLayoutGetCellsMethodInfo
    ResolveEntryCompletionMethod "getCompletionPrefix" o = EntryCompletionGetCompletionPrefixMethodInfo
    ResolveEntryCompletionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveEntryCompletionMethod "getEntry" o = EntryCompletionGetEntryMethodInfo
    ResolveEntryCompletionMethod "getInlineCompletion" o = EntryCompletionGetInlineCompletionMethodInfo
    ResolveEntryCompletionMethod "getInlineSelection" o = EntryCompletionGetInlineSelectionMethodInfo
    ResolveEntryCompletionMethod "getMinimumKeyLength" o = EntryCompletionGetMinimumKeyLengthMethodInfo
    ResolveEntryCompletionMethod "getModel" o = EntryCompletionGetModelMethodInfo
    ResolveEntryCompletionMethod "getPopupCompletion" o = EntryCompletionGetPopupCompletionMethodInfo
    ResolveEntryCompletionMethod "getPopupSetWidth" o = EntryCompletionGetPopupSetWidthMethodInfo
    ResolveEntryCompletionMethod "getPopupSingleMatch" o = EntryCompletionGetPopupSingleMatchMethodInfo
    ResolveEntryCompletionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveEntryCompletionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveEntryCompletionMethod "getTextColumn" o = EntryCompletionGetTextColumnMethodInfo
    ResolveEntryCompletionMethod "setCellDataFunc" o = Gtk.CellLayout.CellLayoutSetCellDataFuncMethodInfo
    ResolveEntryCompletionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveEntryCompletionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveEntryCompletionMethod "setInlineCompletion" o = EntryCompletionSetInlineCompletionMethodInfo
    ResolveEntryCompletionMethod "setInlineSelection" o = EntryCompletionSetInlineSelectionMethodInfo
    ResolveEntryCompletionMethod "setMatchFunc" o = EntryCompletionSetMatchFuncMethodInfo
    ResolveEntryCompletionMethod "setMinimumKeyLength" o = EntryCompletionSetMinimumKeyLengthMethodInfo
    ResolveEntryCompletionMethod "setModel" o = EntryCompletionSetModelMethodInfo
    ResolveEntryCompletionMethod "setPopupCompletion" o = EntryCompletionSetPopupCompletionMethodInfo
    ResolveEntryCompletionMethod "setPopupSetWidth" o = EntryCompletionSetPopupSetWidthMethodInfo
    ResolveEntryCompletionMethod "setPopupSingleMatch" o = EntryCompletionSetPopupSingleMatchMethodInfo
    ResolveEntryCompletionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveEntryCompletionMethod "setTextColumn" o = EntryCompletionSetTextColumnMethodInfo
    ResolveEntryCompletionMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveEntryCompletionMethod t EntryCompletion, O.OverloadedMethod info EntryCompletion p) => OL.IsLabel t (EntryCompletion -> 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 ~ ResolveEntryCompletionMethod t EntryCompletion, O.OverloadedMethod info EntryCompletion p, R.HasField t EntryCompletion p) => R.HasField t EntryCompletion p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- signal EntryCompletion::cursor-on-match
-- | Emitted when a match from the cursor is on a match of the list.
-- 
-- The default behaviour is to replace the contents
-- of the entry with the contents of the text column in the row
-- pointed to by /@iter@/.
-- 
-- Note that /@model@/ is the model that was passed to
-- 'GI.Gtk.Objects.EntryCompletion.entryCompletionSetModel'.
type EntryCompletionCursorOnMatchCallback =
    Gtk.TreeModel.TreeModel
    -- ^ /@model@/: the @GtkTreeModel@ containing the matches
    -> Gtk.TreeIter.TreeIter
    -- ^ /@iter@/: a @GtkTreeIter@ positioned at the selected match
    -> IO Bool
    -- ^ __Returns:__ 'P.True' if the signal has been handled

type C_EntryCompletionCursorOnMatchCallback =
    Ptr EntryCompletion ->                  -- object
    Ptr Gtk.TreeModel.TreeModel ->
    Ptr Gtk.TreeIter.TreeIter ->
    Ptr () ->                               -- user_data
    IO CInt

-- | Generate a function pointer callable from C code, from a `C_EntryCompletionCursorOnMatchCallback`.
foreign import ccall "wrapper"
    mk_EntryCompletionCursorOnMatchCallback :: C_EntryCompletionCursorOnMatchCallback -> IO (FunPtr C_EntryCompletionCursorOnMatchCallback)

wrap_EntryCompletionCursorOnMatchCallback :: 
    GObject a => (a -> EntryCompletionCursorOnMatchCallback) ->
    C_EntryCompletionCursorOnMatchCallback
wrap_EntryCompletionCursorOnMatchCallback :: forall a.
GObject a =>
(a -> EntryCompletionCursorOnMatchCallback)
-> C_EntryCompletionCursorOnMatchCallback
wrap_EntryCompletionCursorOnMatchCallback a -> EntryCompletionCursorOnMatchCallback
gi'cb Ptr EntryCompletion
gi'selfPtr Ptr TreeModel
model Ptr TreeIter
iter Ptr ()
_ = do
    TreeModel
model' <- ((ManagedPtr TreeModel -> TreeModel)
-> Ptr TreeModel -> IO TreeModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TreeModel -> TreeModel
Gtk.TreeModel.TreeModel) Ptr TreeModel
model
    Ptr TreeIter -> (TreeIter -> IO CInt) -> IO CInt
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient  Ptr TreeIter
iter ((TreeIter -> IO CInt) -> IO CInt)
-> (TreeIter -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \TreeIter
iter' -> do
        Bool
result <- Ptr EntryCompletion -> (EntryCompletion -> IO Bool) -> IO Bool
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr EntryCompletion
gi'selfPtr ((EntryCompletion -> IO Bool) -> IO Bool)
-> (EntryCompletion -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \EntryCompletion
gi'self -> a -> EntryCompletionCursorOnMatchCallback
gi'cb (EntryCompletion -> a
forall a b. Coercible a b => a -> b
Coerce.coerce EntryCompletion
gi'self)  TreeModel
model' TreeIter
iter'
        let result' :: CInt
result' = (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
result
        CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [cursorOnMatch](#signal:cursorOnMatch) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' entryCompletion #cursorOnMatch callback
-- @
-- 
-- 
onEntryCompletionCursorOnMatch :: (IsEntryCompletion a, MonadIO m) => a -> ((?self :: a) => EntryCompletionCursorOnMatchCallback) -> m SignalHandlerId
onEntryCompletionCursorOnMatch :: forall a (m :: * -> *).
(IsEntryCompletion a, MonadIO m) =>
a
-> ((?self::a) => EntryCompletionCursorOnMatchCallback)
-> m SignalHandlerId
onEntryCompletionCursorOnMatch a
obj (?self::a) => EntryCompletionCursorOnMatchCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> EntryCompletionCursorOnMatchCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => EntryCompletionCursorOnMatchCallback
EntryCompletionCursorOnMatchCallback
cb
    let wrapped' :: C_EntryCompletionCursorOnMatchCallback
wrapped' = (a -> EntryCompletionCursorOnMatchCallback)
-> C_EntryCompletionCursorOnMatchCallback
forall a.
GObject a =>
(a -> EntryCompletionCursorOnMatchCallback)
-> C_EntryCompletionCursorOnMatchCallback
wrap_EntryCompletionCursorOnMatchCallback a -> EntryCompletionCursorOnMatchCallback
wrapped
    FunPtr C_EntryCompletionCursorOnMatchCallback
wrapped'' <- C_EntryCompletionCursorOnMatchCallback
-> IO (FunPtr C_EntryCompletionCursorOnMatchCallback)
mk_EntryCompletionCursorOnMatchCallback C_EntryCompletionCursorOnMatchCallback
wrapped'
    a
-> Text
-> FunPtr C_EntryCompletionCursorOnMatchCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"cursor-on-match" FunPtr C_EntryCompletionCursorOnMatchCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [cursorOnMatch](#signal:cursorOnMatch) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' entryCompletion #cursorOnMatch callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterEntryCompletionCursorOnMatch :: (IsEntryCompletion a, MonadIO m) => a -> ((?self :: a) => EntryCompletionCursorOnMatchCallback) -> m SignalHandlerId
afterEntryCompletionCursorOnMatch :: forall a (m :: * -> *).
(IsEntryCompletion a, MonadIO m) =>
a
-> ((?self::a) => EntryCompletionCursorOnMatchCallback)
-> m SignalHandlerId
afterEntryCompletionCursorOnMatch a
obj (?self::a) => EntryCompletionCursorOnMatchCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> EntryCompletionCursorOnMatchCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => EntryCompletionCursorOnMatchCallback
EntryCompletionCursorOnMatchCallback
cb
    let wrapped' :: C_EntryCompletionCursorOnMatchCallback
wrapped' = (a -> EntryCompletionCursorOnMatchCallback)
-> C_EntryCompletionCursorOnMatchCallback
forall a.
GObject a =>
(a -> EntryCompletionCursorOnMatchCallback)
-> C_EntryCompletionCursorOnMatchCallback
wrap_EntryCompletionCursorOnMatchCallback a -> EntryCompletionCursorOnMatchCallback
wrapped
    FunPtr C_EntryCompletionCursorOnMatchCallback
wrapped'' <- C_EntryCompletionCursorOnMatchCallback
-> IO (FunPtr C_EntryCompletionCursorOnMatchCallback)
mk_EntryCompletionCursorOnMatchCallback C_EntryCompletionCursorOnMatchCallback
wrapped'
    a
-> Text
-> FunPtr C_EntryCompletionCursorOnMatchCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"cursor-on-match" FunPtr C_EntryCompletionCursorOnMatchCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data EntryCompletionCursorOnMatchSignalInfo
instance SignalInfo EntryCompletionCursorOnMatchSignalInfo where
    type HaskellCallbackType EntryCompletionCursorOnMatchSignalInfo = EntryCompletionCursorOnMatchCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_EntryCompletionCursorOnMatchCallback cb
        cb'' <- mk_EntryCompletionCursorOnMatchCallback cb'
        connectSignalFunPtr obj "cursor-on-match" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion::cursor-on-match"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:signal:cursorOnMatch"})

#endif

-- signal EntryCompletion::insert-prefix
-- | Emitted when the inline autocompletion is triggered.
-- 
-- The default behaviour is to make the entry display the
-- whole prefix and select the newly inserted part.
-- 
-- Applications may connect to this signal in order to insert only a
-- smaller part of the /@prefix@/ into the entry - e.g. the entry used in
-- the @GtkFileChooser@ inserts only the part of the prefix up to the
-- next \'\/\'.
type EntryCompletionInsertPrefixCallback =
    T.Text
    -- ^ /@prefix@/: the common prefix of all possible completions
    -> IO Bool
    -- ^ __Returns:__ 'P.True' if the signal has been handled

type C_EntryCompletionInsertPrefixCallback =
    Ptr EntryCompletion ->                  -- object
    CString ->
    Ptr () ->                               -- user_data
    IO CInt

-- | Generate a function pointer callable from C code, from a `C_EntryCompletionInsertPrefixCallback`.
foreign import ccall "wrapper"
    mk_EntryCompletionInsertPrefixCallback :: C_EntryCompletionInsertPrefixCallback -> IO (FunPtr C_EntryCompletionInsertPrefixCallback)

wrap_EntryCompletionInsertPrefixCallback :: 
    GObject a => (a -> EntryCompletionInsertPrefixCallback) ->
    C_EntryCompletionInsertPrefixCallback
wrap_EntryCompletionInsertPrefixCallback :: forall a.
GObject a =>
(a -> EntryCompletionInsertPrefixCallback)
-> C_EntryCompletionInsertPrefixCallback
wrap_EntryCompletionInsertPrefixCallback a -> EntryCompletionInsertPrefixCallback
gi'cb Ptr EntryCompletion
gi'selfPtr CString
prefix Ptr ()
_ = do
    Text
prefix' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
prefix
    Bool
result <- Ptr EntryCompletion -> (EntryCompletion -> IO Bool) -> IO Bool
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr EntryCompletion
gi'selfPtr ((EntryCompletion -> IO Bool) -> IO Bool)
-> (EntryCompletion -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \EntryCompletion
gi'self -> a -> EntryCompletionInsertPrefixCallback
gi'cb (EntryCompletion -> a
forall a b. Coercible a b => a -> b
Coerce.coerce EntryCompletion
gi'self)  Text
prefix'
    let result' :: CInt
result' = (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
result
    CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [insertPrefix](#signal:insertPrefix) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' entryCompletion #insertPrefix callback
-- @
-- 
-- 
onEntryCompletionInsertPrefix :: (IsEntryCompletion a, MonadIO m) => a -> ((?self :: a) => EntryCompletionInsertPrefixCallback) -> m SignalHandlerId
onEntryCompletionInsertPrefix :: forall a (m :: * -> *).
(IsEntryCompletion a, MonadIO m) =>
a
-> ((?self::a) => EntryCompletionInsertPrefixCallback)
-> m SignalHandlerId
onEntryCompletionInsertPrefix a
obj (?self::a) => EntryCompletionInsertPrefixCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> EntryCompletionInsertPrefixCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => EntryCompletionInsertPrefixCallback
EntryCompletionInsertPrefixCallback
cb
    let wrapped' :: C_EntryCompletionInsertPrefixCallback
wrapped' = (a -> EntryCompletionInsertPrefixCallback)
-> C_EntryCompletionInsertPrefixCallback
forall a.
GObject a =>
(a -> EntryCompletionInsertPrefixCallback)
-> C_EntryCompletionInsertPrefixCallback
wrap_EntryCompletionInsertPrefixCallback a -> EntryCompletionInsertPrefixCallback
wrapped
    FunPtr C_EntryCompletionInsertPrefixCallback
wrapped'' <- C_EntryCompletionInsertPrefixCallback
-> IO (FunPtr C_EntryCompletionInsertPrefixCallback)
mk_EntryCompletionInsertPrefixCallback C_EntryCompletionInsertPrefixCallback
wrapped'
    a
-> Text
-> FunPtr C_EntryCompletionInsertPrefixCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"insert-prefix" FunPtr C_EntryCompletionInsertPrefixCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [insertPrefix](#signal:insertPrefix) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' entryCompletion #insertPrefix callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterEntryCompletionInsertPrefix :: (IsEntryCompletion a, MonadIO m) => a -> ((?self :: a) => EntryCompletionInsertPrefixCallback) -> m SignalHandlerId
afterEntryCompletionInsertPrefix :: forall a (m :: * -> *).
(IsEntryCompletion a, MonadIO m) =>
a
-> ((?self::a) => EntryCompletionInsertPrefixCallback)
-> m SignalHandlerId
afterEntryCompletionInsertPrefix a
obj (?self::a) => EntryCompletionInsertPrefixCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> EntryCompletionInsertPrefixCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => EntryCompletionInsertPrefixCallback
EntryCompletionInsertPrefixCallback
cb
    let wrapped' :: C_EntryCompletionInsertPrefixCallback
wrapped' = (a -> EntryCompletionInsertPrefixCallback)
-> C_EntryCompletionInsertPrefixCallback
forall a.
GObject a =>
(a -> EntryCompletionInsertPrefixCallback)
-> C_EntryCompletionInsertPrefixCallback
wrap_EntryCompletionInsertPrefixCallback a -> EntryCompletionInsertPrefixCallback
wrapped
    FunPtr C_EntryCompletionInsertPrefixCallback
wrapped'' <- C_EntryCompletionInsertPrefixCallback
-> IO (FunPtr C_EntryCompletionInsertPrefixCallback)
mk_EntryCompletionInsertPrefixCallback C_EntryCompletionInsertPrefixCallback
wrapped'
    a
-> Text
-> FunPtr C_EntryCompletionInsertPrefixCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"insert-prefix" FunPtr C_EntryCompletionInsertPrefixCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data EntryCompletionInsertPrefixSignalInfo
instance SignalInfo EntryCompletionInsertPrefixSignalInfo where
    type HaskellCallbackType EntryCompletionInsertPrefixSignalInfo = EntryCompletionInsertPrefixCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_EntryCompletionInsertPrefixCallback cb
        cb'' <- mk_EntryCompletionInsertPrefixCallback cb'
        connectSignalFunPtr obj "insert-prefix" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion::insert-prefix"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:signal:insertPrefix"})

#endif

-- signal EntryCompletion::match-selected
-- | Emitted when a match from the list is selected.
-- 
-- The default behaviour is to replace the contents of the
-- entry with the contents of the text column in the row
-- pointed to by /@iter@/.
-- 
-- Note that /@model@/ is the model that was passed to
-- 'GI.Gtk.Objects.EntryCompletion.entryCompletionSetModel'.
type EntryCompletionMatchSelectedCallback =
    Gtk.TreeModel.TreeModel
    -- ^ /@model@/: the @GtkTreeModel@ containing the matches
    -> Gtk.TreeIter.TreeIter
    -- ^ /@iter@/: a @GtkTreeIter@ positioned at the selected match
    -> IO Bool
    -- ^ __Returns:__ 'P.True' if the signal has been handled

type C_EntryCompletionMatchSelectedCallback =
    Ptr EntryCompletion ->                  -- object
    Ptr Gtk.TreeModel.TreeModel ->
    Ptr Gtk.TreeIter.TreeIter ->
    Ptr () ->                               -- user_data
    IO CInt

-- | Generate a function pointer callable from C code, from a `C_EntryCompletionMatchSelectedCallback`.
foreign import ccall "wrapper"
    mk_EntryCompletionMatchSelectedCallback :: C_EntryCompletionMatchSelectedCallback -> IO (FunPtr C_EntryCompletionMatchSelectedCallback)

wrap_EntryCompletionMatchSelectedCallback :: 
    GObject a => (a -> EntryCompletionMatchSelectedCallback) ->
    C_EntryCompletionMatchSelectedCallback
wrap_EntryCompletionMatchSelectedCallback :: forall a.
GObject a =>
(a -> EntryCompletionCursorOnMatchCallback)
-> C_EntryCompletionCursorOnMatchCallback
wrap_EntryCompletionMatchSelectedCallback a -> EntryCompletionCursorOnMatchCallback
gi'cb Ptr EntryCompletion
gi'selfPtr Ptr TreeModel
model Ptr TreeIter
iter Ptr ()
_ = do
    TreeModel
model' <- ((ManagedPtr TreeModel -> TreeModel)
-> Ptr TreeModel -> IO TreeModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TreeModel -> TreeModel
Gtk.TreeModel.TreeModel) Ptr TreeModel
model
    Ptr TreeIter -> (TreeIter -> IO CInt) -> IO CInt
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient  Ptr TreeIter
iter ((TreeIter -> IO CInt) -> IO CInt)
-> (TreeIter -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \TreeIter
iter' -> do
        Bool
result <- Ptr EntryCompletion -> (EntryCompletion -> IO Bool) -> IO Bool
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr EntryCompletion
gi'selfPtr ((EntryCompletion -> IO Bool) -> IO Bool)
-> (EntryCompletion -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \EntryCompletion
gi'self -> a -> EntryCompletionCursorOnMatchCallback
gi'cb (EntryCompletion -> a
forall a b. Coercible a b => a -> b
Coerce.coerce EntryCompletion
gi'self)  TreeModel
model' TreeIter
iter'
        let result' :: CInt
result' = (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
result
        CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [matchSelected](#signal:matchSelected) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' entryCompletion #matchSelected callback
-- @
-- 
-- 
onEntryCompletionMatchSelected :: (IsEntryCompletion a, MonadIO m) => a -> ((?self :: a) => EntryCompletionMatchSelectedCallback) -> m SignalHandlerId
onEntryCompletionMatchSelected :: forall a (m :: * -> *).
(IsEntryCompletion a, MonadIO m) =>
a
-> ((?self::a) => EntryCompletionCursorOnMatchCallback)
-> m SignalHandlerId
onEntryCompletionMatchSelected a
obj (?self::a) => EntryCompletionCursorOnMatchCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> EntryCompletionCursorOnMatchCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => EntryCompletionCursorOnMatchCallback
EntryCompletionCursorOnMatchCallback
cb
    let wrapped' :: C_EntryCompletionCursorOnMatchCallback
wrapped' = (a -> EntryCompletionCursorOnMatchCallback)
-> C_EntryCompletionCursorOnMatchCallback
forall a.
GObject a =>
(a -> EntryCompletionCursorOnMatchCallback)
-> C_EntryCompletionCursorOnMatchCallback
wrap_EntryCompletionMatchSelectedCallback a -> EntryCompletionCursorOnMatchCallback
wrapped
    FunPtr C_EntryCompletionCursorOnMatchCallback
wrapped'' <- C_EntryCompletionCursorOnMatchCallback
-> IO (FunPtr C_EntryCompletionCursorOnMatchCallback)
mk_EntryCompletionMatchSelectedCallback C_EntryCompletionCursorOnMatchCallback
wrapped'
    a
-> Text
-> FunPtr C_EntryCompletionCursorOnMatchCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"match-selected" FunPtr C_EntryCompletionCursorOnMatchCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [matchSelected](#signal:matchSelected) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' entryCompletion #matchSelected callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterEntryCompletionMatchSelected :: (IsEntryCompletion a, MonadIO m) => a -> ((?self :: a) => EntryCompletionMatchSelectedCallback) -> m SignalHandlerId
afterEntryCompletionMatchSelected :: forall a (m :: * -> *).
(IsEntryCompletion a, MonadIO m) =>
a
-> ((?self::a) => EntryCompletionCursorOnMatchCallback)
-> m SignalHandlerId
afterEntryCompletionMatchSelected a
obj (?self::a) => EntryCompletionCursorOnMatchCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> EntryCompletionCursorOnMatchCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => EntryCompletionCursorOnMatchCallback
EntryCompletionCursorOnMatchCallback
cb
    let wrapped' :: C_EntryCompletionCursorOnMatchCallback
wrapped' = (a -> EntryCompletionCursorOnMatchCallback)
-> C_EntryCompletionCursorOnMatchCallback
forall a.
GObject a =>
(a -> EntryCompletionCursorOnMatchCallback)
-> C_EntryCompletionCursorOnMatchCallback
wrap_EntryCompletionMatchSelectedCallback a -> EntryCompletionCursorOnMatchCallback
wrapped
    FunPtr C_EntryCompletionCursorOnMatchCallback
wrapped'' <- C_EntryCompletionCursorOnMatchCallback
-> IO (FunPtr C_EntryCompletionCursorOnMatchCallback)
mk_EntryCompletionMatchSelectedCallback C_EntryCompletionCursorOnMatchCallback
wrapped'
    a
-> Text
-> FunPtr C_EntryCompletionCursorOnMatchCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"match-selected" FunPtr C_EntryCompletionCursorOnMatchCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data EntryCompletionMatchSelectedSignalInfo
instance SignalInfo EntryCompletionMatchSelectedSignalInfo where
    type HaskellCallbackType EntryCompletionMatchSelectedSignalInfo = EntryCompletionMatchSelectedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_EntryCompletionMatchSelectedCallback cb
        cb'' <- mk_EntryCompletionMatchSelectedCallback cb'
        connectSignalFunPtr obj "match-selected" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion::match-selected"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:signal:matchSelected"})

#endif

-- signal EntryCompletion::no-matches
-- | Emitted when the filter model has zero
-- number of rows in completion_complete method.
-- 
-- In other words when @GtkEntryCompletion@ is out of suggestions.
type EntryCompletionNoMatchesCallback =
    IO ()

type C_EntryCompletionNoMatchesCallback =
    Ptr EntryCompletion ->                  -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_EntryCompletionNoMatchesCallback`.
foreign import ccall "wrapper"
    mk_EntryCompletionNoMatchesCallback :: C_EntryCompletionNoMatchesCallback -> IO (FunPtr C_EntryCompletionNoMatchesCallback)

wrap_EntryCompletionNoMatchesCallback :: 
    GObject a => (a -> EntryCompletionNoMatchesCallback) ->
    C_EntryCompletionNoMatchesCallback
wrap_EntryCompletionNoMatchesCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_EntryCompletionNoMatchesCallback
wrap_EntryCompletionNoMatchesCallback a -> IO ()
gi'cb Ptr EntryCompletion
gi'selfPtr Ptr ()
_ = do
    Ptr EntryCompletion -> (EntryCompletion -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr EntryCompletion
gi'selfPtr ((EntryCompletion -> IO ()) -> IO ())
-> (EntryCompletion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \EntryCompletion
gi'self -> a -> IO ()
gi'cb (EntryCompletion -> a
forall a b. Coercible a b => a -> b
Coerce.coerce EntryCompletion
gi'self) 


-- | Connect a signal handler for the [noMatches](#signal:noMatches) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' entryCompletion #noMatches callback
-- @
-- 
-- 
onEntryCompletionNoMatches :: (IsEntryCompletion a, MonadIO m) => a -> ((?self :: a) => EntryCompletionNoMatchesCallback) -> m SignalHandlerId
onEntryCompletionNoMatches :: forall a (m :: * -> *).
(IsEntryCompletion a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onEntryCompletionNoMatches a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_EntryCompletionNoMatchesCallback
wrapped' = (a -> IO ()) -> C_EntryCompletionNoMatchesCallback
forall a.
GObject a =>
(a -> IO ()) -> C_EntryCompletionNoMatchesCallback
wrap_EntryCompletionNoMatchesCallback a -> IO ()
wrapped
    FunPtr C_EntryCompletionNoMatchesCallback
wrapped'' <- C_EntryCompletionNoMatchesCallback
-> IO (FunPtr C_EntryCompletionNoMatchesCallback)
mk_EntryCompletionNoMatchesCallback C_EntryCompletionNoMatchesCallback
wrapped'
    a
-> Text
-> FunPtr C_EntryCompletionNoMatchesCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"no-matches" FunPtr C_EntryCompletionNoMatchesCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [noMatches](#signal:noMatches) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' entryCompletion #noMatches callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterEntryCompletionNoMatches :: (IsEntryCompletion a, MonadIO m) => a -> ((?self :: a) => EntryCompletionNoMatchesCallback) -> m SignalHandlerId
afterEntryCompletionNoMatches :: forall a (m :: * -> *).
(IsEntryCompletion a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterEntryCompletionNoMatches a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_EntryCompletionNoMatchesCallback
wrapped' = (a -> IO ()) -> C_EntryCompletionNoMatchesCallback
forall a.
GObject a =>
(a -> IO ()) -> C_EntryCompletionNoMatchesCallback
wrap_EntryCompletionNoMatchesCallback a -> IO ()
wrapped
    FunPtr C_EntryCompletionNoMatchesCallback
wrapped'' <- C_EntryCompletionNoMatchesCallback
-> IO (FunPtr C_EntryCompletionNoMatchesCallback)
mk_EntryCompletionNoMatchesCallback C_EntryCompletionNoMatchesCallback
wrapped'
    a
-> Text
-> FunPtr C_EntryCompletionNoMatchesCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"no-matches" FunPtr C_EntryCompletionNoMatchesCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data EntryCompletionNoMatchesSignalInfo
instance SignalInfo EntryCompletionNoMatchesSignalInfo where
    type HaskellCallbackType EntryCompletionNoMatchesSignalInfo = EntryCompletionNoMatchesCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_EntryCompletionNoMatchesCallback cb
        cb'' <- mk_EntryCompletionNoMatchesCallback cb'
        connectSignalFunPtr obj "no-matches" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion::no-matches"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:signal:noMatches"})

#endif

-- VVV Prop "cell-area"
   -- Type: TInterface (Name {namespace = "Gtk", name = "CellArea"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@cell-area@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' entryCompletion #cellArea
-- @
getEntryCompletionCellArea :: (MonadIO m, IsEntryCompletion o) => o -> m (Maybe Gtk.CellArea.CellArea)
getEntryCompletionCellArea :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m (Maybe CellArea)
getEntryCompletionCellArea o
obj = IO (Maybe CellArea) -> m (Maybe CellArea)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe CellArea) -> m (Maybe CellArea))
-> IO (Maybe CellArea) -> m (Maybe CellArea)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr CellArea -> CellArea)
-> IO (Maybe CellArea)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"cell-area" ManagedPtr CellArea -> CellArea
Gtk.CellArea.CellArea

-- | Construct a `GValueConstruct` with valid value for the “@cell-area@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEntryCompletionCellArea :: (IsEntryCompletion o, MIO.MonadIO m, Gtk.CellArea.IsCellArea a) => a -> m (GValueConstruct o)
constructEntryCompletionCellArea :: forall o (m :: * -> *) a.
(IsEntryCompletion o, MonadIO m, IsCellArea a) =>
a -> m (GValueConstruct o)
constructEntryCompletionCellArea a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"cell-area" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data EntryCompletionCellAreaPropertyInfo
instance AttrInfo EntryCompletionCellAreaPropertyInfo where
    type AttrAllowedOps EntryCompletionCellAreaPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryCompletionCellAreaPropertyInfo = IsEntryCompletion
    type AttrSetTypeConstraint EntryCompletionCellAreaPropertyInfo = Gtk.CellArea.IsCellArea
    type AttrTransferTypeConstraint EntryCompletionCellAreaPropertyInfo = Gtk.CellArea.IsCellArea
    type AttrTransferType EntryCompletionCellAreaPropertyInfo = Gtk.CellArea.CellArea
    type AttrGetType EntryCompletionCellAreaPropertyInfo = (Maybe Gtk.CellArea.CellArea)
    type AttrLabel EntryCompletionCellAreaPropertyInfo = "cell-area"
    type AttrOrigin EntryCompletionCellAreaPropertyInfo = EntryCompletion
    attrGet = getEntryCompletionCellArea
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.CellArea.CellArea v
    attrConstruct = constructEntryCompletionCellArea
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.cellArea"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:cellArea"
        })
#endif

-- VVV Prop "inline-completion"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@inline-completion@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' entryCompletion #inlineCompletion
-- @
getEntryCompletionInlineCompletion :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
getEntryCompletionInlineCompletion :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m Bool
getEntryCompletionInlineCompletion o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"inline-completion"

-- | Set the value of the “@inline-completion@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' entryCompletion [ #inlineCompletion 'Data.GI.Base.Attributes.:=' value ]
-- @
setEntryCompletionInlineCompletion :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
setEntryCompletionInlineCompletion :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> Bool -> m ()
setEntryCompletionInlineCompletion o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"inline-completion" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@inline-completion@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEntryCompletionInlineCompletion :: (IsEntryCompletion o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryCompletionInlineCompletion :: forall o (m :: * -> *).
(IsEntryCompletion o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryCompletionInlineCompletion Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"inline-completion" Bool
val

#if defined(ENABLE_OVERLOADING)
data EntryCompletionInlineCompletionPropertyInfo
instance AttrInfo EntryCompletionInlineCompletionPropertyInfo where
    type AttrAllowedOps EntryCompletionInlineCompletionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryCompletionInlineCompletionPropertyInfo = IsEntryCompletion
    type AttrSetTypeConstraint EntryCompletionInlineCompletionPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryCompletionInlineCompletionPropertyInfo = (~) Bool
    type AttrTransferType EntryCompletionInlineCompletionPropertyInfo = Bool
    type AttrGetType EntryCompletionInlineCompletionPropertyInfo = Bool
    type AttrLabel EntryCompletionInlineCompletionPropertyInfo = "inline-completion"
    type AttrOrigin EntryCompletionInlineCompletionPropertyInfo = EntryCompletion
    attrGet = getEntryCompletionInlineCompletion
    attrSet = setEntryCompletionInlineCompletion
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryCompletionInlineCompletion
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.inlineCompletion"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:inlineCompletion"
        })
#endif

-- VVV Prop "inline-selection"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@inline-selection@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' entryCompletion #inlineSelection
-- @
getEntryCompletionInlineSelection :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
getEntryCompletionInlineSelection :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m Bool
getEntryCompletionInlineSelection o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"inline-selection"

-- | Set the value of the “@inline-selection@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' entryCompletion [ #inlineSelection 'Data.GI.Base.Attributes.:=' value ]
-- @
setEntryCompletionInlineSelection :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
setEntryCompletionInlineSelection :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> Bool -> m ()
setEntryCompletionInlineSelection o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"inline-selection" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@inline-selection@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEntryCompletionInlineSelection :: (IsEntryCompletion o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryCompletionInlineSelection :: forall o (m :: * -> *).
(IsEntryCompletion o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryCompletionInlineSelection Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"inline-selection" Bool
val

#if defined(ENABLE_OVERLOADING)
data EntryCompletionInlineSelectionPropertyInfo
instance AttrInfo EntryCompletionInlineSelectionPropertyInfo where
    type AttrAllowedOps EntryCompletionInlineSelectionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryCompletionInlineSelectionPropertyInfo = IsEntryCompletion
    type AttrSetTypeConstraint EntryCompletionInlineSelectionPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryCompletionInlineSelectionPropertyInfo = (~) Bool
    type AttrTransferType EntryCompletionInlineSelectionPropertyInfo = Bool
    type AttrGetType EntryCompletionInlineSelectionPropertyInfo = Bool
    type AttrLabel EntryCompletionInlineSelectionPropertyInfo = "inline-selection"
    type AttrOrigin EntryCompletionInlineSelectionPropertyInfo = EntryCompletion
    attrGet = getEntryCompletionInlineSelection
    attrSet = setEntryCompletionInlineSelection
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryCompletionInlineSelection
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.inlineSelection"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:inlineSelection"
        })
#endif

-- VVV Prop "minimum-key-length"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@minimum-key-length@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' entryCompletion #minimumKeyLength
-- @
getEntryCompletionMinimumKeyLength :: (MonadIO m, IsEntryCompletion o) => o -> m Int32
getEntryCompletionMinimumKeyLength :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m Int32
getEntryCompletionMinimumKeyLength o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"minimum-key-length"

-- | Set the value of the “@minimum-key-length@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' entryCompletion [ #minimumKeyLength 'Data.GI.Base.Attributes.:=' value ]
-- @
setEntryCompletionMinimumKeyLength :: (MonadIO m, IsEntryCompletion o) => o -> Int32 -> m ()
setEntryCompletionMinimumKeyLength :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> Int32 -> m ()
setEntryCompletionMinimumKeyLength o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"minimum-key-length" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@minimum-key-length@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEntryCompletionMinimumKeyLength :: (IsEntryCompletion o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructEntryCompletionMinimumKeyLength :: forall o (m :: * -> *).
(IsEntryCompletion o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructEntryCompletionMinimumKeyLength Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"minimum-key-length" Int32
val

#if defined(ENABLE_OVERLOADING)
data EntryCompletionMinimumKeyLengthPropertyInfo
instance AttrInfo EntryCompletionMinimumKeyLengthPropertyInfo where
    type AttrAllowedOps EntryCompletionMinimumKeyLengthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryCompletionMinimumKeyLengthPropertyInfo = IsEntryCompletion
    type AttrSetTypeConstraint EntryCompletionMinimumKeyLengthPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint EntryCompletionMinimumKeyLengthPropertyInfo = (~) Int32
    type AttrTransferType EntryCompletionMinimumKeyLengthPropertyInfo = Int32
    type AttrGetType EntryCompletionMinimumKeyLengthPropertyInfo = Int32
    type AttrLabel EntryCompletionMinimumKeyLengthPropertyInfo = "minimum-key-length"
    type AttrOrigin EntryCompletionMinimumKeyLengthPropertyInfo = EntryCompletion
    attrGet = getEntryCompletionMinimumKeyLength
    attrSet = setEntryCompletionMinimumKeyLength
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryCompletionMinimumKeyLength
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.minimumKeyLength"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:minimumKeyLength"
        })
#endif

-- VVV Prop "model"
   -- Type: TInterface (Name {namespace = "Gtk", name = "TreeModel"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@model@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' entryCompletion #model
-- @
getEntryCompletionModel :: (MonadIO m, IsEntryCompletion o) => o -> m (Maybe Gtk.TreeModel.TreeModel)
getEntryCompletionModel :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m (Maybe TreeModel)
getEntryCompletionModel o
obj = IO (Maybe TreeModel) -> m (Maybe TreeModel)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe TreeModel) -> m (Maybe TreeModel))
-> IO (Maybe TreeModel) -> m (Maybe TreeModel)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TreeModel -> TreeModel)
-> IO (Maybe TreeModel)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"model" ManagedPtr TreeModel -> TreeModel
Gtk.TreeModel.TreeModel

-- | Set the value of the “@model@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' entryCompletion [ #model 'Data.GI.Base.Attributes.:=' value ]
-- @
setEntryCompletionModel :: (MonadIO m, IsEntryCompletion o, Gtk.TreeModel.IsTreeModel a) => o -> a -> m ()
setEntryCompletionModel :: forall (m :: * -> *) o a.
(MonadIO m, IsEntryCompletion o, IsTreeModel a) =>
o -> a -> m ()
setEntryCompletionModel o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"model" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@model@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEntryCompletionModel :: (IsEntryCompletion o, MIO.MonadIO m, Gtk.TreeModel.IsTreeModel a) => a -> m (GValueConstruct o)
constructEntryCompletionModel :: forall o (m :: * -> *) a.
(IsEntryCompletion o, MonadIO m, IsTreeModel a) =>
a -> m (GValueConstruct o)
constructEntryCompletionModel a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"model" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@model@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #model
-- @
clearEntryCompletionModel :: (MonadIO m, IsEntryCompletion o) => o -> m ()
clearEntryCompletionModel :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m ()
clearEntryCompletionModel o
obj = 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
$ o -> String -> Maybe TreeModel -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"model" (Maybe TreeModel
forall a. Maybe a
Nothing :: Maybe Gtk.TreeModel.TreeModel)

#if defined(ENABLE_OVERLOADING)
data EntryCompletionModelPropertyInfo
instance AttrInfo EntryCompletionModelPropertyInfo where
    type AttrAllowedOps EntryCompletionModelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryCompletionModelPropertyInfo = IsEntryCompletion
    type AttrSetTypeConstraint EntryCompletionModelPropertyInfo = Gtk.TreeModel.IsTreeModel
    type AttrTransferTypeConstraint EntryCompletionModelPropertyInfo = Gtk.TreeModel.IsTreeModel
    type AttrTransferType EntryCompletionModelPropertyInfo = Gtk.TreeModel.TreeModel
    type AttrGetType EntryCompletionModelPropertyInfo = (Maybe Gtk.TreeModel.TreeModel)
    type AttrLabel EntryCompletionModelPropertyInfo = "model"
    type AttrOrigin EntryCompletionModelPropertyInfo = EntryCompletion
    attrGet = getEntryCompletionModel
    attrSet = setEntryCompletionModel
    attrTransfer _ v = do
        unsafeCastTo Gtk.TreeModel.TreeModel v
    attrConstruct = constructEntryCompletionModel
    attrClear = clearEntryCompletionModel
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.model"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:model"
        })
#endif

-- VVV Prop "popup-completion"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@popup-completion@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' entryCompletion #popupCompletion
-- @
getEntryCompletionPopupCompletion :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
getEntryCompletionPopupCompletion :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m Bool
getEntryCompletionPopupCompletion o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"popup-completion"

-- | Set the value of the “@popup-completion@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' entryCompletion [ #popupCompletion 'Data.GI.Base.Attributes.:=' value ]
-- @
setEntryCompletionPopupCompletion :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
setEntryCompletionPopupCompletion :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> Bool -> m ()
setEntryCompletionPopupCompletion o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"popup-completion" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@popup-completion@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEntryCompletionPopupCompletion :: (IsEntryCompletion o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryCompletionPopupCompletion :: forall o (m :: * -> *).
(IsEntryCompletion o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryCompletionPopupCompletion Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"popup-completion" Bool
val

#if defined(ENABLE_OVERLOADING)
data EntryCompletionPopupCompletionPropertyInfo
instance AttrInfo EntryCompletionPopupCompletionPropertyInfo where
    type AttrAllowedOps EntryCompletionPopupCompletionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryCompletionPopupCompletionPropertyInfo = IsEntryCompletion
    type AttrSetTypeConstraint EntryCompletionPopupCompletionPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryCompletionPopupCompletionPropertyInfo = (~) Bool
    type AttrTransferType EntryCompletionPopupCompletionPropertyInfo = Bool
    type AttrGetType EntryCompletionPopupCompletionPropertyInfo = Bool
    type AttrLabel EntryCompletionPopupCompletionPropertyInfo = "popup-completion"
    type AttrOrigin EntryCompletionPopupCompletionPropertyInfo = EntryCompletion
    attrGet = getEntryCompletionPopupCompletion
    attrSet = setEntryCompletionPopupCompletion
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryCompletionPopupCompletion
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.popupCompletion"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:popupCompletion"
        })
#endif

-- VVV Prop "popup-set-width"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@popup-set-width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' entryCompletion #popupSetWidth
-- @
getEntryCompletionPopupSetWidth :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
getEntryCompletionPopupSetWidth :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m Bool
getEntryCompletionPopupSetWidth o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"popup-set-width"

-- | Set the value of the “@popup-set-width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' entryCompletion [ #popupSetWidth 'Data.GI.Base.Attributes.:=' value ]
-- @
setEntryCompletionPopupSetWidth :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
setEntryCompletionPopupSetWidth :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> Bool -> m ()
setEntryCompletionPopupSetWidth o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"popup-set-width" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@popup-set-width@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEntryCompletionPopupSetWidth :: (IsEntryCompletion o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryCompletionPopupSetWidth :: forall o (m :: * -> *).
(IsEntryCompletion o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryCompletionPopupSetWidth Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"popup-set-width" Bool
val

#if defined(ENABLE_OVERLOADING)
data EntryCompletionPopupSetWidthPropertyInfo
instance AttrInfo EntryCompletionPopupSetWidthPropertyInfo where
    type AttrAllowedOps EntryCompletionPopupSetWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryCompletionPopupSetWidthPropertyInfo = IsEntryCompletion
    type AttrSetTypeConstraint EntryCompletionPopupSetWidthPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryCompletionPopupSetWidthPropertyInfo = (~) Bool
    type AttrTransferType EntryCompletionPopupSetWidthPropertyInfo = Bool
    type AttrGetType EntryCompletionPopupSetWidthPropertyInfo = Bool
    type AttrLabel EntryCompletionPopupSetWidthPropertyInfo = "popup-set-width"
    type AttrOrigin EntryCompletionPopupSetWidthPropertyInfo = EntryCompletion
    attrGet = getEntryCompletionPopupSetWidth
    attrSet = setEntryCompletionPopupSetWidth
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryCompletionPopupSetWidth
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.popupSetWidth"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:popupSetWidth"
        })
#endif

-- VVV Prop "popup-single-match"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@popup-single-match@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' entryCompletion #popupSingleMatch
-- @
getEntryCompletionPopupSingleMatch :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
getEntryCompletionPopupSingleMatch :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m Bool
getEntryCompletionPopupSingleMatch o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"popup-single-match"

-- | Set the value of the “@popup-single-match@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' entryCompletion [ #popupSingleMatch 'Data.GI.Base.Attributes.:=' value ]
-- @
setEntryCompletionPopupSingleMatch :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
setEntryCompletionPopupSingleMatch :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> Bool -> m ()
setEntryCompletionPopupSingleMatch o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"popup-single-match" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@popup-single-match@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEntryCompletionPopupSingleMatch :: (IsEntryCompletion o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryCompletionPopupSingleMatch :: forall o (m :: * -> *).
(IsEntryCompletion o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryCompletionPopupSingleMatch Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"popup-single-match" Bool
val

#if defined(ENABLE_OVERLOADING)
data EntryCompletionPopupSingleMatchPropertyInfo
instance AttrInfo EntryCompletionPopupSingleMatchPropertyInfo where
    type AttrAllowedOps EntryCompletionPopupSingleMatchPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryCompletionPopupSingleMatchPropertyInfo = IsEntryCompletion
    type AttrSetTypeConstraint EntryCompletionPopupSingleMatchPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryCompletionPopupSingleMatchPropertyInfo = (~) Bool
    type AttrTransferType EntryCompletionPopupSingleMatchPropertyInfo = Bool
    type AttrGetType EntryCompletionPopupSingleMatchPropertyInfo = Bool
    type AttrLabel EntryCompletionPopupSingleMatchPropertyInfo = "popup-single-match"
    type AttrOrigin EntryCompletionPopupSingleMatchPropertyInfo = EntryCompletion
    attrGet = getEntryCompletionPopupSingleMatch
    attrSet = setEntryCompletionPopupSingleMatch
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryCompletionPopupSingleMatch
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.popupSingleMatch"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:popupSingleMatch"
        })
#endif

-- VVV Prop "text-column"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@text-column@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' entryCompletion #textColumn
-- @
getEntryCompletionTextColumn :: (MonadIO m, IsEntryCompletion o) => o -> m Int32
getEntryCompletionTextColumn :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> m Int32
getEntryCompletionTextColumn o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"text-column"

-- | Set the value of the “@text-column@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' entryCompletion [ #textColumn 'Data.GI.Base.Attributes.:=' value ]
-- @
setEntryCompletionTextColumn :: (MonadIO m, IsEntryCompletion o) => o -> Int32 -> m ()
setEntryCompletionTextColumn :: forall (m :: * -> *) o.
(MonadIO m, IsEntryCompletion o) =>
o -> Int32 -> m ()
setEntryCompletionTextColumn o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"text-column" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@text-column@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEntryCompletionTextColumn :: (IsEntryCompletion o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructEntryCompletionTextColumn :: forall o (m :: * -> *).
(IsEntryCompletion o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructEntryCompletionTextColumn Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"text-column" Int32
val

#if defined(ENABLE_OVERLOADING)
data EntryCompletionTextColumnPropertyInfo
instance AttrInfo EntryCompletionTextColumnPropertyInfo where
    type AttrAllowedOps EntryCompletionTextColumnPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryCompletionTextColumnPropertyInfo = IsEntryCompletion
    type AttrSetTypeConstraint EntryCompletionTextColumnPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint EntryCompletionTextColumnPropertyInfo = (~) Int32
    type AttrTransferType EntryCompletionTextColumnPropertyInfo = Int32
    type AttrGetType EntryCompletionTextColumnPropertyInfo = Int32
    type AttrLabel EntryCompletionTextColumnPropertyInfo = "text-column"
    type AttrOrigin EntryCompletionTextColumnPropertyInfo = EntryCompletion
    attrGet = getEntryCompletionTextColumn
    attrSet = setEntryCompletionTextColumn
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryCompletionTextColumn
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.textColumn"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:textColumn"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EntryCompletion
type instance O.AttributeList EntryCompletion = EntryCompletionAttributeList
type EntryCompletionAttributeList = ('[ '("cellArea", EntryCompletionCellAreaPropertyInfo), '("inlineCompletion", EntryCompletionInlineCompletionPropertyInfo), '("inlineSelection", EntryCompletionInlineSelectionPropertyInfo), '("minimumKeyLength", EntryCompletionMinimumKeyLengthPropertyInfo), '("model", EntryCompletionModelPropertyInfo), '("popupCompletion", EntryCompletionPopupCompletionPropertyInfo), '("popupSetWidth", EntryCompletionPopupSetWidthPropertyInfo), '("popupSingleMatch", EntryCompletionPopupSingleMatchPropertyInfo), '("textColumn", EntryCompletionTextColumnPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
entryCompletionCellArea :: AttrLabelProxy "cellArea"
entryCompletionCellArea = AttrLabelProxy

entryCompletionInlineCompletion :: AttrLabelProxy "inlineCompletion"
entryCompletionInlineCompletion = AttrLabelProxy

entryCompletionInlineSelection :: AttrLabelProxy "inlineSelection"
entryCompletionInlineSelection = AttrLabelProxy

entryCompletionMinimumKeyLength :: AttrLabelProxy "minimumKeyLength"
entryCompletionMinimumKeyLength = AttrLabelProxy

entryCompletionModel :: AttrLabelProxy "model"
entryCompletionModel = AttrLabelProxy

entryCompletionPopupCompletion :: AttrLabelProxy "popupCompletion"
entryCompletionPopupCompletion = AttrLabelProxy

entryCompletionPopupSetWidth :: AttrLabelProxy "popupSetWidth"
entryCompletionPopupSetWidth = AttrLabelProxy

entryCompletionPopupSingleMatch :: AttrLabelProxy "popupSingleMatch"
entryCompletionPopupSingleMatch = AttrLabelProxy

entryCompletionTextColumn :: AttrLabelProxy "textColumn"
entryCompletionTextColumn = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList EntryCompletion = EntryCompletionSignalList
type EntryCompletionSignalList = ('[ '("cursorOnMatch", EntryCompletionCursorOnMatchSignalInfo), '("insertPrefix", EntryCompletionInsertPrefixSignalInfo), '("matchSelected", EntryCompletionMatchSelectedSignalInfo), '("noMatches", EntryCompletionNoMatchesSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method EntryCompletion::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "EntryCompletion" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_new" gtk_entry_completion_new :: 
    IO (Ptr EntryCompletion)

{-# DEPRECATED entryCompletionNew ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Creates a new @GtkEntryCompletion@ object.
entryCompletionNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m EntryCompletion
    -- ^ __Returns:__ A newly created @GtkEntryCompletion@ object
entryCompletionNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m EntryCompletion
entryCompletionNew  = IO EntryCompletion -> m EntryCompletion
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EntryCompletion -> m EntryCompletion)
-> IO EntryCompletion -> m EntryCompletion
forall a b. (a -> b) -> a -> b
$ do
    Ptr EntryCompletion
result <- IO (Ptr EntryCompletion)
gtk_entry_completion_new
    Text -> Ptr EntryCompletion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"entryCompletionNew" Ptr EntryCompletion
result
    EntryCompletion
result' <- ((ManagedPtr EntryCompletion -> EntryCompletion)
-> Ptr EntryCompletion -> IO EntryCompletion
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr EntryCompletion -> EntryCompletion
EntryCompletion) Ptr EntryCompletion
result
    EntryCompletion -> IO EntryCompletion
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EntryCompletion
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method EntryCompletion::new_with_area
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "area"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CellArea" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkCellArea` used to layout cells"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "EntryCompletion" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_new_with_area" gtk_entry_completion_new_with_area :: 
    Ptr Gtk.CellArea.CellArea ->            -- area : TInterface (Name {namespace = "Gtk", name = "CellArea"})
    IO (Ptr EntryCompletion)

{-# DEPRECATED entryCompletionNewWithArea ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Creates a new @GtkEntryCompletion@ object using the
-- specified /@area@/.
-- 
-- The @GtkCellArea@ is used to layout cells in the underlying
-- @GtkTreeViewColumn@ for the drop-down menu.
entryCompletionNewWithArea ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.CellArea.IsCellArea a) =>
    a
    -- ^ /@area@/: the @GtkCellArea@ used to layout cells
    -> m EntryCompletion
    -- ^ __Returns:__ A newly created @GtkEntryCompletion@ object
entryCompletionNewWithArea :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCellArea a) =>
a -> m EntryCompletion
entryCompletionNewWithArea a
area = IO EntryCompletion -> m EntryCompletion
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EntryCompletion -> m EntryCompletion)
-> IO EntryCompletion -> m EntryCompletion
forall a b. (a -> b) -> a -> b
$ do
    Ptr CellArea
area' <- a -> IO (Ptr CellArea)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
area
    Ptr EntryCompletion
result <- Ptr CellArea -> IO (Ptr EntryCompletion)
gtk_entry_completion_new_with_area Ptr CellArea
area'
    Text -> Ptr EntryCompletion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"entryCompletionNewWithArea" Ptr EntryCompletion
result
    EntryCompletion
result' <- ((ManagedPtr EntryCompletion -> EntryCompletion)
-> Ptr EntryCompletion -> IO EntryCompletion
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr EntryCompletion -> EntryCompletion
EntryCompletion) Ptr EntryCompletion
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
area
    EntryCompletion -> IO EntryCompletion
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EntryCompletion
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method EntryCompletion::complete
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_complete" gtk_entry_completion_complete :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO ()

{-# DEPRECATED entryCompletionComplete ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Requests a completion operation, or in other words a refiltering of the
-- current list with completions, using the current key.
-- 
-- The completion list view will be updated accordingly.
entryCompletionComplete ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m ()
entryCompletionComplete :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m ()
entryCompletionComplete a
completion = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    Ptr EntryCompletion -> IO ()
gtk_entry_completion_complete Ptr EntryCompletion
completion'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionCompleteMethodInfo
instance (signature ~ (m ()), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionCompleteMethodInfo a signature where
    overloadedMethod = entryCompletionComplete

instance O.OverloadedMethodInfo EntryCompletionCompleteMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionComplete",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionComplete"
        })


#endif

-- method EntryCompletion::compute_prefix
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the entry completion"
--                 , 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 text to complete for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_compute_prefix" gtk_entry_completion_compute_prefix :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    CString ->                              -- key : TBasicType TUTF8
    IO CString

{-# DEPRECATED entryCompletionComputePrefix ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Computes the common prefix that is shared by all rows in /@completion@/
-- that start with /@key@/.
-- 
-- If no row matches /@key@/, 'P.Nothing' will be returned.
-- Note that a text column must have been set for this function to work,
-- see 'GI.Gtk.Objects.EntryCompletion.entryCompletionSetTextColumn' for details.
entryCompletionComputePrefix ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: the entry completion
    -> T.Text
    -- ^ /@key@/: The text to complete for
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The common prefix all rows
    --   starting with /@key@/
entryCompletionComputePrefix :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> Text -> m (Maybe Text)
entryCompletionComputePrefix a
completion Text
key = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
result <- Ptr EntryCompletion -> CString -> IO CString
gtk_entry_completion_compute_prefix Ptr EntryCompletion
completion' CString
key'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data EntryCompletionComputePrefixMethodInfo
instance (signature ~ (T.Text -> m (Maybe T.Text)), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionComputePrefixMethodInfo a signature where
    overloadedMethod = entryCompletionComputePrefix

instance O.OverloadedMethodInfo EntryCompletionComputePrefixMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionComputePrefix",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionComputePrefix"
        })


#endif

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

foreign import ccall "gtk_entry_completion_get_completion_prefix" gtk_entry_completion_get_completion_prefix :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO CString

{-# DEPRECATED entryCompletionGetCompletionPrefix ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Get the original text entered by the user that triggered
-- the completion or 'P.Nothing' if there’s no completion ongoing.
entryCompletionGetCompletionPrefix ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the prefix for the current completion
entryCompletionGetCompletionPrefix :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m (Maybe Text)
entryCompletionGetCompletionPrefix a
completion = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    CString
result <- Ptr EntryCompletion -> IO CString
gtk_entry_completion_get_completion_prefix Ptr EntryCompletion
completion'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data EntryCompletionGetCompletionPrefixMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionGetCompletionPrefixMethodInfo a signature where
    overloadedMethod = entryCompletionGetCompletionPrefix

instance O.OverloadedMethodInfo EntryCompletionGetCompletionPrefixMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionGetCompletionPrefix",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetCompletionPrefix"
        })


#endif

-- method EntryCompletion::get_entry
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Widget" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_get_entry" gtk_entry_completion_get_entry :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO (Ptr Gtk.Widget.Widget)

{-# DEPRECATED entryCompletionGetEntry ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Gets the entry /@completion@/ has been attached to.
entryCompletionGetEntry ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m Gtk.Widget.Widget
    -- ^ __Returns:__ The entry /@completion@/ has been attached to
entryCompletionGetEntry :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m Widget
entryCompletionGetEntry a
completion = IO Widget -> m Widget
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
    Ptr EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    Ptr Widget
result <- Ptr EntryCompletion -> IO (Ptr Widget)
gtk_entry_completion_get_entry Ptr EntryCompletion
completion'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"entryCompletionGetEntry" Ptr Widget
result
    Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Widget -> IO Widget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'

#if defined(ENABLE_OVERLOADING)
data EntryCompletionGetEntryMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionGetEntryMethodInfo a signature where
    overloadedMethod = entryCompletionGetEntry

instance O.OverloadedMethodInfo EntryCompletionGetEntryMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionGetEntry",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetEntry"
        })


#endif

-- method EntryCompletion::get_inline_completion
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , 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 "gtk_entry_completion_get_inline_completion" gtk_entry_completion_get_inline_completion :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO CInt

{-# DEPRECATED entryCompletionGetInlineCompletion ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Returns whether the common prefix of the possible completions should
-- be automatically inserted in the entry.
entryCompletionGetInlineCompletion ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if inline completion is turned on
entryCompletionGetInlineCompletion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m Bool
entryCompletionGetInlineCompletion a
completion = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    CInt
result <- Ptr EntryCompletion -> IO CInt
gtk_entry_completion_get_inline_completion Ptr EntryCompletion
completion'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data EntryCompletionGetInlineCompletionMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionGetInlineCompletionMethodInfo a signature where
    overloadedMethod = entryCompletionGetInlineCompletion

instance O.OverloadedMethodInfo EntryCompletionGetInlineCompletionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionGetInlineCompletion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetInlineCompletion"
        })


#endif

-- method EntryCompletion::get_inline_selection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , 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 "gtk_entry_completion_get_inline_selection" gtk_entry_completion_get_inline_selection :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO CInt

{-# DEPRECATED entryCompletionGetInlineSelection ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Returns 'P.True' if inline-selection mode is turned on.
entryCompletionGetInlineSelection ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if inline-selection mode is on
entryCompletionGetInlineSelection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m Bool
entryCompletionGetInlineSelection a
completion = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    CInt
result <- Ptr EntryCompletion -> IO CInt
gtk_entry_completion_get_inline_selection Ptr EntryCompletion
completion'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data EntryCompletionGetInlineSelectionMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionGetInlineSelectionMethodInfo a signature where
    overloadedMethod = entryCompletionGetInlineSelection

instance O.OverloadedMethodInfo EntryCompletionGetInlineSelectionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionGetInlineSelection",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetInlineSelection"
        })


#endif

-- method EntryCompletion::get_minimum_key_length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_get_minimum_key_length" gtk_entry_completion_get_minimum_key_length :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO Int32

{-# DEPRECATED entryCompletionGetMinimumKeyLength ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Returns the minimum key length as set for /@completion@/.
entryCompletionGetMinimumKeyLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m Int32
    -- ^ __Returns:__ The currently used minimum key length
entryCompletionGetMinimumKeyLength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m Int32
entryCompletionGetMinimumKeyLength a
completion = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    Int32
result <- Ptr EntryCompletion -> IO Int32
gtk_entry_completion_get_minimum_key_length Ptr EntryCompletion
completion'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data EntryCompletionGetMinimumKeyLengthMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionGetMinimumKeyLengthMethodInfo a signature where
    overloadedMethod = entryCompletionGetMinimumKeyLength

instance O.OverloadedMethodInfo EntryCompletionGetMinimumKeyLengthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionGetMinimumKeyLength",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetMinimumKeyLength"
        })


#endif

-- method EntryCompletion::get_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "TreeModel" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_get_model" gtk_entry_completion_get_model :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO (Ptr Gtk.TreeModel.TreeModel)

{-# DEPRECATED entryCompletionGetModel ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Returns the model the @GtkEntryCompletion@ is using as data source.
-- 
-- Returns 'P.Nothing' if the model is unset.
entryCompletionGetModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m (Maybe Gtk.TreeModel.TreeModel)
    -- ^ __Returns:__ A @GtkTreeModel@
entryCompletionGetModel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m (Maybe TreeModel)
entryCompletionGetModel a
completion = IO (Maybe TreeModel) -> m (Maybe TreeModel)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeModel) -> m (Maybe TreeModel))
-> IO (Maybe TreeModel) -> m (Maybe TreeModel)
forall a b. (a -> b) -> a -> b
$ do
    Ptr EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    Ptr TreeModel
result <- Ptr EntryCompletion -> IO (Ptr TreeModel)
gtk_entry_completion_get_model Ptr EntryCompletion
completion'
    Maybe TreeModel
maybeResult <- Ptr TreeModel
-> (Ptr TreeModel -> IO TreeModel) -> IO (Maybe TreeModel)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeModel
result ((Ptr TreeModel -> IO TreeModel) -> IO (Maybe TreeModel))
-> (Ptr TreeModel -> IO TreeModel) -> IO (Maybe TreeModel)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeModel
result' -> do
        TreeModel
result'' <- ((ManagedPtr TreeModel -> TreeModel)
-> Ptr TreeModel -> IO TreeModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TreeModel -> TreeModel
Gtk.TreeModel.TreeModel) Ptr TreeModel
result'
        TreeModel -> IO TreeModel
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeModel
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Maybe TreeModel -> IO (Maybe TreeModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeModel
maybeResult

#if defined(ENABLE_OVERLOADING)
data EntryCompletionGetModelMethodInfo
instance (signature ~ (m (Maybe Gtk.TreeModel.TreeModel)), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionGetModelMethodInfo a signature where
    overloadedMethod = entryCompletionGetModel

instance O.OverloadedMethodInfo EntryCompletionGetModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionGetModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetModel"
        })


#endif

-- method EntryCompletion::get_popup_completion
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , 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 "gtk_entry_completion_get_popup_completion" gtk_entry_completion_get_popup_completion :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO CInt

{-# DEPRECATED entryCompletionGetPopupCompletion ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Returns whether the completions should be presented in a popup window.
entryCompletionGetPopupCompletion ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if popup completion is turned on
entryCompletionGetPopupCompletion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m Bool
entryCompletionGetPopupCompletion a
completion = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    CInt
result <- Ptr EntryCompletion -> IO CInt
gtk_entry_completion_get_popup_completion Ptr EntryCompletion
completion'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data EntryCompletionGetPopupCompletionMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionGetPopupCompletionMethodInfo a signature where
    overloadedMethod = entryCompletionGetPopupCompletion

instance O.OverloadedMethodInfo EntryCompletionGetPopupCompletionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionGetPopupCompletion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetPopupCompletion"
        })


#endif

-- method EntryCompletion::get_popup_set_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , 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 "gtk_entry_completion_get_popup_set_width" gtk_entry_completion_get_popup_set_width :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO CInt

{-# DEPRECATED entryCompletionGetPopupSetWidth ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Returns whether the completion popup window will be resized to the
-- width of the entry.
entryCompletionGetPopupSetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the popup window will be resized to the width of
    --   the entry
entryCompletionGetPopupSetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m Bool
entryCompletionGetPopupSetWidth a
completion = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    CInt
result <- Ptr EntryCompletion -> IO CInt
gtk_entry_completion_get_popup_set_width Ptr EntryCompletion
completion'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data EntryCompletionGetPopupSetWidthMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionGetPopupSetWidthMethodInfo a signature where
    overloadedMethod = entryCompletionGetPopupSetWidth

instance O.OverloadedMethodInfo EntryCompletionGetPopupSetWidthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionGetPopupSetWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetPopupSetWidth"
        })


#endif

-- method EntryCompletion::get_popup_single_match
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , 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 "gtk_entry_completion_get_popup_single_match" gtk_entry_completion_get_popup_single_match :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO CInt

{-# DEPRECATED entryCompletionGetPopupSingleMatch ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Returns whether the completion popup window will appear even if there is
-- only a single match.
entryCompletionGetPopupSingleMatch ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the popup window will appear regardless of the
    --    number of matches
entryCompletionGetPopupSingleMatch :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m Bool
entryCompletionGetPopupSingleMatch a
completion = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    CInt
result <- Ptr EntryCompletion -> IO CInt
gtk_entry_completion_get_popup_single_match Ptr EntryCompletion
completion'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data EntryCompletionGetPopupSingleMatchMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionGetPopupSingleMatchMethodInfo a signature where
    overloadedMethod = entryCompletionGetPopupSingleMatch

instance O.OverloadedMethodInfo EntryCompletionGetPopupSingleMatchMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionGetPopupSingleMatch",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetPopupSingleMatch"
        })


#endif

-- method EntryCompletion::get_text_column
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_get_text_column" gtk_entry_completion_get_text_column :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO Int32

{-# DEPRECATED entryCompletionGetTextColumn ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Returns the column in the model of /@completion@/ to get strings from.
entryCompletionGetTextColumn ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m Int32
    -- ^ __Returns:__ the column containing the strings
entryCompletionGetTextColumn :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m Int32
entryCompletionGetTextColumn a
completion = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    Int32
result <- Ptr EntryCompletion -> IO Int32
gtk_entry_completion_get_text_column Ptr EntryCompletion
completion'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data EntryCompletionGetTextColumnMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionGetTextColumnMethodInfo a signature where
    overloadedMethod = entryCompletionGetTextColumn

instance O.OverloadedMethodInfo EntryCompletionGetTextColumnMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionGetTextColumn",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetTextColumn"
        })


#endif

-- method EntryCompletion::insert_prefix
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_insert_prefix" gtk_entry_completion_insert_prefix :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    IO ()

{-# DEPRECATED entryCompletionInsertPrefix ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Requests a prefix insertion.
entryCompletionInsertPrefix ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> m ()
entryCompletionInsertPrefix :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> m ()
entryCompletionInsertPrefix a
completion = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    Ptr EntryCompletion -> IO ()
gtk_entry_completion_insert_prefix Ptr EntryCompletion
completion'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionInsertPrefixMethodInfo
instance (signature ~ (m ()), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionInsertPrefixMethodInfo a signature where
    overloadedMethod = entryCompletionInsertPrefix

instance O.OverloadedMethodInfo EntryCompletionInsertPrefixMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionInsertPrefix",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionInsertPrefix"
        })


#endif

-- method EntryCompletion::set_inline_completion
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "inline_completion"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to do inline completion"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_set_inline_completion" gtk_entry_completion_set_inline_completion :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    CInt ->                                 -- inline_completion : TBasicType TBoolean
    IO ()

{-# DEPRECATED entryCompletionSetInlineCompletion ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Sets whether the common prefix of the possible completions should
-- be automatically inserted in the entry.
entryCompletionSetInlineCompletion ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> Bool
    -- ^ /@inlineCompletion@/: 'P.True' to do inline completion
    -> m ()
entryCompletionSetInlineCompletion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> Bool -> m ()
entryCompletionSetInlineCompletion a
completion Bool
inlineCompletion = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    let inlineCompletion' :: CInt
inlineCompletion' = (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
inlineCompletion
    Ptr EntryCompletion -> CInt -> IO ()
gtk_entry_completion_set_inline_completion Ptr EntryCompletion
completion' CInt
inlineCompletion'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionSetInlineCompletionMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionSetInlineCompletionMethodInfo a signature where
    overloadedMethod = entryCompletionSetInlineCompletion

instance O.OverloadedMethodInfo EntryCompletionSetInlineCompletionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionSetInlineCompletion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetInlineCompletion"
        })


#endif

-- method EntryCompletion::set_inline_selection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "inline_selection"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to do inline selection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_set_inline_selection" gtk_entry_completion_set_inline_selection :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    CInt ->                                 -- inline_selection : TBasicType TBoolean
    IO ()

{-# DEPRECATED entryCompletionSetInlineSelection ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Sets whether it is possible to cycle through the possible completions
-- inside the entry.
entryCompletionSetInlineSelection ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> Bool
    -- ^ /@inlineSelection@/: 'P.True' to do inline selection
    -> m ()
entryCompletionSetInlineSelection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> Bool -> m ()
entryCompletionSetInlineSelection a
completion Bool
inlineSelection = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    let inlineSelection' :: CInt
inlineSelection' = (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
inlineSelection
    Ptr EntryCompletion -> CInt -> IO ()
gtk_entry_completion_set_inline_selection Ptr EntryCompletion
completion' CInt
inlineSelection'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionSetInlineSelectionMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionSetInlineSelectionMethodInfo a signature where
    overloadedMethod = entryCompletionSetInlineSelection

instance O.OverloadedMethodInfo EntryCompletionSetInlineSelectionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionSetInlineSelection",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetInlineSelection"
        })


#endif

-- method EntryCompletion::set_match_func
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "func"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "EntryCompletionMatchFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkEntryCompletion`MatchFunc to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 2
--           , argDestroy = 3
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "func_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data for @func"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "func_notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destroy notify for @func_data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_set_match_func" gtk_entry_completion_set_match_func :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    FunPtr Gtk.Callbacks.C_EntryCompletionMatchFunc -> -- func : TInterface (Name {namespace = "Gtk", name = "EntryCompletionMatchFunc"})
    Ptr () ->                               -- func_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- func_notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

{-# DEPRECATED entryCompletionSetMatchFunc ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Sets the match function for /@completion@/ to be /@func@/.
-- 
-- The match function is used to determine if a row should or
-- should not be in the completion list.
entryCompletionSetMatchFunc ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> Gtk.Callbacks.EntryCompletionMatchFunc
    -- ^ /@func@/: the @GtkEntryCompletion@MatchFunc to use
    -> m ()
entryCompletionSetMatchFunc :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> EntryCompletionMatchFunc -> m ()
entryCompletionSetMatchFunc a
completion EntryCompletionMatchFunc
func = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    FunPtr C_EntryCompletionMatchFunc
func' <- C_EntryCompletionMatchFunc
-> IO (FunPtr C_EntryCompletionMatchFunc)
Gtk.Callbacks.mk_EntryCompletionMatchFunc (Maybe (Ptr (FunPtr C_EntryCompletionMatchFunc))
-> EntryCompletionMatchFunc_WithClosures
-> C_EntryCompletionMatchFunc
Gtk.Callbacks.wrap_EntryCompletionMatchFunc Maybe (Ptr (FunPtr C_EntryCompletionMatchFunc))
forall a. Maybe a
Nothing (EntryCompletionMatchFunc -> EntryCompletionMatchFunc_WithClosures
Gtk.Callbacks.drop_closures_EntryCompletionMatchFunc EntryCompletionMatchFunc
func))
    let funcData :: Ptr ()
funcData = FunPtr C_EntryCompletionMatchFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_EntryCompletionMatchFunc
func'
    let funcNotify :: FunPtr (Ptr a -> IO ())
funcNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr EntryCompletion
-> FunPtr C_EntryCompletionMatchFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
gtk_entry_completion_set_match_func Ptr EntryCompletion
completion' FunPtr C_EntryCompletionMatchFunc
func' Ptr ()
funcData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
funcNotify
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionSetMatchFuncMethodInfo
instance (signature ~ (Gtk.Callbacks.EntryCompletionMatchFunc -> m ()), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionSetMatchFuncMethodInfo a signature where
    overloadedMethod = entryCompletionSetMatchFunc

instance O.OverloadedMethodInfo EntryCompletionSetMatchFuncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionSetMatchFunc",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetMatchFunc"
        })


#endif

-- method EntryCompletion::set_minimum_key_length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the minimum length of the key in order to start completing"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_set_minimum_key_length" gtk_entry_completion_set_minimum_key_length :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    Int32 ->                                -- length : TBasicType TInt
    IO ()

{-# DEPRECATED entryCompletionSetMinimumKeyLength ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Requires the length of the search key for /@completion@/ to be at least
-- /@length@/.
-- 
-- This is useful for long lists, where completing using a small
-- key takes a lot of time and will come up with meaningless results anyway
-- (ie, a too large dataset).
entryCompletionSetMinimumKeyLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> Int32
    -- ^ /@length@/: the minimum length of the key in order to start completing
    -> m ()
entryCompletionSetMinimumKeyLength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> Int32 -> m ()
entryCompletionSetMinimumKeyLength a
completion Int32
length_ = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    Ptr EntryCompletion -> Int32 -> IO ()
gtk_entry_completion_set_minimum_key_length Ptr EntryCompletion
completion' Int32
length_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionSetMinimumKeyLengthMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionSetMinimumKeyLengthMethodInfo a signature where
    overloadedMethod = entryCompletionSetMinimumKeyLength

instance O.OverloadedMethodInfo EntryCompletionSetMinimumKeyLengthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionSetMinimumKeyLength",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetMinimumKeyLength"
        })


#endif

-- method EntryCompletion::set_model
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeModel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkTreeModel`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_set_model" gtk_entry_completion_set_model :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    Ptr Gtk.TreeModel.TreeModel ->          -- model : TInterface (Name {namespace = "Gtk", name = "TreeModel"})
    IO ()

{-# DEPRECATED entryCompletionSetModel ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Sets the model for a @GtkEntryCompletion@.
-- 
-- If /@completion@/ already has a model set, it will remove it
-- before setting the new model. If model is 'P.Nothing', then it
-- will unset the model.
entryCompletionSetModel ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a, Gtk.TreeModel.IsTreeModel b) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> Maybe (b)
    -- ^ /@model@/: the @GtkTreeModel@
    -> m ()
entryCompletionSetModel :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsEntryCompletion a, IsTreeModel b) =>
a -> Maybe b -> m ()
entryCompletionSetModel a
completion Maybe b
model = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    Ptr TreeModel
maybeModel <- case Maybe b
model of
        Maybe b
Nothing -> Ptr TreeModel -> IO (Ptr TreeModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeModel
forall a. Ptr a
nullPtr
        Just b
jModel -> do
            Ptr TreeModel
jModel' <- b -> IO (Ptr TreeModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
            Ptr TreeModel -> IO (Ptr TreeModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeModel
jModel'
    Ptr EntryCompletion -> Ptr TreeModel -> IO ()
gtk_entry_completion_set_model Ptr EntryCompletion
completion' Ptr TreeModel
maybeModel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
model b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionSetModelMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsEntryCompletion a, Gtk.TreeModel.IsTreeModel b) => O.OverloadedMethod EntryCompletionSetModelMethodInfo a signature where
    overloadedMethod = entryCompletionSetModel

instance O.OverloadedMethodInfo EntryCompletionSetModelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionSetModel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetModel"
        })


#endif

-- method EntryCompletion::set_popup_completion
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "popup_completion"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to do popup completion"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_set_popup_completion" gtk_entry_completion_set_popup_completion :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    CInt ->                                 -- popup_completion : TBasicType TBoolean
    IO ()

{-# DEPRECATED entryCompletionSetPopupCompletion ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Sets whether the completions should be presented in a popup window.
entryCompletionSetPopupCompletion ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> Bool
    -- ^ /@popupCompletion@/: 'P.True' to do popup completion
    -> m ()
entryCompletionSetPopupCompletion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> Bool -> m ()
entryCompletionSetPopupCompletion a
completion Bool
popupCompletion = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    let popupCompletion' :: CInt
popupCompletion' = (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
popupCompletion
    Ptr EntryCompletion -> CInt -> IO ()
gtk_entry_completion_set_popup_completion Ptr EntryCompletion
completion' CInt
popupCompletion'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionSetPopupCompletionMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionSetPopupCompletionMethodInfo a signature where
    overloadedMethod = entryCompletionSetPopupCompletion

instance O.OverloadedMethodInfo EntryCompletionSetPopupCompletionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionSetPopupCompletion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetPopupCompletion"
        })


#endif

-- method EntryCompletion::set_popup_set_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "popup_set_width"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%TRUE to make the width of the popup the same as the entry"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_set_popup_set_width" gtk_entry_completion_set_popup_set_width :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    CInt ->                                 -- popup_set_width : TBasicType TBoolean
    IO ()

{-# DEPRECATED entryCompletionSetPopupSetWidth ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Sets whether the completion popup window will be resized to be the same
-- width as the entry.
entryCompletionSetPopupSetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> Bool
    -- ^ /@popupSetWidth@/: 'P.True' to make the width of the popup the same as the entry
    -> m ()
entryCompletionSetPopupSetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> Bool -> m ()
entryCompletionSetPopupSetWidth a
completion Bool
popupSetWidth = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    let popupSetWidth' :: CInt
popupSetWidth' = (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
popupSetWidth
    Ptr EntryCompletion -> CInt -> IO ()
gtk_entry_completion_set_popup_set_width Ptr EntryCompletion
completion' CInt
popupSetWidth'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionSetPopupSetWidthMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionSetPopupSetWidthMethodInfo a signature where
    overloadedMethod = entryCompletionSetPopupSetWidth

instance O.OverloadedMethodInfo EntryCompletionSetPopupSetWidthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionSetPopupSetWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetPopupSetWidth"
        })


#endif

-- method EntryCompletion::set_popup_single_match
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "popup_single_match"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%TRUE if the popup should appear even for a single match"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_set_popup_single_match" gtk_entry_completion_set_popup_single_match :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    CInt ->                                 -- popup_single_match : TBasicType TBoolean
    IO ()

{-# DEPRECATED entryCompletionSetPopupSingleMatch ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Sets whether the completion popup window will appear even if there is
-- only a single match.
-- 
-- You may want to set this to 'P.False' if you
-- are using [EntryCompletion:inlineCompletion]("GI.Gtk.Objects.EntryCompletion#g:attr:inlineCompletion").
entryCompletionSetPopupSingleMatch ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> Bool
    -- ^ /@popupSingleMatch@/: 'P.True' if the popup should appear even for a single match
    -> m ()
entryCompletionSetPopupSingleMatch :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> Bool -> m ()
entryCompletionSetPopupSingleMatch a
completion Bool
popupSingleMatch = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    let popupSingleMatch' :: CInt
popupSingleMatch' = (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
popupSingleMatch
    Ptr EntryCompletion -> CInt -> IO ()
gtk_entry_completion_set_popup_single_match Ptr EntryCompletion
completion' CInt
popupSingleMatch'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionSetPopupSingleMatchMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionSetPopupSingleMatchMethodInfo a signature where
    overloadedMethod = entryCompletionSetPopupSingleMatch

instance O.OverloadedMethodInfo EntryCompletionSetPopupSingleMatchMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionSetPopupSingleMatch",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetPopupSingleMatch"
        })


#endif

-- method EntryCompletion::set_text_column
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "completion"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "EntryCompletion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkEntryCompletion`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "column"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the column in the model of @completion to get strings from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_entry_completion_set_text_column" gtk_entry_completion_set_text_column :: 
    Ptr EntryCompletion ->                  -- completion : TInterface (Name {namespace = "Gtk", name = "EntryCompletion"})
    Int32 ->                                -- column : TBasicType TInt
    IO ()

{-# DEPRECATED entryCompletionSetTextColumn ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
-- | Convenience function for setting up the most used case of this code: a
-- completion list with just strings.
-- 
-- This function will set up /@completion@/
-- to have a list displaying all (and just) strings in the completion list,
-- and to get those strings from /@column@/ in the model of /@completion@/.
-- 
-- This functions creates and adds a @GtkCellRendererText@ for the selected
-- column. If you need to set the text column, but don\'t want the cell
-- renderer, use @/g_object_set()/@ to set the
-- [EntryCompletion:textColumn]("GI.Gtk.Objects.EntryCompletion#g:attr:textColumn") property directly.
entryCompletionSetTextColumn ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
    a
    -- ^ /@completion@/: a @GtkEntryCompletion@
    -> Int32
    -- ^ /@column@/: the column in the model of /@completion@/ to get strings from
    -> m ()
entryCompletionSetTextColumn :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryCompletion a) =>
a -> Int32 -> m ()
entryCompletionSetTextColumn a
completion Int32
column = 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 EntryCompletion
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
    Ptr EntryCompletion -> Int32 -> IO ()
gtk_entry_completion_set_text_column Ptr EntryCompletion
completion' Int32
column
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
completion
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EntryCompletionSetTextColumnMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsEntryCompletion a) => O.OverloadedMethod EntryCompletionSetTextColumnMethodInfo a signature where
    overloadedMethod = entryCompletionSetTextColumn

instance O.OverloadedMethodInfo EntryCompletionSetTextColumnMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.EntryCompletion.entryCompletionSetTextColumn",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetTextColumn"
        })


#endif