{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.EntryCompletion
(
EntryCompletion(..) ,
IsEntryCompletion ,
toEntryCompletion ,
#if defined(ENABLE_OVERLOADING)
ResolveEntryCompletionMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
EntryCompletionCompleteMethodInfo ,
#endif
entryCompletionComplete ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionComputePrefixMethodInfo ,
#endif
entryCompletionComputePrefix ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionGetCompletionPrefixMethodInfo,
#endif
entryCompletionGetCompletionPrefix ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionGetEntryMethodInfo ,
#endif
entryCompletionGetEntry ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionGetInlineCompletionMethodInfo,
#endif
entryCompletionGetInlineCompletion ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionGetInlineSelectionMethodInfo,
#endif
entryCompletionGetInlineSelection ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionGetMinimumKeyLengthMethodInfo,
#endif
entryCompletionGetMinimumKeyLength ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionGetModelMethodInfo ,
#endif
entryCompletionGetModel ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionGetPopupCompletionMethodInfo,
#endif
entryCompletionGetPopupCompletion ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionGetPopupSetWidthMethodInfo,
#endif
entryCompletionGetPopupSetWidth ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionGetPopupSingleMatchMethodInfo,
#endif
entryCompletionGetPopupSingleMatch ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionGetTextColumnMethodInfo ,
#endif
entryCompletionGetTextColumn ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionInsertPrefixMethodInfo ,
#endif
entryCompletionInsertPrefix ,
entryCompletionNew ,
entryCompletionNewWithArea ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionSetInlineCompletionMethodInfo,
#endif
entryCompletionSetInlineCompletion ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionSetInlineSelectionMethodInfo,
#endif
entryCompletionSetInlineSelection ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionSetMatchFuncMethodInfo ,
#endif
entryCompletionSetMatchFunc ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionSetMinimumKeyLengthMethodInfo,
#endif
entryCompletionSetMinimumKeyLength ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionSetModelMethodInfo ,
#endif
entryCompletionSetModel ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionSetPopupCompletionMethodInfo,
#endif
entryCompletionSetPopupCompletion ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionSetPopupSetWidthMethodInfo,
#endif
entryCompletionSetPopupSetWidth ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionSetPopupSingleMatchMethodInfo,
#endif
entryCompletionSetPopupSingleMatch ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionSetTextColumnMethodInfo ,
#endif
entryCompletionSetTextColumn ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionCellAreaPropertyInfo ,
#endif
constructEntryCompletionCellArea ,
#if defined(ENABLE_OVERLOADING)
entryCompletionCellArea ,
#endif
getEntryCompletionCellArea ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionInlineCompletionPropertyInfo,
#endif
constructEntryCompletionInlineCompletion,
#if defined(ENABLE_OVERLOADING)
entryCompletionInlineCompletion ,
#endif
getEntryCompletionInlineCompletion ,
setEntryCompletionInlineCompletion ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionInlineSelectionPropertyInfo,
#endif
constructEntryCompletionInlineSelection ,
#if defined(ENABLE_OVERLOADING)
entryCompletionInlineSelection ,
#endif
getEntryCompletionInlineSelection ,
setEntryCompletionInlineSelection ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionMinimumKeyLengthPropertyInfo,
#endif
constructEntryCompletionMinimumKeyLength,
#if defined(ENABLE_OVERLOADING)
entryCompletionMinimumKeyLength ,
#endif
getEntryCompletionMinimumKeyLength ,
setEntryCompletionMinimumKeyLength ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionModelPropertyInfo ,
#endif
clearEntryCompletionModel ,
constructEntryCompletionModel ,
#if defined(ENABLE_OVERLOADING)
entryCompletionModel ,
#endif
getEntryCompletionModel ,
setEntryCompletionModel ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionPopupCompletionPropertyInfo,
#endif
constructEntryCompletionPopupCompletion ,
#if defined(ENABLE_OVERLOADING)
entryCompletionPopupCompletion ,
#endif
getEntryCompletionPopupCompletion ,
setEntryCompletionPopupCompletion ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionPopupSetWidthPropertyInfo,
#endif
constructEntryCompletionPopupSetWidth ,
#if defined(ENABLE_OVERLOADING)
entryCompletionPopupSetWidth ,
#endif
getEntryCompletionPopupSetWidth ,
setEntryCompletionPopupSetWidth ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionPopupSingleMatchPropertyInfo,
#endif
constructEntryCompletionPopupSingleMatch,
#if defined(ENABLE_OVERLOADING)
entryCompletionPopupSingleMatch ,
#endif
getEntryCompletionPopupSingleMatch ,
setEntryCompletionPopupSingleMatch ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionTextColumnPropertyInfo ,
#endif
constructEntryCompletionTextColumn ,
#if defined(ENABLE_OVERLOADING)
entryCompletionTextColumn ,
#endif
getEntryCompletionTextColumn ,
setEntryCompletionTextColumn ,
EntryCompletionCursorOnMatchCallback ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionCursorOnMatchSignalInfo ,
#endif
afterEntryCompletionCursorOnMatch ,
onEntryCompletionCursorOnMatch ,
EntryCompletionInsertPrefixCallback ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionInsertPrefixSignalInfo ,
#endif
afterEntryCompletionInsertPrefix ,
onEntryCompletionInsertPrefix ,
EntryCompletionMatchSelectedCallback ,
#if defined(ENABLE_OVERLOADING)
EntryCompletionMatchSelectedSignalInfo ,
#endif
afterEntryCompletionMatchSelected ,
onEntryCompletionMatchSelected ,
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import qualified GI.Gdk.Objects.Clipboard as Gdk.Clipboard
import qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.Event as Gdk.Event
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import qualified GI.Gdk.Objects.Surface as Gdk.Surface
import qualified GI.Gdk.Objects.Texture as Gdk.Texture
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Graphene.Structs.Size as Graphene.Size
import qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3
import qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4
import qualified GI.Gsk.Enums as Gsk.Enums
import qualified GI.Gsk.Objects.GLShader as Gsk.GLShader
import qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import qualified GI.Gsk.Objects.Renderer as Gsk.Renderer
import qualified GI.Gsk.Structs.ColorStop as Gsk.ColorStop
import qualified GI.Gsk.Structs.Path as Gsk.Path
import qualified GI.Gsk.Structs.RoundedRect as Gsk.RoundedRect
import qualified GI.Gsk.Structs.Shadow as Gsk.Shadow
import qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
import qualified GI.Gsk.Structs.Transform as Gsk.Transform
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.CellEditable as Gtk.CellEditable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.CellLayout as Gtk.CellLayout
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Native as Gtk.Native
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Root as Gtk.Root
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.TreeModel as Gtk.TreeModel
import {-# SOURCE #-} qualified GI.Gtk.Objects.ATContext as Gtk.ATContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.CellArea as Gtk.CellArea
import {-# SOURCE #-} qualified GI.Gtk.Objects.CellAreaContext as Gtk.CellAreaContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.CellRenderer as Gtk.CellRenderer
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutChild as Gtk.LayoutChild
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutManager as Gtk.LayoutManager
import {-# SOURCE #-} qualified GI.Gtk.Objects.Settings as Gtk.Settings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Snapshot as Gtk.Snapshot
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Tooltip as Gtk.Tooltip
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.Requisition as Gtk.Requisition
import {-# SOURCE #-} qualified GI.Gtk.Structs.TreeIter as Gtk.TreeIter
import {-# SOURCE #-} qualified GI.Gtk.Structs.TreePath as Gtk.TreePath
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Objects.Layout as Pango.Layout
#else
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
#endif
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
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]
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
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 <- 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 /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject EntryCompletion ptr
else return 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
type EntryCompletionCursorOnMatchCallback =
Gtk.TreeModel.TreeModel
-> Gtk.TreeIter.TreeIter
-> IO Bool
type C_EntryCompletionCursorOnMatchCallback =
Ptr EntryCompletion ->
Ptr Gtk.TreeModel.TreeModel ->
Ptr Gtk.TreeIter.TreeIter ->
Ptr () ->
IO CInt
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
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
B.ManagedPtr.withTransient iter $ \TreeIter
iter' -> do
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' = (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
return result'
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
wrapped'' <- C_EntryCompletionCursorOnMatchCallback
-> IO (FunPtr C_EntryCompletionCursorOnMatchCallback)
mk_EntryCompletionCursorOnMatchCallback C_EntryCompletionCursorOnMatchCallback
wrapped'
connectSignalFunPtr obj "cursor-on-match" wrapped'' SignalConnectBefore Nothing
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
wrapped'' <- C_EntryCompletionCursorOnMatchCallback
-> IO (FunPtr C_EntryCompletionCursorOnMatchCallback)
mk_EntryCompletionCursorOnMatchCallback C_EntryCompletionCursorOnMatchCallback
wrapped'
connectSignalFunPtr obj "cursor-on-match" wrapped'' SignalConnectAfter 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:signal:cursorOnMatch"})
#endif
type EntryCompletionInsertPrefixCallback =
T.Text
-> IO Bool
type C_EntryCompletionInsertPrefixCallback =
Ptr EntryCompletion ->
CString ->
Ptr () ->
IO CInt
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
prefix' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
prefix
result <- B.ManagedPtr.withNewObject gi'selfPtr $ \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' = (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
return result'
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
wrapped'' <- C_EntryCompletionInsertPrefixCallback
-> IO (FunPtr C_EntryCompletionInsertPrefixCallback)
mk_EntryCompletionInsertPrefixCallback C_EntryCompletionInsertPrefixCallback
wrapped'
connectSignalFunPtr obj "insert-prefix" wrapped'' SignalConnectBefore Nothing
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
wrapped'' <- C_EntryCompletionInsertPrefixCallback
-> IO (FunPtr C_EntryCompletionInsertPrefixCallback)
mk_EntryCompletionInsertPrefixCallback C_EntryCompletionInsertPrefixCallback
wrapped'
connectSignalFunPtr obj "insert-prefix" wrapped'' SignalConnectAfter 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:signal:insertPrefix"})
#endif
type EntryCompletionMatchSelectedCallback =
Gtk.TreeModel.TreeModel
-> Gtk.TreeIter.TreeIter
-> IO Bool
type C_EntryCompletionMatchSelectedCallback =
Ptr EntryCompletion ->
Ptr Gtk.TreeModel.TreeModel ->
Ptr Gtk.TreeIter.TreeIter ->
Ptr () ->
IO CInt
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
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
B.ManagedPtr.withTransient iter $ \TreeIter
iter' -> do
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' = (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
return result'
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
wrapped'' <- C_EntryCompletionCursorOnMatchCallback
-> IO (FunPtr C_EntryCompletionCursorOnMatchCallback)
mk_EntryCompletionMatchSelectedCallback C_EntryCompletionCursorOnMatchCallback
wrapped'
connectSignalFunPtr obj "match-selected" wrapped'' SignalConnectBefore Nothing
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
wrapped'' <- C_EntryCompletionCursorOnMatchCallback
-> IO (FunPtr C_EntryCompletionCursorOnMatchCallback)
mk_EntryCompletionMatchSelectedCallback C_EntryCompletionCursorOnMatchCallback
wrapped'
connectSignalFunPtr obj "match-selected" wrapped'' SignalConnectAfter 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:signal:matchSelected"})
#endif
type EntryCompletionNoMatchesCallback =
IO ()
type C_EntryCompletionNoMatchesCallback =
Ptr EntryCompletion ->
Ptr () ->
IO ()
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)
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
wrapped'' <- C_EntryCompletionNoMatchesCallback
-> IO (FunPtr C_EntryCompletionNoMatchesCallback)
mk_EntryCompletionNoMatchesCallback C_EntryCompletionNoMatchesCallback
wrapped'
connectSignalFunPtr obj "no-matches" wrapped'' SignalConnectBefore Nothing
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
wrapped'' <- C_EntryCompletionNoMatchesCallback
-> IO (FunPtr C_EntryCompletionNoMatchesCallback)
mk_EntryCompletionNoMatchesCallback C_EntryCompletionNoMatchesCallback
wrapped'
connectSignalFunPtr obj "no-matches" wrapped'' SignalConnectAfter 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:signal:noMatches"})
#endif
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
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:cellArea"
})
#endif
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"
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
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:inlineCompletion"
})
#endif
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"
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
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:inlineSelection"
})
#endif
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"
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
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:minimumKeyLength"
})
#endif
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
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)
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)
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:model"
})
#endif
getEntryCompletionPopupCompletion :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
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"
setEntryCompletionPopupCompletion :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
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
constructEntryCompletionPopupCompletion :: (IsEntryCompletion o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:popupCompletion"
})
#endif
getEntryCompletionPopupSetWidth :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
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"
setEntryCompletionPopupSetWidth :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
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
constructEntryCompletionPopupSetWidth :: (IsEntryCompletion o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:popupSetWidth"
})
#endif
getEntryCompletionPopupSingleMatch :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
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"
setEntryCompletionPopupSingleMatch :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
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
constructEntryCompletionPopupSingleMatch :: (IsEntryCompletion o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#g:attr:popupSingleMatch"
})
#endif
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"
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
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-gtk4-4.0.12/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
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."] #-}
entryCompletionNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m EntryCompletion
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
result <- IO (Ptr EntryCompletion)
gtk_entry_completion_new
checkUnexpectedReturnNULL "entryCompletionNew" result
result' <- (wrapObject EntryCompletion) result
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_entry_completion_new_with_area" gtk_entry_completion_new_with_area ::
Ptr Gtk.CellArea.CellArea ->
IO (Ptr EntryCompletion)
{-# DEPRECATED entryCompletionNewWithArea ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionNewWithArea ::
(B.CallStack.HasCallStack, MonadIO m, Gtk.CellArea.IsCellArea a) =>
a
-> m EntryCompletion
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
area' <- a -> IO (Ptr CellArea)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
area
result <- gtk_entry_completion_new_with_area area'
checkUnexpectedReturnNULL "entryCompletionNewWithArea" result
result' <- (wrapObject EntryCompletion) result
touchManagedPtr area
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_entry_completion_complete" gtk_entry_completion_complete ::
Ptr EntryCompletion ->
IO ()
{-# DEPRECATED entryCompletionComplete ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionComplete ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> 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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
gtk_entry_completion_complete completion'
touchManagedPtr completion
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionComplete"
})
#endif
foreign import ccall "gtk_entry_completion_compute_prefix" gtk_entry_completion_compute_prefix ::
Ptr EntryCompletion ->
CString ->
IO CString
{-# DEPRECATED entryCompletionComputePrefix ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionComputePrefix ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> T.Text
-> m (Maybe T.Text)
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
key' <- textToCString key
result <- gtk_entry_completion_compute_prefix completion' key'
maybeResult <- convertIfNonNull result $ \CString
result' -> do
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
freeMem result'
return result''
touchManagedPtr completion
freeMem key'
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionComputePrefix"
})
#endif
foreign import ccall "gtk_entry_completion_get_completion_prefix" gtk_entry_completion_get_completion_prefix ::
Ptr EntryCompletion ->
IO CString
{-# DEPRECATED entryCompletionGetCompletionPrefix ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionGetCompletionPrefix ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> m (Maybe T.Text)
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
result <- gtk_entry_completion_get_completion_prefix completion'
maybeResult <- convertIfNonNull result $ \CString
result' -> do
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
return result''
touchManagedPtr completion
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetCompletionPrefix"
})
#endif
foreign import ccall "gtk_entry_completion_get_entry" gtk_entry_completion_get_entry ::
Ptr EntryCompletion ->
IO (Ptr Gtk.Widget.Widget)
{-# DEPRECATED entryCompletionGetEntry ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionGetEntry ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> m Gtk.Widget.Widget
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
result <- gtk_entry_completion_get_entry completion'
checkUnexpectedReturnNULL "entryCompletionGetEntry" result
result' <- (newObject Gtk.Widget.Widget) result
touchManagedPtr completion
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetEntry"
})
#endif
foreign import ccall "gtk_entry_completion_get_inline_completion" gtk_entry_completion_get_inline_completion ::
Ptr EntryCompletion ->
IO CInt
{-# DEPRECATED entryCompletionGetInlineCompletion ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionGetInlineCompletion ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> m Bool
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
result <- gtk_entry_completion_get_inline_completion completion'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr completion
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetInlineCompletion"
})
#endif
foreign import ccall "gtk_entry_completion_get_inline_selection" gtk_entry_completion_get_inline_selection ::
Ptr EntryCompletion ->
IO CInt
{-# DEPRECATED entryCompletionGetInlineSelection ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionGetInlineSelection ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> m Bool
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
result <- gtk_entry_completion_get_inline_selection completion'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr completion
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetInlineSelection"
})
#endif
foreign import ccall "gtk_entry_completion_get_minimum_key_length" gtk_entry_completion_get_minimum_key_length ::
Ptr EntryCompletion ->
IO Int32
{-# DEPRECATED entryCompletionGetMinimumKeyLength ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionGetMinimumKeyLength ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> m Int32
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
result <- gtk_entry_completion_get_minimum_key_length completion'
touchManagedPtr completion
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetMinimumKeyLength"
})
#endif
foreign import ccall "gtk_entry_completion_get_model" gtk_entry_completion_get_model ::
Ptr EntryCompletion ->
IO (Ptr Gtk.TreeModel.TreeModel)
{-# DEPRECATED entryCompletionGetModel ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionGetModel ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> m (Maybe Gtk.TreeModel.TreeModel)
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
result <- gtk_entry_completion_get_model completion'
maybeResult <- convertIfNonNull result $ \Ptr TreeModel
result' -> do
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'
return result''
touchManagedPtr completion
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetModel"
})
#endif
foreign import ccall "gtk_entry_completion_get_popup_completion" ::
Ptr EntryCompletion ->
IO CInt
{-# DEPRECATED entryCompletionGetPopupCompletion ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionGetPopupCompletion ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> m Bool
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
result <- gtk_entry_completion_get_popup_completion completion'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr completion
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetPopupCompletion"
})
#endif
foreign import ccall "gtk_entry_completion_get_popup_set_width" ::
Ptr EntryCompletion ->
IO CInt
{-# DEPRECATED entryCompletionGetPopupSetWidth ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionGetPopupSetWidth ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> m Bool
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
result <- gtk_entry_completion_get_popup_set_width completion'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr completion
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetPopupSetWidth"
})
#endif
foreign import ccall "gtk_entry_completion_get_popup_single_match" ::
Ptr EntryCompletion ->
IO CInt
{-# DEPRECATED entryCompletionGetPopupSingleMatch ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionGetPopupSingleMatch ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> m Bool
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
result <- gtk_entry_completion_get_popup_single_match completion'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr completion
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetPopupSingleMatch"
})
#endif
foreign import ccall "gtk_entry_completion_get_text_column" gtk_entry_completion_get_text_column ::
Ptr EntryCompletion ->
IO Int32
{-# DEPRECATED entryCompletionGetTextColumn ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionGetTextColumn ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> m Int32
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
result <- gtk_entry_completion_get_text_column completion'
touchManagedPtr completion
return 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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionGetTextColumn"
})
#endif
foreign import ccall "gtk_entry_completion_insert_prefix" gtk_entry_completion_insert_prefix ::
Ptr EntryCompletion ->
IO ()
{-# DEPRECATED entryCompletionInsertPrefix ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionInsertPrefix ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> 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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
gtk_entry_completion_insert_prefix completion'
touchManagedPtr completion
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionInsertPrefix"
})
#endif
foreign import ccall "gtk_entry_completion_set_inline_completion" gtk_entry_completion_set_inline_completion ::
Ptr EntryCompletion ->
CInt ->
IO ()
{-# DEPRECATED entryCompletionSetInlineCompletion ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionSetInlineCompletion ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> Bool
-> 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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
let 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
gtk_entry_completion_set_inline_completion completion' inlineCompletion'
touchManagedPtr completion
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetInlineCompletion"
})
#endif
foreign import ccall "gtk_entry_completion_set_inline_selection" gtk_entry_completion_set_inline_selection ::
Ptr EntryCompletion ->
CInt ->
IO ()
{-# DEPRECATED entryCompletionSetInlineSelection ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionSetInlineSelection ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> Bool
-> 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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
let 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
gtk_entry_completion_set_inline_selection completion' inlineSelection'
touchManagedPtr completion
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetInlineSelection"
})
#endif
foreign import ccall "gtk_entry_completion_set_match_func" gtk_entry_completion_set_match_func ::
Ptr EntryCompletion ->
FunPtr Gtk.Callbacks.C_EntryCompletionMatchFunc ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
{-# DEPRECATED entryCompletionSetMatchFunc ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionSetMatchFunc ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> Gtk.Callbacks.EntryCompletionMatchFunc
-> 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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
func' <- Gtk.Callbacks.mk_EntryCompletionMatchFunc (Gtk.Callbacks.wrap_EntryCompletionMatchFunc Nothing (Gtk.Callbacks.drop_closures_EntryCompletionMatchFunc func))
let funcData = FunPtr C_EntryCompletionMatchFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_EntryCompletionMatchFunc
func'
let funcNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
gtk_entry_completion_set_match_func completion' func' funcData funcNotify
touchManagedPtr completion
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetMatchFunc"
})
#endif
foreign import ccall "gtk_entry_completion_set_minimum_key_length" gtk_entry_completion_set_minimum_key_length ::
Ptr EntryCompletion ->
Int32 ->
IO ()
{-# DEPRECATED entryCompletionSetMinimumKeyLength ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionSetMinimumKeyLength ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> Int32
-> 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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
gtk_entry_completion_set_minimum_key_length completion' length_
touchManagedPtr completion
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetMinimumKeyLength"
})
#endif
foreign import ccall "gtk_entry_completion_set_model" gtk_entry_completion_set_model ::
Ptr EntryCompletion ->
Ptr Gtk.TreeModel.TreeModel ->
IO ()
{-# DEPRECATED entryCompletionSetModel ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionSetModel ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a, Gtk.TreeModel.IsTreeModel b) =>
a
-> Maybe (b)
-> 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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
maybeModel <- case 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
FP.nullPtr
Just b
jModel -> do
jModel' <- b -> IO (Ptr TreeModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
return jModel'
gtk_entry_completion_set_model completion' maybeModel
touchManagedPtr completion
whenJust model touchManagedPtr
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetModel"
})
#endif
foreign import ccall "gtk_entry_completion_set_popup_completion" ::
Ptr EntryCompletion ->
CInt ->
IO ()
{-# DEPRECATED entryCompletionSetPopupCompletion ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionSetPopupCompletion ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> Bool
-> m ()
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
let 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
gtk_entry_completion_set_popup_completion completion' popupCompletion'
touchManagedPtr completion
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetPopupCompletion"
})
#endif
foreign import ccall "gtk_entry_completion_set_popup_set_width" ::
Ptr EntryCompletion ->
CInt ->
IO ()
{-# DEPRECATED entryCompletionSetPopupSetWidth ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionSetPopupSetWidth ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> Bool
-> m ()
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
let 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
gtk_entry_completion_set_popup_set_width completion' popupSetWidth'
touchManagedPtr completion
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetPopupSetWidth"
})
#endif
foreign import ccall "gtk_entry_completion_set_popup_single_match" ::
Ptr EntryCompletion ->
CInt ->
IO ()
{-# DEPRECATED entryCompletionSetPopupSingleMatch ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionSetPopupSingleMatch ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> Bool
-> m ()
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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
let 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
gtk_entry_completion_set_popup_single_match completion' popupSingleMatch'
touchManagedPtr completion
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetPopupSingleMatch"
})
#endif
foreign import ccall "gtk_entry_completion_set_text_column" gtk_entry_completion_set_text_column ::
Ptr EntryCompletion ->
Int32 ->
IO ()
{-# DEPRECATED entryCompletionSetTextColumn ["(Since version 4.10)","GtkEntryCompletion will be removed in GTK 5."] #-}
entryCompletionSetTextColumn ::
(B.CallStack.HasCallStack, MonadIO m, IsEntryCompletion a) =>
a
-> Int32
-> 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
completion' <- a -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
completion
gtk_entry_completion_set_text_column completion' column
touchManagedPtr completion
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-gtk4-4.0.12/docs/GI-Gtk-Objects-EntryCompletion.html#v:entryCompletionSetTextColumn"
})
#endif