{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.Entry
    ( 
    Entry(..)                               ,
    IsEntry                                 ,
    toEntry                                 ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveEntryMethod                      ,
#endif
#if defined(ENABLE_OVERLOADING)
    EntryGetActivatesDefaultMethodInfo      ,
#endif
    entryGetActivatesDefault                ,
#if defined(ENABLE_OVERLOADING)
    EntryGetAlignmentMethodInfo             ,
#endif
    entryGetAlignment                       ,
#if defined(ENABLE_OVERLOADING)
    EntryGetAttributesMethodInfo            ,
#endif
    entryGetAttributes                      ,
#if defined(ENABLE_OVERLOADING)
    EntryGetBufferMethodInfo                ,
#endif
    entryGetBuffer                          ,
#if defined(ENABLE_OVERLOADING)
    EntryGetCompletionMethodInfo            ,
#endif
    entryGetCompletion                      ,
#if defined(ENABLE_OVERLOADING)
    EntryGetCurrentIconDragSourceMethodInfo ,
#endif
    entryGetCurrentIconDragSource           ,
#if defined(ENABLE_OVERLOADING)
    EntryGetExtraMenuMethodInfo             ,
#endif
    entryGetExtraMenu                       ,
#if defined(ENABLE_OVERLOADING)
    EntryGetHasFrameMethodInfo              ,
#endif
    entryGetHasFrame                        ,
#if defined(ENABLE_OVERLOADING)
    EntryGetIconActivatableMethodInfo       ,
#endif
    entryGetIconActivatable                 ,
#if defined(ENABLE_OVERLOADING)
    EntryGetIconAreaMethodInfo              ,
#endif
    entryGetIconArea                        ,
#if defined(ENABLE_OVERLOADING)
    EntryGetIconAtPosMethodInfo             ,
#endif
    entryGetIconAtPos                       ,
#if defined(ENABLE_OVERLOADING)
    EntryGetIconGiconMethodInfo             ,
#endif
    entryGetIconGicon                       ,
#if defined(ENABLE_OVERLOADING)
    EntryGetIconNameMethodInfo              ,
#endif
    entryGetIconName                        ,
#if defined(ENABLE_OVERLOADING)
    EntryGetIconPaintableMethodInfo         ,
#endif
    entryGetIconPaintable                   ,
#if defined(ENABLE_OVERLOADING)
    EntryGetIconSensitiveMethodInfo         ,
#endif
    entryGetIconSensitive                   ,
#if defined(ENABLE_OVERLOADING)
    EntryGetIconStorageTypeMethodInfo       ,
#endif
    entryGetIconStorageType                 ,
#if defined(ENABLE_OVERLOADING)
    EntryGetIconTooltipMarkupMethodInfo     ,
#endif
    entryGetIconTooltipMarkup               ,
#if defined(ENABLE_OVERLOADING)
    EntryGetIconTooltipTextMethodInfo       ,
#endif
    entryGetIconTooltipText                 ,
#if defined(ENABLE_OVERLOADING)
    EntryGetInputHintsMethodInfo            ,
#endif
    entryGetInputHints                      ,
#if defined(ENABLE_OVERLOADING)
    EntryGetInputPurposeMethodInfo          ,
#endif
    entryGetInputPurpose                    ,
#if defined(ENABLE_OVERLOADING)
    EntryGetInvisibleCharMethodInfo         ,
#endif
    entryGetInvisibleChar                   ,
#if defined(ENABLE_OVERLOADING)
    EntryGetMaxLengthMethodInfo             ,
#endif
    entryGetMaxLength                       ,
#if defined(ENABLE_OVERLOADING)
    EntryGetOverwriteModeMethodInfo         ,
#endif
    entryGetOverwriteMode                   ,
#if defined(ENABLE_OVERLOADING)
    EntryGetPlaceholderTextMethodInfo       ,
#endif
    entryGetPlaceholderText                 ,
#if defined(ENABLE_OVERLOADING)
    EntryGetProgressFractionMethodInfo      ,
#endif
    entryGetProgressFraction                ,
#if defined(ENABLE_OVERLOADING)
    EntryGetProgressPulseStepMethodInfo     ,
#endif
    entryGetProgressPulseStep               ,
#if defined(ENABLE_OVERLOADING)
    EntryGetTabsMethodInfo                  ,
#endif
    entryGetTabs                            ,
#if defined(ENABLE_OVERLOADING)
    EntryGetTextLengthMethodInfo            ,
#endif
    entryGetTextLength                      ,
#if defined(ENABLE_OVERLOADING)
    EntryGetVisibilityMethodInfo            ,
#endif
    entryGetVisibility                      ,
#if defined(ENABLE_OVERLOADING)
    EntryGrabFocusWithoutSelectingMethodInfo,
#endif
    entryGrabFocusWithoutSelecting          ,
    entryNew                                ,
    entryNewWithBuffer                      ,
#if defined(ENABLE_OVERLOADING)
    EntryProgressPulseMethodInfo            ,
#endif
    entryProgressPulse                      ,
#if defined(ENABLE_OVERLOADING)
    EntryResetImContextMethodInfo           ,
#endif
    entryResetImContext                     ,
#if defined(ENABLE_OVERLOADING)
    EntrySetActivatesDefaultMethodInfo      ,
#endif
    entrySetActivatesDefault                ,
#if defined(ENABLE_OVERLOADING)
    EntrySetAlignmentMethodInfo             ,
#endif
    entrySetAlignment                       ,
#if defined(ENABLE_OVERLOADING)
    EntrySetAttributesMethodInfo            ,
#endif
    entrySetAttributes                      ,
#if defined(ENABLE_OVERLOADING)
    EntrySetBufferMethodInfo                ,
#endif
    entrySetBuffer                          ,
#if defined(ENABLE_OVERLOADING)
    EntrySetCompletionMethodInfo            ,
#endif
    entrySetCompletion                      ,
#if defined(ENABLE_OVERLOADING)
    EntrySetExtraMenuMethodInfo             ,
#endif
    entrySetExtraMenu                       ,
#if defined(ENABLE_OVERLOADING)
    EntrySetHasFrameMethodInfo              ,
#endif
    entrySetHasFrame                        ,
#if defined(ENABLE_OVERLOADING)
    EntrySetIconActivatableMethodInfo       ,
#endif
    entrySetIconActivatable                 ,
#if defined(ENABLE_OVERLOADING)
    EntrySetIconDragSourceMethodInfo        ,
#endif
    entrySetIconDragSource                  ,
#if defined(ENABLE_OVERLOADING)
    EntrySetIconFromGiconMethodInfo         ,
#endif
    entrySetIconFromGicon                   ,
#if defined(ENABLE_OVERLOADING)
    EntrySetIconFromIconNameMethodInfo      ,
#endif
    entrySetIconFromIconName                ,
#if defined(ENABLE_OVERLOADING)
    EntrySetIconFromPaintableMethodInfo     ,
#endif
    entrySetIconFromPaintable               ,
#if defined(ENABLE_OVERLOADING)
    EntrySetIconSensitiveMethodInfo         ,
#endif
    entrySetIconSensitive                   ,
#if defined(ENABLE_OVERLOADING)
    EntrySetIconTooltipMarkupMethodInfo     ,
#endif
    entrySetIconTooltipMarkup               ,
#if defined(ENABLE_OVERLOADING)
    EntrySetIconTooltipTextMethodInfo       ,
#endif
    entrySetIconTooltipText                 ,
#if defined(ENABLE_OVERLOADING)
    EntrySetInputHintsMethodInfo            ,
#endif
    entrySetInputHints                      ,
#if defined(ENABLE_OVERLOADING)
    EntrySetInputPurposeMethodInfo          ,
#endif
    entrySetInputPurpose                    ,
#if defined(ENABLE_OVERLOADING)
    EntrySetInvisibleCharMethodInfo         ,
#endif
    entrySetInvisibleChar                   ,
#if defined(ENABLE_OVERLOADING)
    EntrySetMaxLengthMethodInfo             ,
#endif
    entrySetMaxLength                       ,
#if defined(ENABLE_OVERLOADING)
    EntrySetOverwriteModeMethodInfo         ,
#endif
    entrySetOverwriteMode                   ,
#if defined(ENABLE_OVERLOADING)
    EntrySetPlaceholderTextMethodInfo       ,
#endif
    entrySetPlaceholderText                 ,
#if defined(ENABLE_OVERLOADING)
    EntrySetProgressFractionMethodInfo      ,
#endif
    entrySetProgressFraction                ,
#if defined(ENABLE_OVERLOADING)
    EntrySetProgressPulseStepMethodInfo     ,
#endif
    entrySetProgressPulseStep               ,
#if defined(ENABLE_OVERLOADING)
    EntrySetTabsMethodInfo                  ,
#endif
    entrySetTabs                            ,
#if defined(ENABLE_OVERLOADING)
    EntrySetVisibilityMethodInfo            ,
#endif
    entrySetVisibility                      ,
#if defined(ENABLE_OVERLOADING)
    EntryUnsetInvisibleCharMethodInfo       ,
#endif
    entryUnsetInvisibleChar                 ,
 
#if defined(ENABLE_OVERLOADING)
    EntryActivatesDefaultPropertyInfo       ,
#endif
    constructEntryActivatesDefault          ,
#if defined(ENABLE_OVERLOADING)
    entryActivatesDefault                   ,
#endif
    getEntryActivatesDefault                ,
    setEntryActivatesDefault                ,
#if defined(ENABLE_OVERLOADING)
    EntryAttributesPropertyInfo             ,
#endif
    constructEntryAttributes                ,
#if defined(ENABLE_OVERLOADING)
    entryAttributes                         ,
#endif
    getEntryAttributes                      ,
    setEntryAttributes                      ,
#if defined(ENABLE_OVERLOADING)
    EntryBufferPropertyInfo                 ,
#endif
    constructEntryBuffer                    ,
#if defined(ENABLE_OVERLOADING)
    entryBuffer                             ,
#endif
    getEntryBuffer                          ,
    setEntryBuffer                          ,
#if defined(ENABLE_OVERLOADING)
    EntryCompletionPropertyInfo             ,
#endif
    clearEntryCompletion                    ,
    constructEntryCompletion                ,
#if defined(ENABLE_OVERLOADING)
    entryCompletion                         ,
#endif
    getEntryCompletion                      ,
    setEntryCompletion                      ,
#if defined(ENABLE_OVERLOADING)
    EntryEnableEmojiCompletionPropertyInfo  ,
#endif
    constructEntryEnableEmojiCompletion     ,
#if defined(ENABLE_OVERLOADING)
    entryEnableEmojiCompletion              ,
#endif
    getEntryEnableEmojiCompletion           ,
    setEntryEnableEmojiCompletion           ,
#if defined(ENABLE_OVERLOADING)
    EntryExtraMenuPropertyInfo              ,
#endif
    clearEntryExtraMenu                     ,
    constructEntryExtraMenu                 ,
#if defined(ENABLE_OVERLOADING)
    entryExtraMenu                          ,
#endif
    getEntryExtraMenu                       ,
    setEntryExtraMenu                       ,
#if defined(ENABLE_OVERLOADING)
    EntryHasFramePropertyInfo               ,
#endif
    constructEntryHasFrame                  ,
#if defined(ENABLE_OVERLOADING)
    entryHasFrame                           ,
#endif
    getEntryHasFrame                        ,
    setEntryHasFrame                        ,
#if defined(ENABLE_OVERLOADING)
    EntryImModulePropertyInfo               ,
#endif
    clearEntryImModule                      ,
    constructEntryImModule                  ,
#if defined(ENABLE_OVERLOADING)
    entryImModule                           ,
#endif
    getEntryImModule                        ,
    setEntryImModule                        ,
#if defined(ENABLE_OVERLOADING)
    EntryInputHintsPropertyInfo             ,
#endif
    constructEntryInputHints                ,
#if defined(ENABLE_OVERLOADING)
    entryInputHints                         ,
#endif
    getEntryInputHints                      ,
    setEntryInputHints                      ,
#if defined(ENABLE_OVERLOADING)
    EntryInputPurposePropertyInfo           ,
#endif
    constructEntryInputPurpose              ,
#if defined(ENABLE_OVERLOADING)
    entryInputPurpose                       ,
#endif
    getEntryInputPurpose                    ,
    setEntryInputPurpose                    ,
#if defined(ENABLE_OVERLOADING)
    EntryInvisibleCharPropertyInfo          ,
#endif
    constructEntryInvisibleChar             ,
#if defined(ENABLE_OVERLOADING)
    entryInvisibleChar                      ,
#endif
    getEntryInvisibleChar                   ,
    setEntryInvisibleChar                   ,
#if defined(ENABLE_OVERLOADING)
    EntryInvisibleCharSetPropertyInfo       ,
#endif
    constructEntryInvisibleCharSet          ,
#if defined(ENABLE_OVERLOADING)
    entryInvisibleCharSet                   ,
#endif
    getEntryInvisibleCharSet                ,
    setEntryInvisibleCharSet                ,
#if defined(ENABLE_OVERLOADING)
    EntryMaxLengthPropertyInfo              ,
#endif
    constructEntryMaxLength                 ,
#if defined(ENABLE_OVERLOADING)
    entryMaxLength                          ,
#endif
    getEntryMaxLength                       ,
    setEntryMaxLength                       ,
#if defined(ENABLE_OVERLOADING)
    EntryOverwriteModePropertyInfo          ,
#endif
    constructEntryOverwriteMode             ,
#if defined(ENABLE_OVERLOADING)
    entryOverwriteMode                      ,
#endif
    getEntryOverwriteMode                   ,
    setEntryOverwriteMode                   ,
#if defined(ENABLE_OVERLOADING)
    EntryPlaceholderTextPropertyInfo        ,
#endif
    clearEntryPlaceholderText               ,
    constructEntryPlaceholderText           ,
#if defined(ENABLE_OVERLOADING)
    entryPlaceholderText                    ,
#endif
    getEntryPlaceholderText                 ,
    setEntryPlaceholderText                 ,
#if defined(ENABLE_OVERLOADING)
    EntryPrimaryIconActivatablePropertyInfo ,
#endif
    constructEntryPrimaryIconActivatable    ,
#if defined(ENABLE_OVERLOADING)
    entryPrimaryIconActivatable             ,
#endif
    getEntryPrimaryIconActivatable          ,
    setEntryPrimaryIconActivatable          ,
#if defined(ENABLE_OVERLOADING)
    EntryPrimaryIconGiconPropertyInfo       ,
#endif
    clearEntryPrimaryIconGicon              ,
    constructEntryPrimaryIconGicon          ,
#if defined(ENABLE_OVERLOADING)
    entryPrimaryIconGicon                   ,
#endif
    getEntryPrimaryIconGicon                ,
    setEntryPrimaryIconGicon                ,
#if defined(ENABLE_OVERLOADING)
    EntryPrimaryIconNamePropertyInfo        ,
#endif
    clearEntryPrimaryIconName               ,
    constructEntryPrimaryIconName           ,
#if defined(ENABLE_OVERLOADING)
    entryPrimaryIconName                    ,
#endif
    getEntryPrimaryIconName                 ,
    setEntryPrimaryIconName                 ,
#if defined(ENABLE_OVERLOADING)
    EntryPrimaryIconPaintablePropertyInfo   ,
#endif
    clearEntryPrimaryIconPaintable          ,
    constructEntryPrimaryIconPaintable      ,
#if defined(ENABLE_OVERLOADING)
    entryPrimaryIconPaintable               ,
#endif
    getEntryPrimaryIconPaintable            ,
    setEntryPrimaryIconPaintable            ,
#if defined(ENABLE_OVERLOADING)
    EntryPrimaryIconSensitivePropertyInfo   ,
#endif
    constructEntryPrimaryIconSensitive      ,
#if defined(ENABLE_OVERLOADING)
    entryPrimaryIconSensitive               ,
#endif
    getEntryPrimaryIconSensitive            ,
    setEntryPrimaryIconSensitive            ,
#if defined(ENABLE_OVERLOADING)
    EntryPrimaryIconStorageTypePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
    entryPrimaryIconStorageType             ,
#endif
    getEntryPrimaryIconStorageType          ,
#if defined(ENABLE_OVERLOADING)
    EntryPrimaryIconTooltipMarkupPropertyInfo,
#endif
    clearEntryPrimaryIconTooltipMarkup      ,
    constructEntryPrimaryIconTooltipMarkup  ,
#if defined(ENABLE_OVERLOADING)
    entryPrimaryIconTooltipMarkup           ,
#endif
    getEntryPrimaryIconTooltipMarkup        ,
    setEntryPrimaryIconTooltipMarkup        ,
#if defined(ENABLE_OVERLOADING)
    EntryPrimaryIconTooltipTextPropertyInfo ,
#endif
    clearEntryPrimaryIconTooltipText        ,
    constructEntryPrimaryIconTooltipText    ,
#if defined(ENABLE_OVERLOADING)
    entryPrimaryIconTooltipText             ,
#endif
    getEntryPrimaryIconTooltipText          ,
    setEntryPrimaryIconTooltipText          ,
#if defined(ENABLE_OVERLOADING)
    EntryProgressFractionPropertyInfo       ,
#endif
    constructEntryProgressFraction          ,
#if defined(ENABLE_OVERLOADING)
    entryProgressFraction                   ,
#endif
    getEntryProgressFraction                ,
    setEntryProgressFraction                ,
#if defined(ENABLE_OVERLOADING)
    EntryProgressPulseStepPropertyInfo      ,
#endif
    constructEntryProgressPulseStep         ,
#if defined(ENABLE_OVERLOADING)
    entryProgressPulseStep                  ,
#endif
    getEntryProgressPulseStep               ,
    setEntryProgressPulseStep               ,
#if defined(ENABLE_OVERLOADING)
    EntryScrollOffsetPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    entryScrollOffset                       ,
#endif
    getEntryScrollOffset                    ,
#if defined(ENABLE_OVERLOADING)
    EntrySecondaryIconActivatablePropertyInfo,
#endif
    constructEntrySecondaryIconActivatable  ,
#if defined(ENABLE_OVERLOADING)
    entrySecondaryIconActivatable           ,
#endif
    getEntrySecondaryIconActivatable        ,
    setEntrySecondaryIconActivatable        ,
#if defined(ENABLE_OVERLOADING)
    EntrySecondaryIconGiconPropertyInfo     ,
#endif
    clearEntrySecondaryIconGicon            ,
    constructEntrySecondaryIconGicon        ,
#if defined(ENABLE_OVERLOADING)
    entrySecondaryIconGicon                 ,
#endif
    getEntrySecondaryIconGicon              ,
    setEntrySecondaryIconGicon              ,
#if defined(ENABLE_OVERLOADING)
    EntrySecondaryIconNamePropertyInfo      ,
#endif
    clearEntrySecondaryIconName             ,
    constructEntrySecondaryIconName         ,
#if defined(ENABLE_OVERLOADING)
    entrySecondaryIconName                  ,
#endif
    getEntrySecondaryIconName               ,
    setEntrySecondaryIconName               ,
#if defined(ENABLE_OVERLOADING)
    EntrySecondaryIconPaintablePropertyInfo ,
#endif
    clearEntrySecondaryIconPaintable        ,
    constructEntrySecondaryIconPaintable    ,
#if defined(ENABLE_OVERLOADING)
    entrySecondaryIconPaintable             ,
#endif
    getEntrySecondaryIconPaintable          ,
    setEntrySecondaryIconPaintable          ,
#if defined(ENABLE_OVERLOADING)
    EntrySecondaryIconSensitivePropertyInfo ,
#endif
    constructEntrySecondaryIconSensitive    ,
#if defined(ENABLE_OVERLOADING)
    entrySecondaryIconSensitive             ,
#endif
    getEntrySecondaryIconSensitive          ,
    setEntrySecondaryIconSensitive          ,
#if defined(ENABLE_OVERLOADING)
    EntrySecondaryIconStorageTypePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    entrySecondaryIconStorageType           ,
#endif
    getEntrySecondaryIconStorageType        ,
#if defined(ENABLE_OVERLOADING)
    EntrySecondaryIconTooltipMarkupPropertyInfo,
#endif
    clearEntrySecondaryIconTooltipMarkup    ,
    constructEntrySecondaryIconTooltipMarkup,
#if defined(ENABLE_OVERLOADING)
    entrySecondaryIconTooltipMarkup         ,
#endif
    getEntrySecondaryIconTooltipMarkup      ,
    setEntrySecondaryIconTooltipMarkup      ,
#if defined(ENABLE_OVERLOADING)
    EntrySecondaryIconTooltipTextPropertyInfo,
#endif
    clearEntrySecondaryIconTooltipText      ,
    constructEntrySecondaryIconTooltipText  ,
#if defined(ENABLE_OVERLOADING)
    entrySecondaryIconTooltipText           ,
#endif
    getEntrySecondaryIconTooltipText        ,
    setEntrySecondaryIconTooltipText        ,
#if defined(ENABLE_OVERLOADING)
    EntryShowEmojiIconPropertyInfo          ,
#endif
    constructEntryShowEmojiIcon             ,
#if defined(ENABLE_OVERLOADING)
    entryShowEmojiIcon                      ,
#endif
    getEntryShowEmojiIcon                   ,
    setEntryShowEmojiIcon                   ,
#if defined(ENABLE_OVERLOADING)
    EntryTabsPropertyInfo                   ,
#endif
    clearEntryTabs                          ,
    constructEntryTabs                      ,
#if defined(ENABLE_OVERLOADING)
    entryTabs                               ,
#endif
    getEntryTabs                            ,
    setEntryTabs                            ,
#if defined(ENABLE_OVERLOADING)
    EntryTextLengthPropertyInfo             ,
#endif
#if defined(ENABLE_OVERLOADING)
    entryTextLength                         ,
#endif
    getEntryTextLength                      ,
#if defined(ENABLE_OVERLOADING)
    EntryTruncateMultilinePropertyInfo      ,
#endif
    constructEntryTruncateMultiline         ,
#if defined(ENABLE_OVERLOADING)
    entryTruncateMultiline                  ,
#endif
    getEntryTruncateMultiline               ,
    setEntryTruncateMultiline               ,
#if defined(ENABLE_OVERLOADING)
    EntryVisibilityPropertyInfo             ,
#endif
    constructEntryVisibility                ,
#if defined(ENABLE_OVERLOADING)
    entryVisibility                         ,
#endif
    getEntryVisibility                      ,
    setEntryVisibility                      ,
 
    C_EntryActivateCallback                 ,
    EntryActivateCallback                   ,
#if defined(ENABLE_OVERLOADING)
    EntryActivateSignalInfo                 ,
#endif
    afterEntryActivate                      ,
    genClosure_EntryActivate                ,
    mk_EntryActivateCallback                ,
    noEntryActivateCallback                 ,
    onEntryActivate                         ,
    wrap_EntryActivateCallback              ,
    C_EntryIconPressCallback                ,
    EntryIconPressCallback                  ,
#if defined(ENABLE_OVERLOADING)
    EntryIconPressSignalInfo                ,
#endif
    afterEntryIconPress                     ,
    genClosure_EntryIconPress               ,
    mk_EntryIconPressCallback               ,
    noEntryIconPressCallback                ,
    onEntryIconPress                        ,
    wrap_EntryIconPressCallback             ,
    C_EntryIconReleaseCallback              ,
    EntryIconReleaseCallback                ,
#if defined(ENABLE_OVERLOADING)
    EntryIconReleaseSignalInfo              ,
#endif
    afterEntryIconRelease                   ,
    genClosure_EntryIconRelease             ,
    mk_EntryIconReleaseCallback             ,
    noEntryIconReleaseCallback              ,
    onEntryIconRelease                      ,
    wrap_EntryIconReleaseCallback           ,
    ) 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.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
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.ContentProvider as Gdk.ContentProvider
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
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.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Editable as Gtk.Editable
import {-# SOURCE #-} qualified GI.Gtk.Objects.EntryBuffer as Gtk.EntryBuffer
import {-# SOURCE #-} qualified GI.Gtk.Objects.EntryCompletion as Gtk.EntryCompletion
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import qualified GI.Pango.Structs.AttrList as Pango.AttrList
import qualified GI.Pango.Structs.TabArray as Pango.TabArray
newtype Entry = Entry (SP.ManagedPtr Entry)
    deriving (Entry -> Entry -> Bool
(Entry -> Entry -> Bool) -> (Entry -> Entry -> Bool) -> Eq Entry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Entry -> Entry -> Bool
$c/= :: Entry -> Entry -> Bool
== :: Entry -> Entry -> Bool
$c== :: Entry -> Entry -> Bool
Eq)
instance SP.ManagedPtrNewtype Entry where
    toManagedPtr :: Entry -> ManagedPtr Entry
toManagedPtr (Entry ManagedPtr Entry
p) = ManagedPtr Entry
p
foreign import ccall "gtk_entry_get_type"
    c_gtk_entry_get_type :: IO B.Types.GType
instance B.Types.TypedObject Entry where
    glibType :: IO GType
glibType = IO GType
c_gtk_entry_get_type
instance B.Types.GObject Entry
class (SP.GObject o, O.IsDescendantOf Entry o) => IsEntry o
instance (SP.GObject o, O.IsDescendantOf Entry o) => IsEntry o
instance O.HasParentTypes Entry
type instance O.ParentTypes Entry = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.CellEditable.CellEditable, Gtk.ConstraintTarget.ConstraintTarget, Gtk.Editable.Editable]
toEntry :: (MIO.MonadIO m, IsEntry o) => o -> m Entry
toEntry :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Entry
toEntry = IO Entry -> m Entry
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Entry -> m Entry) -> (o -> IO Entry) -> o -> m Entry
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Entry -> Entry) -> o -> IO Entry
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Entry -> Entry
Entry
instance B.GValue.IsGValue (Maybe Entry) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_entry_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Entry -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Entry
P.Nothing = Ptr GValue -> Ptr Entry -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Entry
forall a. Ptr a
FP.nullPtr :: FP.Ptr Entry)
    gvalueSet_ Ptr GValue
gv (P.Just Entry
obj) = Entry -> (Ptr Entry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Entry
obj (Ptr GValue -> Ptr Entry -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Entry)
gvalueGet_ Ptr GValue
gv = do
        Ptr Entry
ptr <- Ptr GValue -> IO (Ptr Entry)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Entry)
        if Ptr Entry
ptr Ptr Entry -> Ptr Entry -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Entry
forall a. Ptr a
FP.nullPtr
        then Entry -> Maybe Entry
forall a. a -> Maybe a
P.Just (Entry -> Maybe Entry) -> IO Entry -> IO (Maybe Entry)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Entry -> Entry) -> Ptr Entry -> IO Entry
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Entry -> Entry
Entry Ptr Entry
ptr
        else Maybe Entry -> IO (Maybe Entry)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Entry
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveEntryMethod (t :: Symbol) (o :: *) :: * where
    ResolveEntryMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveEntryMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveEntryMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveEntryMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveEntryMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveEntryMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveEntryMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveEntryMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveEntryMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveEntryMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveEntryMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveEntryMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveEntryMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveEntryMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveEntryMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveEntryMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveEntryMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveEntryMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveEntryMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveEntryMethod "deleteSelection" o = Gtk.Editable.EditableDeleteSelectionMethodInfo
    ResolveEntryMethod "deleteText" o = Gtk.Editable.EditableDeleteTextMethodInfo
    ResolveEntryMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveEntryMethod "editingDone" o = Gtk.CellEditable.CellEditableEditingDoneMethodInfo
    ResolveEntryMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveEntryMethod "finishDelegate" o = Gtk.Editable.EditableFinishDelegateMethodInfo
    ResolveEntryMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveEntryMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveEntryMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveEntryMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveEntryMethod "grabFocusWithoutSelecting" o = EntryGrabFocusWithoutSelectingMethodInfo
    ResolveEntryMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveEntryMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveEntryMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveEntryMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveEntryMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveEntryMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveEntryMethod "initDelegate" o = Gtk.Editable.EditableInitDelegateMethodInfo
    ResolveEntryMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveEntryMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveEntryMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveEntryMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveEntryMethod "insertText" o = Gtk.Editable.EditableInsertTextMethodInfo
    ResolveEntryMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveEntryMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveEntryMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveEntryMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveEntryMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveEntryMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveEntryMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveEntryMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveEntryMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveEntryMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveEntryMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveEntryMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveEntryMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveEntryMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveEntryMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveEntryMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveEntryMethod "progressPulse" o = EntryProgressPulseMethodInfo
    ResolveEntryMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveEntryMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveEntryMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveEntryMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveEntryMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveEntryMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveEntryMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveEntryMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveEntryMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveEntryMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveEntryMethod "removeWidget" o = Gtk.CellEditable.CellEditableRemoveWidgetMethodInfo
    ResolveEntryMethod "resetImContext" o = EntryResetImContextMethodInfo
    ResolveEntryMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveEntryMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveEntryMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveEntryMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveEntryMethod "selectRegion" o = Gtk.Editable.EditableSelectRegionMethodInfo
    ResolveEntryMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveEntryMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveEntryMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveEntryMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveEntryMethod "startEditing" o = Gtk.CellEditable.CellEditableStartEditingMethodInfo
    ResolveEntryMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveEntryMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveEntryMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveEntryMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveEntryMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveEntryMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveEntryMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveEntryMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveEntryMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveEntryMethod "unsetInvisibleChar" o = EntryUnsetInvisibleCharMethodInfo
    ResolveEntryMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveEntryMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveEntryMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveEntryMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveEntryMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveEntryMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveEntryMethod "getActivatesDefault" o = EntryGetActivatesDefaultMethodInfo
    ResolveEntryMethod "getAlignment" o = EntryGetAlignmentMethodInfo
    ResolveEntryMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveEntryMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveEntryMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveEntryMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveEntryMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveEntryMethod "getAttributes" o = EntryGetAttributesMethodInfo
    ResolveEntryMethod "getBuffer" o = EntryGetBufferMethodInfo
    ResolveEntryMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveEntryMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveEntryMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveEntryMethod "getChars" o = Gtk.Editable.EditableGetCharsMethodInfo
    ResolveEntryMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveEntryMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveEntryMethod "getCompletion" o = EntryGetCompletionMethodInfo
    ResolveEntryMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveEntryMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveEntryMethod "getCurrentIconDragSource" o = EntryGetCurrentIconDragSourceMethodInfo
    ResolveEntryMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveEntryMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveEntryMethod "getDelegate" o = Gtk.Editable.EditableGetDelegateMethodInfo
    ResolveEntryMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveEntryMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveEntryMethod "getEditable" o = Gtk.Editable.EditableGetEditableMethodInfo
    ResolveEntryMethod "getEnableUndo" o = Gtk.Editable.EditableGetEnableUndoMethodInfo
    ResolveEntryMethod "getExtraMenu" o = EntryGetExtraMenuMethodInfo
    ResolveEntryMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveEntryMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveEntryMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveEntryMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveEntryMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveEntryMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveEntryMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveEntryMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveEntryMethod "getHasFrame" o = EntryGetHasFrameMethodInfo
    ResolveEntryMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveEntryMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveEntryMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveEntryMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveEntryMethod "getIconActivatable" o = EntryGetIconActivatableMethodInfo
    ResolveEntryMethod "getIconArea" o = EntryGetIconAreaMethodInfo
    ResolveEntryMethod "getIconAtPos" o = EntryGetIconAtPosMethodInfo
    ResolveEntryMethod "getIconGicon" o = EntryGetIconGiconMethodInfo
    ResolveEntryMethod "getIconName" o = EntryGetIconNameMethodInfo
    ResolveEntryMethod "getIconPaintable" o = EntryGetIconPaintableMethodInfo
    ResolveEntryMethod "getIconSensitive" o = EntryGetIconSensitiveMethodInfo
    ResolveEntryMethod "getIconStorageType" o = EntryGetIconStorageTypeMethodInfo
    ResolveEntryMethod "getIconTooltipMarkup" o = EntryGetIconTooltipMarkupMethodInfo
    ResolveEntryMethod "getIconTooltipText" o = EntryGetIconTooltipTextMethodInfo
    ResolveEntryMethod "getInputHints" o = EntryGetInputHintsMethodInfo
    ResolveEntryMethod "getInputPurpose" o = EntryGetInputPurposeMethodInfo
    ResolveEntryMethod "getInvisibleChar" o = EntryGetInvisibleCharMethodInfo
    ResolveEntryMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveEntryMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveEntryMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveEntryMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveEntryMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveEntryMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveEntryMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveEntryMethod "getMaxLength" o = EntryGetMaxLengthMethodInfo
    ResolveEntryMethod "getMaxWidthChars" o = Gtk.Editable.EditableGetMaxWidthCharsMethodInfo
    ResolveEntryMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveEntryMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveEntryMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveEntryMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveEntryMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveEntryMethod "getOverwriteMode" o = EntryGetOverwriteModeMethodInfo
    ResolveEntryMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveEntryMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveEntryMethod "getPlaceholderText" o = EntryGetPlaceholderTextMethodInfo
    ResolveEntryMethod "getPosition" o = Gtk.Editable.EditableGetPositionMethodInfo
    ResolveEntryMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveEntryMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveEntryMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveEntryMethod "getProgressFraction" o = EntryGetProgressFractionMethodInfo
    ResolveEntryMethod "getProgressPulseStep" o = EntryGetProgressPulseStepMethodInfo
    ResolveEntryMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveEntryMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveEntryMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveEntryMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveEntryMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveEntryMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveEntryMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveEntryMethod "getSelectionBounds" o = Gtk.Editable.EditableGetSelectionBoundsMethodInfo
    ResolveEntryMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveEntryMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveEntryMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveEntryMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveEntryMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveEntryMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveEntryMethod "getTabs" o = EntryGetTabsMethodInfo
    ResolveEntryMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveEntryMethod "getText" o = Gtk.Editable.EditableGetTextMethodInfo
    ResolveEntryMethod "getTextLength" o = EntryGetTextLengthMethodInfo
    ResolveEntryMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveEntryMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveEntryMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveEntryMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveEntryMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveEntryMethod "getVisibility" o = EntryGetVisibilityMethodInfo
    ResolveEntryMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveEntryMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveEntryMethod "getWidthChars" o = Gtk.Editable.EditableGetWidthCharsMethodInfo
    ResolveEntryMethod "setActivatesDefault" o = EntrySetActivatesDefaultMethodInfo
    ResolveEntryMethod "setAlignment" o = EntrySetAlignmentMethodInfo
    ResolveEntryMethod "setAttributes" o = EntrySetAttributesMethodInfo
    ResolveEntryMethod "setBuffer" o = EntrySetBufferMethodInfo
    ResolveEntryMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveEntryMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveEntryMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveEntryMethod "setCompletion" o = EntrySetCompletionMethodInfo
    ResolveEntryMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveEntryMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveEntryMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveEntryMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveEntryMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveEntryMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveEntryMethod "setEditable" o = Gtk.Editable.EditableSetEditableMethodInfo
    ResolveEntryMethod "setEnableUndo" o = Gtk.Editable.EditableSetEnableUndoMethodInfo
    ResolveEntryMethod "setExtraMenu" o = EntrySetExtraMenuMethodInfo
    ResolveEntryMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveEntryMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveEntryMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveEntryMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveEntryMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveEntryMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveEntryMethod "setHasFrame" o = EntrySetHasFrameMethodInfo
    ResolveEntryMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveEntryMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveEntryMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveEntryMethod "setIconActivatable" o = EntrySetIconActivatableMethodInfo
    ResolveEntryMethod "setIconDragSource" o = EntrySetIconDragSourceMethodInfo
    ResolveEntryMethod "setIconFromGicon" o = EntrySetIconFromGiconMethodInfo
    ResolveEntryMethod "setIconFromIconName" o = EntrySetIconFromIconNameMethodInfo
    ResolveEntryMethod "setIconFromPaintable" o = EntrySetIconFromPaintableMethodInfo
    ResolveEntryMethod "setIconSensitive" o = EntrySetIconSensitiveMethodInfo
    ResolveEntryMethod "setIconTooltipMarkup" o = EntrySetIconTooltipMarkupMethodInfo
    ResolveEntryMethod "setIconTooltipText" o = EntrySetIconTooltipTextMethodInfo
    ResolveEntryMethod "setInputHints" o = EntrySetInputHintsMethodInfo
    ResolveEntryMethod "setInputPurpose" o = EntrySetInputPurposeMethodInfo
    ResolveEntryMethod "setInvisibleChar" o = EntrySetInvisibleCharMethodInfo
    ResolveEntryMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveEntryMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveEntryMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveEntryMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveEntryMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveEntryMethod "setMaxLength" o = EntrySetMaxLengthMethodInfo
    ResolveEntryMethod "setMaxWidthChars" o = Gtk.Editable.EditableSetMaxWidthCharsMethodInfo
    ResolveEntryMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveEntryMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveEntryMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveEntryMethod "setOverwriteMode" o = EntrySetOverwriteModeMethodInfo
    ResolveEntryMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveEntryMethod "setPlaceholderText" o = EntrySetPlaceholderTextMethodInfo
    ResolveEntryMethod "setPosition" o = Gtk.Editable.EditableSetPositionMethodInfo
    ResolveEntryMethod "setProgressFraction" o = EntrySetProgressFractionMethodInfo
    ResolveEntryMethod "setProgressPulseStep" o = EntrySetProgressPulseStepMethodInfo
    ResolveEntryMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveEntryMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveEntryMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveEntryMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveEntryMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveEntryMethod "setTabs" o = EntrySetTabsMethodInfo
    ResolveEntryMethod "setText" o = Gtk.Editable.EditableSetTextMethodInfo
    ResolveEntryMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveEntryMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveEntryMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveEntryMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveEntryMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveEntryMethod "setVisibility" o = EntrySetVisibilityMethodInfo
    ResolveEntryMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveEntryMethod "setWidthChars" o = Gtk.Editable.EditableSetWidthCharsMethodInfo
    ResolveEntryMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEntryMethod t Entry, O.OverloadedMethod info Entry p) => OL.IsLabel t (Entry -> 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 ~ ResolveEntryMethod t Entry, O.OverloadedMethod info Entry p, R.HasField t Entry p) => R.HasField t Entry p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveEntryMethod t Entry, O.OverloadedMethodInfo info Entry) => OL.IsLabel t (O.MethodProxy info Entry) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
type EntryActivateCallback =
    IO ()
noEntryActivateCallback :: Maybe EntryActivateCallback
noEntryActivateCallback :: Maybe (IO ())
noEntryActivateCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_EntryActivateCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_EntryActivateCallback :: C_EntryActivateCallback -> IO (FunPtr C_EntryActivateCallback)
genClosure_EntryActivate :: MonadIO m => EntryActivateCallback -> m (GClosure C_EntryActivateCallback)
genClosure_EntryActivate :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_EntryActivateCallback)
genClosure_EntryActivate IO ()
cb = IO (GClosure C_EntryActivateCallback)
-> m (GClosure C_EntryActivateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_EntryActivateCallback)
 -> m (GClosure C_EntryActivateCallback))
-> IO (GClosure C_EntryActivateCallback)
-> m (GClosure C_EntryActivateCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_EntryActivateCallback
cb' = IO () -> C_EntryActivateCallback
wrap_EntryActivateCallback IO ()
cb
    C_EntryActivateCallback -> IO (FunPtr C_EntryActivateCallback)
mk_EntryActivateCallback C_EntryActivateCallback
cb' IO (FunPtr C_EntryActivateCallback)
-> (FunPtr C_EntryActivateCallback
    -> IO (GClosure C_EntryActivateCallback))
-> IO (GClosure C_EntryActivateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_EntryActivateCallback
-> IO (GClosure C_EntryActivateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_EntryActivateCallback ::
    EntryActivateCallback ->
    C_EntryActivateCallback
wrap_EntryActivateCallback :: IO () -> C_EntryActivateCallback
wrap_EntryActivateCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onEntryActivate :: (IsEntry a, MonadIO m) => a -> EntryActivateCallback -> m SignalHandlerId
onEntryActivate :: forall a (m :: * -> *).
(IsEntry a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onEntryActivate a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EntryActivateCallback
cb' = IO () -> C_EntryActivateCallback
wrap_EntryActivateCallback IO ()
cb
    FunPtr C_EntryActivateCallback
cb'' <- C_EntryActivateCallback -> IO (FunPtr C_EntryActivateCallback)
mk_EntryActivateCallback C_EntryActivateCallback
cb'
    a
-> Text
-> FunPtr C_EntryActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_EntryActivateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterEntryActivate :: (IsEntry a, MonadIO m) => a -> EntryActivateCallback -> m SignalHandlerId
afterEntryActivate :: forall a (m :: * -> *).
(IsEntry a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterEntryActivate a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EntryActivateCallback
cb' = IO () -> C_EntryActivateCallback
wrap_EntryActivateCallback IO ()
cb
    FunPtr C_EntryActivateCallback
cb'' <- C_EntryActivateCallback -> IO (FunPtr C_EntryActivateCallback)
mk_EntryActivateCallback C_EntryActivateCallback
cb'
    a
-> Text
-> FunPtr C_EntryActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_EntryActivateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data EntryActivateSignalInfo
instance SignalInfo EntryActivateSignalInfo where
    type HaskellCallbackType EntryActivateSignalInfo = EntryActivateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_EntryActivateCallback cb
        cb'' <- mk_EntryActivateCallback cb'
        connectSignalFunPtr obj "activate" cb'' connectMode detail
#endif
type EntryIconPressCallback =
    Gtk.Enums.EntryIconPosition
    
    -> IO ()
noEntryIconPressCallback :: Maybe EntryIconPressCallback
noEntryIconPressCallback :: Maybe EntryIconPressCallback
noEntryIconPressCallback = Maybe EntryIconPressCallback
forall a. Maybe a
Nothing
type C_EntryIconPressCallback =
    Ptr () ->                               
    CUInt ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_EntryIconPressCallback :: C_EntryIconPressCallback -> IO (FunPtr C_EntryIconPressCallback)
genClosure_EntryIconPress :: MonadIO m => EntryIconPressCallback -> m (GClosure C_EntryIconPressCallback)
genClosure_EntryIconPress :: forall (m :: * -> *).
MonadIO m =>
EntryIconPressCallback -> m (GClosure C_EntryIconPressCallback)
genClosure_EntryIconPress EntryIconPressCallback
cb = IO (GClosure C_EntryIconPressCallback)
-> m (GClosure C_EntryIconPressCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_EntryIconPressCallback)
 -> m (GClosure C_EntryIconPressCallback))
-> IO (GClosure C_EntryIconPressCallback)
-> m (GClosure C_EntryIconPressCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_EntryIconPressCallback
cb' = EntryIconPressCallback -> C_EntryIconPressCallback
wrap_EntryIconPressCallback EntryIconPressCallback
cb
    C_EntryIconPressCallback -> IO (FunPtr C_EntryIconPressCallback)
mk_EntryIconPressCallback C_EntryIconPressCallback
cb' IO (FunPtr C_EntryIconPressCallback)
-> (FunPtr C_EntryIconPressCallback
    -> IO (GClosure C_EntryIconPressCallback))
-> IO (GClosure C_EntryIconPressCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_EntryIconPressCallback
-> IO (GClosure C_EntryIconPressCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_EntryIconPressCallback ::
    EntryIconPressCallback ->
    C_EntryIconPressCallback
wrap_EntryIconPressCallback :: EntryIconPressCallback -> C_EntryIconPressCallback
wrap_EntryIconPressCallback EntryIconPressCallback
_cb Ptr ()
_ CUInt
iconPos Ptr ()
_ = do
    let iconPos' :: EntryIconPosition
iconPos' = (Int -> EntryIconPosition
forall a. Enum a => Int -> a
toEnum (Int -> EntryIconPosition)
-> (CUInt -> Int) -> CUInt -> EntryIconPosition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
iconPos
    EntryIconPressCallback
_cb  EntryIconPosition
iconPos'
onEntryIconPress :: (IsEntry a, MonadIO m) => a -> EntryIconPressCallback -> m SignalHandlerId
onEntryIconPress :: forall a (m :: * -> *).
(IsEntry a, MonadIO m) =>
a -> EntryIconPressCallback -> m SignalHandlerId
onEntryIconPress a
obj EntryIconPressCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EntryIconPressCallback
cb' = EntryIconPressCallback -> C_EntryIconPressCallback
wrap_EntryIconPressCallback EntryIconPressCallback
cb
    FunPtr C_EntryIconPressCallback
cb'' <- C_EntryIconPressCallback -> IO (FunPtr C_EntryIconPressCallback)
mk_EntryIconPressCallback C_EntryIconPressCallback
cb'
    a
-> Text
-> FunPtr C_EntryIconPressCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"icon-press" FunPtr C_EntryIconPressCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterEntryIconPress :: (IsEntry a, MonadIO m) => a -> EntryIconPressCallback -> m SignalHandlerId
afterEntryIconPress :: forall a (m :: * -> *).
(IsEntry a, MonadIO m) =>
a -> EntryIconPressCallback -> m SignalHandlerId
afterEntryIconPress a
obj EntryIconPressCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EntryIconPressCallback
cb' = EntryIconPressCallback -> C_EntryIconPressCallback
wrap_EntryIconPressCallback EntryIconPressCallback
cb
    FunPtr C_EntryIconPressCallback
cb'' <- C_EntryIconPressCallback -> IO (FunPtr C_EntryIconPressCallback)
mk_EntryIconPressCallback C_EntryIconPressCallback
cb'
    a
-> Text
-> FunPtr C_EntryIconPressCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"icon-press" FunPtr C_EntryIconPressCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data EntryIconPressSignalInfo
instance SignalInfo EntryIconPressSignalInfo where
    type HaskellCallbackType EntryIconPressSignalInfo = EntryIconPressCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_EntryIconPressCallback cb
        cb'' <- mk_EntryIconPressCallback cb'
        connectSignalFunPtr obj "icon-press" cb'' connectMode detail
#endif
type EntryIconReleaseCallback =
    Gtk.Enums.EntryIconPosition
    
    -> IO ()
noEntryIconReleaseCallback :: Maybe EntryIconReleaseCallback
noEntryIconReleaseCallback :: Maybe EntryIconPressCallback
noEntryIconReleaseCallback = Maybe EntryIconPressCallback
forall a. Maybe a
Nothing
type C_EntryIconReleaseCallback =
    Ptr () ->                               
    CUInt ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_EntryIconReleaseCallback :: C_EntryIconReleaseCallback -> IO (FunPtr C_EntryIconReleaseCallback)
genClosure_EntryIconRelease :: MonadIO m => EntryIconReleaseCallback -> m (GClosure C_EntryIconReleaseCallback)
genClosure_EntryIconRelease :: forall (m :: * -> *).
MonadIO m =>
EntryIconPressCallback -> m (GClosure C_EntryIconPressCallback)
genClosure_EntryIconRelease EntryIconPressCallback
cb = IO (GClosure C_EntryIconPressCallback)
-> m (GClosure C_EntryIconPressCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_EntryIconPressCallback)
 -> m (GClosure C_EntryIconPressCallback))
-> IO (GClosure C_EntryIconPressCallback)
-> m (GClosure C_EntryIconPressCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_EntryIconPressCallback
cb' = EntryIconPressCallback -> C_EntryIconPressCallback
wrap_EntryIconReleaseCallback EntryIconPressCallback
cb
    C_EntryIconPressCallback -> IO (FunPtr C_EntryIconPressCallback)
mk_EntryIconReleaseCallback C_EntryIconPressCallback
cb' IO (FunPtr C_EntryIconPressCallback)
-> (FunPtr C_EntryIconPressCallback
    -> IO (GClosure C_EntryIconPressCallback))
-> IO (GClosure C_EntryIconPressCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_EntryIconPressCallback
-> IO (GClosure C_EntryIconPressCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_EntryIconReleaseCallback ::
    EntryIconReleaseCallback ->
    C_EntryIconReleaseCallback
wrap_EntryIconReleaseCallback :: EntryIconPressCallback -> C_EntryIconPressCallback
wrap_EntryIconReleaseCallback EntryIconPressCallback
_cb Ptr ()
_ CUInt
iconPos Ptr ()
_ = do
    let iconPos' :: EntryIconPosition
iconPos' = (Int -> EntryIconPosition
forall a. Enum a => Int -> a
toEnum (Int -> EntryIconPosition)
-> (CUInt -> Int) -> CUInt -> EntryIconPosition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
iconPos
    EntryIconPressCallback
_cb  EntryIconPosition
iconPos'
onEntryIconRelease :: (IsEntry a, MonadIO m) => a -> EntryIconReleaseCallback -> m SignalHandlerId
onEntryIconRelease :: forall a (m :: * -> *).
(IsEntry a, MonadIO m) =>
a -> EntryIconPressCallback -> m SignalHandlerId
onEntryIconRelease a
obj EntryIconPressCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EntryIconPressCallback
cb' = EntryIconPressCallback -> C_EntryIconPressCallback
wrap_EntryIconReleaseCallback EntryIconPressCallback
cb
    FunPtr C_EntryIconPressCallback
cb'' <- C_EntryIconPressCallback -> IO (FunPtr C_EntryIconPressCallback)
mk_EntryIconReleaseCallback C_EntryIconPressCallback
cb'
    a
-> Text
-> FunPtr C_EntryIconPressCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"icon-release" FunPtr C_EntryIconPressCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterEntryIconRelease :: (IsEntry a, MonadIO m) => a -> EntryIconReleaseCallback -> m SignalHandlerId
afterEntryIconRelease :: forall a (m :: * -> *).
(IsEntry a, MonadIO m) =>
a -> EntryIconPressCallback -> m SignalHandlerId
afterEntryIconRelease a
obj EntryIconPressCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EntryIconPressCallback
cb' = EntryIconPressCallback -> C_EntryIconPressCallback
wrap_EntryIconReleaseCallback EntryIconPressCallback
cb
    FunPtr C_EntryIconPressCallback
cb'' <- C_EntryIconPressCallback -> IO (FunPtr C_EntryIconPressCallback)
mk_EntryIconReleaseCallback C_EntryIconPressCallback
cb'
    a
-> Text
-> FunPtr C_EntryIconPressCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"icon-release" FunPtr C_EntryIconPressCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data EntryIconReleaseSignalInfo
instance SignalInfo EntryIconReleaseSignalInfo where
    type HaskellCallbackType EntryIconReleaseSignalInfo = EntryIconReleaseCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_EntryIconReleaseCallback cb
        cb'' <- mk_EntryIconReleaseCallback cb'
        connectSignalFunPtr obj "icon-release" cb'' connectMode detail
#endif
   
   
   
getEntryActivatesDefault :: (MonadIO m, IsEntry o) => o -> m Bool
getEntryActivatesDefault :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntryActivatesDefault o
obj = IO Bool -> m Bool
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
"activates-default"
setEntryActivatesDefault :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryActivatesDefault :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryActivatesDefault o
obj Bool
val = IO () -> m ()
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
"activates-default" Bool
val
constructEntryActivatesDefault :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryActivatesDefault :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryActivatesDefault Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"activates-default" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntryActivatesDefaultPropertyInfo
instance AttrInfo EntryActivatesDefaultPropertyInfo where
    type AttrAllowedOps EntryActivatesDefaultPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryActivatesDefaultPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryActivatesDefaultPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryActivatesDefaultPropertyInfo = (~) Bool
    type AttrTransferType EntryActivatesDefaultPropertyInfo = Bool
    type AttrGetType EntryActivatesDefaultPropertyInfo = Bool
    type AttrLabel EntryActivatesDefaultPropertyInfo = "activates-default"
    type AttrOrigin EntryActivatesDefaultPropertyInfo = Entry
    attrGet = getEntryActivatesDefault
    attrSet = setEntryActivatesDefault
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryActivatesDefault
    attrClear = undefined
#endif
   
   
   
getEntryAttributes :: (MonadIO m, IsEntry o) => o -> m (Maybe Pango.AttrList.AttrList)
getEntryAttributes :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe AttrList)
getEntryAttributes o
obj = IO (Maybe AttrList) -> m (Maybe AttrList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe AttrList) -> m (Maybe AttrList))
-> IO (Maybe AttrList) -> m (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr AttrList -> AttrList)
-> IO (Maybe AttrList)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"attributes" ManagedPtr AttrList -> AttrList
Pango.AttrList.AttrList
setEntryAttributes :: (MonadIO m, IsEntry o) => o -> Pango.AttrList.AttrList -> m ()
setEntryAttributes :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> AttrList -> m ()
setEntryAttributes o
obj AttrList
val = IO () -> m ()
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 AttrList -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"attributes" (AttrList -> Maybe AttrList
forall a. a -> Maybe a
Just AttrList
val)
constructEntryAttributes :: (IsEntry o, MIO.MonadIO m) => Pango.AttrList.AttrList -> m (GValueConstruct o)
constructEntryAttributes :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
AttrList -> m (GValueConstruct o)
constructEntryAttributes AttrList
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 AttrList -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"attributes" (AttrList -> Maybe AttrList
forall a. a -> Maybe a
P.Just AttrList
val)
#if defined(ENABLE_OVERLOADING)
data EntryAttributesPropertyInfo
instance AttrInfo EntryAttributesPropertyInfo where
    type AttrAllowedOps EntryAttributesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryAttributesPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryAttributesPropertyInfo = (~) Pango.AttrList.AttrList
    type AttrTransferTypeConstraint EntryAttributesPropertyInfo = (~) Pango.AttrList.AttrList
    type AttrTransferType EntryAttributesPropertyInfo = Pango.AttrList.AttrList
    type AttrGetType EntryAttributesPropertyInfo = (Maybe Pango.AttrList.AttrList)
    type AttrLabel EntryAttributesPropertyInfo = "attributes"
    type AttrOrigin EntryAttributesPropertyInfo = Entry
    attrGet = getEntryAttributes
    attrSet = setEntryAttributes
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryAttributes
    attrClear = undefined
#endif
   
   
   
getEntryBuffer :: (MonadIO m, IsEntry o) => o -> m Gtk.EntryBuffer.EntryBuffer
getEntryBuffer :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m EntryBuffer
getEntryBuffer o
obj = IO EntryBuffer -> m EntryBuffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO EntryBuffer -> m EntryBuffer)
-> IO EntryBuffer -> m EntryBuffer
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe EntryBuffer) -> IO EntryBuffer
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEntryBuffer" (IO (Maybe EntryBuffer) -> IO EntryBuffer)
-> IO (Maybe EntryBuffer) -> IO EntryBuffer
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr EntryBuffer -> EntryBuffer)
-> IO (Maybe EntryBuffer)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"buffer" ManagedPtr EntryBuffer -> EntryBuffer
Gtk.EntryBuffer.EntryBuffer
setEntryBuffer :: (MonadIO m, IsEntry o, Gtk.EntryBuffer.IsEntryBuffer a) => o -> a -> m ()
setEntryBuffer :: forall (m :: * -> *) o a.
(MonadIO m, IsEntry o, IsEntryBuffer a) =>
o -> a -> m ()
setEntryBuffer o
obj a
val = IO () -> m ()
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
"buffer" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructEntryBuffer :: (IsEntry o, MIO.MonadIO m, Gtk.EntryBuffer.IsEntryBuffer a) => a -> m (GValueConstruct o)
constructEntryBuffer :: forall o (m :: * -> *) a.
(IsEntry o, MonadIO m, IsEntryBuffer a) =>
a -> m (GValueConstruct o)
constructEntryBuffer a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"buffer" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data EntryBufferPropertyInfo
instance AttrInfo EntryBufferPropertyInfo where
    type AttrAllowedOps EntryBufferPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryBufferPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryBufferPropertyInfo = Gtk.EntryBuffer.IsEntryBuffer
    type AttrTransferTypeConstraint EntryBufferPropertyInfo = Gtk.EntryBuffer.IsEntryBuffer
    type AttrTransferType EntryBufferPropertyInfo = Gtk.EntryBuffer.EntryBuffer
    type AttrGetType EntryBufferPropertyInfo = Gtk.EntryBuffer.EntryBuffer
    type AttrLabel EntryBufferPropertyInfo = "buffer"
    type AttrOrigin EntryBufferPropertyInfo = Entry
    attrGet = getEntryBuffer
    attrSet = setEntryBuffer
    attrTransfer _ v = do
        unsafeCastTo Gtk.EntryBuffer.EntryBuffer v
    attrConstruct = constructEntryBuffer
    attrClear = undefined
#endif
   
   
   
getEntryCompletion :: (MonadIO m, IsEntry o) => o -> m (Maybe Gtk.EntryCompletion.EntryCompletion)
getEntryCompletion :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe EntryCompletion)
getEntryCompletion o
obj = IO (Maybe EntryCompletion) -> m (Maybe EntryCompletion)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe EntryCompletion) -> m (Maybe EntryCompletion))
-> IO (Maybe EntryCompletion) -> m (Maybe EntryCompletion)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr EntryCompletion -> EntryCompletion)
-> IO (Maybe EntryCompletion)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"completion" ManagedPtr EntryCompletion -> EntryCompletion
Gtk.EntryCompletion.EntryCompletion
setEntryCompletion :: (MonadIO m, IsEntry o, Gtk.EntryCompletion.IsEntryCompletion a) => o -> a -> m ()
setEntryCompletion :: forall (m :: * -> *) o a.
(MonadIO m, IsEntry o, IsEntryCompletion a) =>
o -> a -> m ()
setEntryCompletion o
obj a
val = IO () -> m ()
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
"completion" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructEntryCompletion :: (IsEntry o, MIO.MonadIO m, Gtk.EntryCompletion.IsEntryCompletion a) => a -> m (GValueConstruct o)
constructEntryCompletion :: forall o (m :: * -> *) a.
(IsEntry o, MonadIO m, IsEntryCompletion a) =>
a -> m (GValueConstruct o)
constructEntryCompletion a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"completion" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearEntryCompletion :: (MonadIO m, IsEntry o) => o -> m ()
clearEntryCompletion :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntryCompletion o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe EntryCompletion -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"completion" (Maybe EntryCompletion
forall a. Maybe a
Nothing :: Maybe Gtk.EntryCompletion.EntryCompletion)
#if defined(ENABLE_OVERLOADING)
data EntryCompletionPropertyInfo
instance AttrInfo EntryCompletionPropertyInfo where
    type AttrAllowedOps EntryCompletionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryCompletionPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryCompletionPropertyInfo = Gtk.EntryCompletion.IsEntryCompletion
    type AttrTransferTypeConstraint EntryCompletionPropertyInfo = Gtk.EntryCompletion.IsEntryCompletion
    type AttrTransferType EntryCompletionPropertyInfo = Gtk.EntryCompletion.EntryCompletion
    type AttrGetType EntryCompletionPropertyInfo = (Maybe Gtk.EntryCompletion.EntryCompletion)
    type AttrLabel EntryCompletionPropertyInfo = "completion"
    type AttrOrigin EntryCompletionPropertyInfo = Entry
    attrGet = getEntryCompletion
    attrSet = setEntryCompletion
    attrTransfer _ v = do
        unsafeCastTo Gtk.EntryCompletion.EntryCompletion v
    attrConstruct = constructEntryCompletion
    attrClear = clearEntryCompletion
#endif
   
   
   
getEntryEnableEmojiCompletion :: (MonadIO m, IsEntry o) => o -> m Bool
getEntryEnableEmojiCompletion :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntryEnableEmojiCompletion o
obj = IO Bool -> m Bool
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
"enable-emoji-completion"
setEntryEnableEmojiCompletion :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryEnableEmojiCompletion :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryEnableEmojiCompletion o
obj Bool
val = IO () -> m ()
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
"enable-emoji-completion" Bool
val
constructEntryEnableEmojiCompletion :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryEnableEmojiCompletion :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryEnableEmojiCompletion Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"enable-emoji-completion" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntryEnableEmojiCompletionPropertyInfo
instance AttrInfo EntryEnableEmojiCompletionPropertyInfo where
    type AttrAllowedOps EntryEnableEmojiCompletionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryEnableEmojiCompletionPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryEnableEmojiCompletionPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryEnableEmojiCompletionPropertyInfo = (~) Bool
    type AttrTransferType EntryEnableEmojiCompletionPropertyInfo = Bool
    type AttrGetType EntryEnableEmojiCompletionPropertyInfo = Bool
    type AttrLabel EntryEnableEmojiCompletionPropertyInfo = "enable-emoji-completion"
    type AttrOrigin EntryEnableEmojiCompletionPropertyInfo = Entry
    attrGet = getEntryEnableEmojiCompletion
    attrSet = setEntryEnableEmojiCompletion
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryEnableEmojiCompletion
    attrClear = undefined
#endif
   
   
   
getEntryExtraMenu :: (MonadIO m, IsEntry o) => o -> m (Maybe Gio.MenuModel.MenuModel)
 o
obj = IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe MenuModel) -> m (Maybe MenuModel))
-> IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr MenuModel -> MenuModel)
-> IO (Maybe MenuModel)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"extra-menu" ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel
setEntryExtraMenu :: (MonadIO m, IsEntry o, Gio.MenuModel.IsMenuModel a) => o -> a -> m ()
 o
obj a
val = IO () -> m ()
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
"extra-menu" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructEntryExtraMenu :: (IsEntry o, MIO.MonadIO m, Gio.MenuModel.IsMenuModel a) => a -> m (GValueConstruct o)
 a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"extra-menu" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearEntryExtraMenu :: (MonadIO m, IsEntry o) => o -> m ()
 o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe MenuModel -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"extra-menu" (Maybe MenuModel
forall a. Maybe a
Nothing :: Maybe Gio.MenuModel.MenuModel)
#if defined(ENABLE_OVERLOADING)
data EntryExtraMenuPropertyInfo
instance AttrInfo EntryExtraMenuPropertyInfo where
    type AttrAllowedOps EntryExtraMenuPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryExtraMenuPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryExtraMenuPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferTypeConstraint EntryExtraMenuPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferType EntryExtraMenuPropertyInfo = Gio.MenuModel.MenuModel
    type AttrGetType EntryExtraMenuPropertyInfo = (Maybe Gio.MenuModel.MenuModel)
    type AttrLabel EntryExtraMenuPropertyInfo = "extra-menu"
    type AttrOrigin EntryExtraMenuPropertyInfo = Entry
    attrGet = getEntryExtraMenu
    attrSet = setEntryExtraMenu
    attrTransfer _ v = do
        unsafeCastTo Gio.MenuModel.MenuModel v
    attrConstruct = constructEntryExtraMenu
    attrClear = clearEntryExtraMenu
#endif
   
   
   
getEntryHasFrame :: (MonadIO m, IsEntry o) => o -> m Bool
getEntryHasFrame :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntryHasFrame o
obj = IO Bool -> m Bool
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
"has-frame"
setEntryHasFrame :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryHasFrame :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryHasFrame o
obj Bool
val = IO () -> m ()
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
"has-frame" Bool
val
constructEntryHasFrame :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryHasFrame :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryHasFrame Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"has-frame" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntryHasFramePropertyInfo
instance AttrInfo EntryHasFramePropertyInfo where
    type AttrAllowedOps EntryHasFramePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryHasFramePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryHasFramePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryHasFramePropertyInfo = (~) Bool
    type AttrTransferType EntryHasFramePropertyInfo = Bool
    type AttrGetType EntryHasFramePropertyInfo = Bool
    type AttrLabel EntryHasFramePropertyInfo = "has-frame"
    type AttrOrigin EntryHasFramePropertyInfo = Entry
    attrGet = getEntryHasFrame
    attrSet = setEntryHasFrame
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryHasFrame
    attrClear = undefined
#endif
   
   
   
getEntryImModule :: (MonadIO m, IsEntry o) => o -> m (Maybe T.Text)
getEntryImModule :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Text)
getEntryImModule o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"im-module"
setEntryImModule :: (MonadIO m, IsEntry o) => o -> T.Text -> m ()
setEntryImModule :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Text -> m ()
setEntryImModule o
obj Text
val = IO () -> m ()
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"im-module" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructEntryImModule :: (IsEntry o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEntryImModule :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEntryImModule Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"im-module" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearEntryImModule :: (MonadIO m, IsEntry o) => o -> m ()
clearEntryImModule :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntryImModule o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"im-module" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data EntryImModulePropertyInfo
instance AttrInfo EntryImModulePropertyInfo where
    type AttrAllowedOps EntryImModulePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryImModulePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryImModulePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EntryImModulePropertyInfo = (~) T.Text
    type AttrTransferType EntryImModulePropertyInfo = T.Text
    type AttrGetType EntryImModulePropertyInfo = (Maybe T.Text)
    type AttrLabel EntryImModulePropertyInfo = "im-module"
    type AttrOrigin EntryImModulePropertyInfo = Entry
    attrGet = getEntryImModule
    attrSet = setEntryImModule
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryImModule
    attrClear = clearEntryImModule
#endif
   
   
   
getEntryInputHints :: (MonadIO m, IsEntry o) => o -> m [Gtk.Flags.InputHints]
getEntryInputHints :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m [InputHints]
getEntryInputHints o
obj = IO [InputHints] -> m [InputHints]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [InputHints] -> m [InputHints])
-> IO [InputHints] -> m [InputHints]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [InputHints]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"input-hints"
setEntryInputHints :: (MonadIO m, IsEntry o) => o -> [Gtk.Flags.InputHints] -> m ()
setEntryInputHints :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> [InputHints] -> m ()
setEntryInputHints o
obj [InputHints]
val = IO () -> m ()
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 -> [InputHints] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"input-hints" [InputHints]
val
constructEntryInputHints :: (IsEntry o, MIO.MonadIO m) => [Gtk.Flags.InputHints] -> m (GValueConstruct o)
constructEntryInputHints :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
[InputHints] -> m (GValueConstruct o)
constructEntryInputHints [InputHints]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> [InputHints] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"input-hints" [InputHints]
val
#if defined(ENABLE_OVERLOADING)
data EntryInputHintsPropertyInfo
instance AttrInfo EntryInputHintsPropertyInfo where
    type AttrAllowedOps EntryInputHintsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryInputHintsPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryInputHintsPropertyInfo = (~) [Gtk.Flags.InputHints]
    type AttrTransferTypeConstraint EntryInputHintsPropertyInfo = (~) [Gtk.Flags.InputHints]
    type AttrTransferType EntryInputHintsPropertyInfo = [Gtk.Flags.InputHints]
    type AttrGetType EntryInputHintsPropertyInfo = [Gtk.Flags.InputHints]
    type AttrLabel EntryInputHintsPropertyInfo = "input-hints"
    type AttrOrigin EntryInputHintsPropertyInfo = Entry
    attrGet = getEntryInputHints
    attrSet = setEntryInputHints
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryInputHints
    attrClear = undefined
#endif
   
   
   
getEntryInputPurpose :: (MonadIO m, IsEntry o) => o -> m Gtk.Enums.InputPurpose
getEntryInputPurpose :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m InputPurpose
getEntryInputPurpose o
obj = IO InputPurpose -> m InputPurpose
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO InputPurpose -> m InputPurpose)
-> IO InputPurpose -> m InputPurpose
forall a b. (a -> b) -> a -> b
$ o -> String -> IO InputPurpose
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"input-purpose"
setEntryInputPurpose :: (MonadIO m, IsEntry o) => o -> Gtk.Enums.InputPurpose -> m ()
setEntryInputPurpose :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> InputPurpose -> m ()
setEntryInputPurpose o
obj InputPurpose
val = IO () -> m ()
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 -> InputPurpose -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"input-purpose" InputPurpose
val
constructEntryInputPurpose :: (IsEntry o, MIO.MonadIO m) => Gtk.Enums.InputPurpose -> m (GValueConstruct o)
constructEntryInputPurpose :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
InputPurpose -> m (GValueConstruct o)
constructEntryInputPurpose InputPurpose
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> InputPurpose -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"input-purpose" InputPurpose
val
#if defined(ENABLE_OVERLOADING)
data EntryInputPurposePropertyInfo
instance AttrInfo EntryInputPurposePropertyInfo where
    type AttrAllowedOps EntryInputPurposePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryInputPurposePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryInputPurposePropertyInfo = (~) Gtk.Enums.InputPurpose
    type AttrTransferTypeConstraint EntryInputPurposePropertyInfo = (~) Gtk.Enums.InputPurpose
    type AttrTransferType EntryInputPurposePropertyInfo = Gtk.Enums.InputPurpose
    type AttrGetType EntryInputPurposePropertyInfo = Gtk.Enums.InputPurpose
    type AttrLabel EntryInputPurposePropertyInfo = "input-purpose"
    type AttrOrigin EntryInputPurposePropertyInfo = Entry
    attrGet = getEntryInputPurpose
    attrSet = setEntryInputPurpose
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryInputPurpose
    attrClear = undefined
#endif
   
   
   
getEntryInvisibleChar :: (MonadIO m, IsEntry o) => o -> m Word32
getEntryInvisibleChar :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Word32
getEntryInvisibleChar o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"invisible-char"
setEntryInvisibleChar :: (MonadIO m, IsEntry o) => o -> Word32 -> m ()
setEntryInvisibleChar :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> Word32 -> m ()
setEntryInvisibleChar o
obj Word32
val = IO () -> m ()
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"invisible-char" Word32
val
constructEntryInvisibleChar :: (IsEntry o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructEntryInvisibleChar :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructEntryInvisibleChar Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"invisible-char" Word32
val
#if defined(ENABLE_OVERLOADING)
data EntryInvisibleCharPropertyInfo
instance AttrInfo EntryInvisibleCharPropertyInfo where
    type AttrAllowedOps EntryInvisibleCharPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryInvisibleCharPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryInvisibleCharPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint EntryInvisibleCharPropertyInfo = (~) Word32
    type AttrTransferType EntryInvisibleCharPropertyInfo = Word32
    type AttrGetType EntryInvisibleCharPropertyInfo = Word32
    type AttrLabel EntryInvisibleCharPropertyInfo = "invisible-char"
    type AttrOrigin EntryInvisibleCharPropertyInfo = Entry
    attrGet = getEntryInvisibleChar
    attrSet = setEntryInvisibleChar
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryInvisibleChar
    attrClear = undefined
#endif
   
   
   
getEntryInvisibleCharSet :: (MonadIO m, IsEntry o) => o -> m Bool
getEntryInvisibleCharSet :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntryInvisibleCharSet o
obj = IO Bool -> m Bool
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
"invisible-char-set"
setEntryInvisibleCharSet :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryInvisibleCharSet :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryInvisibleCharSet o
obj Bool
val = IO () -> m ()
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
"invisible-char-set" Bool
val
constructEntryInvisibleCharSet :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryInvisibleCharSet :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryInvisibleCharSet Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"invisible-char-set" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntryInvisibleCharSetPropertyInfo
instance AttrInfo EntryInvisibleCharSetPropertyInfo where
    type AttrAllowedOps EntryInvisibleCharSetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryInvisibleCharSetPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryInvisibleCharSetPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryInvisibleCharSetPropertyInfo = (~) Bool
    type AttrTransferType EntryInvisibleCharSetPropertyInfo = Bool
    type AttrGetType EntryInvisibleCharSetPropertyInfo = Bool
    type AttrLabel EntryInvisibleCharSetPropertyInfo = "invisible-char-set"
    type AttrOrigin EntryInvisibleCharSetPropertyInfo = Entry
    attrGet = getEntryInvisibleCharSet
    attrSet = setEntryInvisibleCharSet
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryInvisibleCharSet
    attrClear = undefined
#endif
   
   
   
getEntryMaxLength :: (MonadIO m, IsEntry o) => o -> m Int32
getEntryMaxLength :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Int32
getEntryMaxLength o
obj = IO Int32 -> m Int32
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
"max-length"
setEntryMaxLength :: (MonadIO m, IsEntry o) => o -> Int32 -> m ()
setEntryMaxLength :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> Int32 -> m ()
setEntryMaxLength o
obj Int32
val = IO () -> m ()
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
"max-length" Int32
val
constructEntryMaxLength :: (IsEntry o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructEntryMaxLength :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructEntryMaxLength Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"max-length" Int32
val
#if defined(ENABLE_OVERLOADING)
data EntryMaxLengthPropertyInfo
instance AttrInfo EntryMaxLengthPropertyInfo where
    type AttrAllowedOps EntryMaxLengthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryMaxLengthPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryMaxLengthPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint EntryMaxLengthPropertyInfo = (~) Int32
    type AttrTransferType EntryMaxLengthPropertyInfo = Int32
    type AttrGetType EntryMaxLengthPropertyInfo = Int32
    type AttrLabel EntryMaxLengthPropertyInfo = "max-length"
    type AttrOrigin EntryMaxLengthPropertyInfo = Entry
    attrGet = getEntryMaxLength
    attrSet = setEntryMaxLength
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryMaxLength
    attrClear = undefined
#endif
   
   
   
getEntryOverwriteMode :: (MonadIO m, IsEntry o) => o -> m Bool
getEntryOverwriteMode :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntryOverwriteMode o
obj = IO Bool -> m Bool
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
"overwrite-mode"
setEntryOverwriteMode :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryOverwriteMode :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryOverwriteMode o
obj Bool
val = IO () -> m ()
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
"overwrite-mode" Bool
val
constructEntryOverwriteMode :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryOverwriteMode :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryOverwriteMode Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"overwrite-mode" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntryOverwriteModePropertyInfo
instance AttrInfo EntryOverwriteModePropertyInfo where
    type AttrAllowedOps EntryOverwriteModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryOverwriteModePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryOverwriteModePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryOverwriteModePropertyInfo = (~) Bool
    type AttrTransferType EntryOverwriteModePropertyInfo = Bool
    type AttrGetType EntryOverwriteModePropertyInfo = Bool
    type AttrLabel EntryOverwriteModePropertyInfo = "overwrite-mode"
    type AttrOrigin EntryOverwriteModePropertyInfo = Entry
    attrGet = getEntryOverwriteMode
    attrSet = setEntryOverwriteMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryOverwriteMode
    attrClear = undefined
#endif
   
   
   
getEntryPlaceholderText :: (MonadIO m, IsEntry o) => o -> m (Maybe T.Text)
getEntryPlaceholderText :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Text)
getEntryPlaceholderText o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"placeholder-text"
setEntryPlaceholderText :: (MonadIO m, IsEntry o) => o -> T.Text -> m ()
setEntryPlaceholderText :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Text -> m ()
setEntryPlaceholderText o
obj Text
val = IO () -> m ()
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"placeholder-text" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructEntryPlaceholderText :: (IsEntry o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEntryPlaceholderText :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEntryPlaceholderText Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"placeholder-text" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearEntryPlaceholderText :: (MonadIO m, IsEntry o) => o -> m ()
clearEntryPlaceholderText :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntryPlaceholderText o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"placeholder-text" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data EntryPlaceholderTextPropertyInfo
instance AttrInfo EntryPlaceholderTextPropertyInfo where
    type AttrAllowedOps EntryPlaceholderTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryPlaceholderTextPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryPlaceholderTextPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EntryPlaceholderTextPropertyInfo = (~) T.Text
    type AttrTransferType EntryPlaceholderTextPropertyInfo = T.Text
    type AttrGetType EntryPlaceholderTextPropertyInfo = (Maybe T.Text)
    type AttrLabel EntryPlaceholderTextPropertyInfo = "placeholder-text"
    type AttrOrigin EntryPlaceholderTextPropertyInfo = Entry
    attrGet = getEntryPlaceholderText
    attrSet = setEntryPlaceholderText
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryPlaceholderText
    attrClear = clearEntryPlaceholderText
#endif
   
   
   
getEntryPrimaryIconActivatable :: (MonadIO m, IsEntry o) => o -> m Bool
getEntryPrimaryIconActivatable :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntryPrimaryIconActivatable o
obj = IO Bool -> m Bool
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
"primary-icon-activatable"
setEntryPrimaryIconActivatable :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryPrimaryIconActivatable :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryPrimaryIconActivatable o
obj Bool
val = IO () -> m ()
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
"primary-icon-activatable" Bool
val
constructEntryPrimaryIconActivatable :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryPrimaryIconActivatable :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryPrimaryIconActivatable Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"primary-icon-activatable" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntryPrimaryIconActivatablePropertyInfo
instance AttrInfo EntryPrimaryIconActivatablePropertyInfo where
    type AttrAllowedOps EntryPrimaryIconActivatablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryPrimaryIconActivatablePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryPrimaryIconActivatablePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryPrimaryIconActivatablePropertyInfo = (~) Bool
    type AttrTransferType EntryPrimaryIconActivatablePropertyInfo = Bool
    type AttrGetType EntryPrimaryIconActivatablePropertyInfo = Bool
    type AttrLabel EntryPrimaryIconActivatablePropertyInfo = "primary-icon-activatable"
    type AttrOrigin EntryPrimaryIconActivatablePropertyInfo = Entry
    attrGet = getEntryPrimaryIconActivatable
    attrSet = setEntryPrimaryIconActivatable
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryPrimaryIconActivatable
    attrClear = undefined
#endif
   
   
   
getEntryPrimaryIconGicon :: (MonadIO m, IsEntry o) => o -> m (Maybe Gio.Icon.Icon)
getEntryPrimaryIconGicon :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Icon)
getEntryPrimaryIconGicon o
obj = IO (Maybe Icon) -> m (Maybe Icon)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Icon) -> m (Maybe Icon))
-> IO (Maybe Icon) -> m (Maybe Icon)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Icon -> Icon) -> IO (Maybe Icon)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"primary-icon-gicon" ManagedPtr Icon -> Icon
Gio.Icon.Icon
setEntryPrimaryIconGicon :: (MonadIO m, IsEntry o, Gio.Icon.IsIcon a) => o -> a -> m ()
setEntryPrimaryIconGicon :: forall (m :: * -> *) o a.
(MonadIO m, IsEntry o, IsIcon a) =>
o -> a -> m ()
setEntryPrimaryIconGicon o
obj a
val = IO () -> m ()
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
"primary-icon-gicon" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructEntryPrimaryIconGicon :: (IsEntry o, MIO.MonadIO m, Gio.Icon.IsIcon a) => a -> m (GValueConstruct o)
constructEntryPrimaryIconGicon :: forall o (m :: * -> *) a.
(IsEntry o, MonadIO m, IsIcon a) =>
a -> m (GValueConstruct o)
constructEntryPrimaryIconGicon a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"primary-icon-gicon" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearEntryPrimaryIconGicon :: (MonadIO m, IsEntry o) => o -> m ()
clearEntryPrimaryIconGicon :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntryPrimaryIconGicon o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Icon -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"primary-icon-gicon" (Maybe Icon
forall a. Maybe a
Nothing :: Maybe Gio.Icon.Icon)
#if defined(ENABLE_OVERLOADING)
data EntryPrimaryIconGiconPropertyInfo
instance AttrInfo EntryPrimaryIconGiconPropertyInfo where
    type AttrAllowedOps EntryPrimaryIconGiconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryPrimaryIconGiconPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryPrimaryIconGiconPropertyInfo = Gio.Icon.IsIcon
    type AttrTransferTypeConstraint EntryPrimaryIconGiconPropertyInfo = Gio.Icon.IsIcon
    type AttrTransferType EntryPrimaryIconGiconPropertyInfo = Gio.Icon.Icon
    type AttrGetType EntryPrimaryIconGiconPropertyInfo = (Maybe Gio.Icon.Icon)
    type AttrLabel EntryPrimaryIconGiconPropertyInfo = "primary-icon-gicon"
    type AttrOrigin EntryPrimaryIconGiconPropertyInfo = Entry
    attrGet = getEntryPrimaryIconGicon
    attrSet = setEntryPrimaryIconGicon
    attrTransfer _ v = do
        unsafeCastTo Gio.Icon.Icon v
    attrConstruct = constructEntryPrimaryIconGicon
    attrClear = clearEntryPrimaryIconGicon
#endif
   
   
   
getEntryPrimaryIconName :: (MonadIO m, IsEntry o) => o -> m (Maybe T.Text)
getEntryPrimaryIconName :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Text)
getEntryPrimaryIconName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"primary-icon-name"
setEntryPrimaryIconName :: (MonadIO m, IsEntry o) => o -> T.Text -> m ()
setEntryPrimaryIconName :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Text -> m ()
setEntryPrimaryIconName o
obj Text
val = IO () -> m ()
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"primary-icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructEntryPrimaryIconName :: (IsEntry o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEntryPrimaryIconName :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEntryPrimaryIconName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"primary-icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearEntryPrimaryIconName :: (MonadIO m, IsEntry o) => o -> m ()
clearEntryPrimaryIconName :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntryPrimaryIconName o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"primary-icon-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data EntryPrimaryIconNamePropertyInfo
instance AttrInfo EntryPrimaryIconNamePropertyInfo where
    type AttrAllowedOps EntryPrimaryIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryPrimaryIconNamePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryPrimaryIconNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EntryPrimaryIconNamePropertyInfo = (~) T.Text
    type AttrTransferType EntryPrimaryIconNamePropertyInfo = T.Text
    type AttrGetType EntryPrimaryIconNamePropertyInfo = (Maybe T.Text)
    type AttrLabel EntryPrimaryIconNamePropertyInfo = "primary-icon-name"
    type AttrOrigin EntryPrimaryIconNamePropertyInfo = Entry
    attrGet = getEntryPrimaryIconName
    attrSet = setEntryPrimaryIconName
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryPrimaryIconName
    attrClear = clearEntryPrimaryIconName
#endif
   
   
   
getEntryPrimaryIconPaintable :: (MonadIO m, IsEntry o) => o -> m (Maybe Gdk.Paintable.Paintable)
getEntryPrimaryIconPaintable :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Paintable)
getEntryPrimaryIconPaintable o
obj = IO (Maybe Paintable) -> m (Maybe Paintable)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Paintable) -> m (Maybe Paintable))
-> IO (Maybe Paintable) -> m (Maybe Paintable)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Paintable -> Paintable)
-> IO (Maybe Paintable)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"primary-icon-paintable" ManagedPtr Paintable -> Paintable
Gdk.Paintable.Paintable
setEntryPrimaryIconPaintable :: (MonadIO m, IsEntry o, Gdk.Paintable.IsPaintable a) => o -> a -> m ()
setEntryPrimaryIconPaintable :: forall (m :: * -> *) o a.
(MonadIO m, IsEntry o, IsPaintable a) =>
o -> a -> m ()
setEntryPrimaryIconPaintable o
obj a
val = IO () -> m ()
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
"primary-icon-paintable" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructEntryPrimaryIconPaintable :: (IsEntry o, MIO.MonadIO m, Gdk.Paintable.IsPaintable a) => a -> m (GValueConstruct o)
constructEntryPrimaryIconPaintable :: forall o (m :: * -> *) a.
(IsEntry o, MonadIO m, IsPaintable a) =>
a -> m (GValueConstruct o)
constructEntryPrimaryIconPaintable a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"primary-icon-paintable" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearEntryPrimaryIconPaintable :: (MonadIO m, IsEntry o) => o -> m ()
clearEntryPrimaryIconPaintable :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntryPrimaryIconPaintable o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Paintable -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"primary-icon-paintable" (Maybe Paintable
forall a. Maybe a
Nothing :: Maybe Gdk.Paintable.Paintable)
#if defined(ENABLE_OVERLOADING)
data EntryPrimaryIconPaintablePropertyInfo
instance AttrInfo EntryPrimaryIconPaintablePropertyInfo where
    type AttrAllowedOps EntryPrimaryIconPaintablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryPrimaryIconPaintablePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryPrimaryIconPaintablePropertyInfo = Gdk.Paintable.IsPaintable
    type AttrTransferTypeConstraint EntryPrimaryIconPaintablePropertyInfo = Gdk.Paintable.IsPaintable
    type AttrTransferType EntryPrimaryIconPaintablePropertyInfo = Gdk.Paintable.Paintable
    type AttrGetType EntryPrimaryIconPaintablePropertyInfo = (Maybe Gdk.Paintable.Paintable)
    type AttrLabel EntryPrimaryIconPaintablePropertyInfo = "primary-icon-paintable"
    type AttrOrigin EntryPrimaryIconPaintablePropertyInfo = Entry
    attrGet = getEntryPrimaryIconPaintable
    attrSet = setEntryPrimaryIconPaintable
    attrTransfer _ v = do
        unsafeCastTo Gdk.Paintable.Paintable v
    attrConstruct = constructEntryPrimaryIconPaintable
    attrClear = clearEntryPrimaryIconPaintable
#endif
   
   
   
getEntryPrimaryIconSensitive :: (MonadIO m, IsEntry o) => o -> m Bool
getEntryPrimaryIconSensitive :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntryPrimaryIconSensitive o
obj = IO Bool -> m Bool
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
"primary-icon-sensitive"
setEntryPrimaryIconSensitive :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryPrimaryIconSensitive :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryPrimaryIconSensitive o
obj Bool
val = IO () -> m ()
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
"primary-icon-sensitive" Bool
val
constructEntryPrimaryIconSensitive :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryPrimaryIconSensitive :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryPrimaryIconSensitive Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"primary-icon-sensitive" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntryPrimaryIconSensitivePropertyInfo
instance AttrInfo EntryPrimaryIconSensitivePropertyInfo where
    type AttrAllowedOps EntryPrimaryIconSensitivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryPrimaryIconSensitivePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryPrimaryIconSensitivePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryPrimaryIconSensitivePropertyInfo = (~) Bool
    type AttrTransferType EntryPrimaryIconSensitivePropertyInfo = Bool
    type AttrGetType EntryPrimaryIconSensitivePropertyInfo = Bool
    type AttrLabel EntryPrimaryIconSensitivePropertyInfo = "primary-icon-sensitive"
    type AttrOrigin EntryPrimaryIconSensitivePropertyInfo = Entry
    attrGet = getEntryPrimaryIconSensitive
    attrSet = setEntryPrimaryIconSensitive
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryPrimaryIconSensitive
    attrClear = undefined
#endif
   
   
   
getEntryPrimaryIconStorageType :: (MonadIO m, IsEntry o) => o -> m Gtk.Enums.ImageType
getEntryPrimaryIconStorageType :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ImageType
getEntryPrimaryIconStorageType o
obj = IO ImageType -> m ImageType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ImageType -> m ImageType) -> IO ImageType -> m ImageType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO ImageType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"primary-icon-storage-type"
#if defined(ENABLE_OVERLOADING)
data EntryPrimaryIconStorageTypePropertyInfo
instance AttrInfo EntryPrimaryIconStorageTypePropertyInfo where
    type AttrAllowedOps EntryPrimaryIconStorageTypePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint EntryPrimaryIconStorageTypePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryPrimaryIconStorageTypePropertyInfo = (~) ()
    type AttrTransferTypeConstraint EntryPrimaryIconStorageTypePropertyInfo = (~) ()
    type AttrTransferType EntryPrimaryIconStorageTypePropertyInfo = ()
    type AttrGetType EntryPrimaryIconStorageTypePropertyInfo = Gtk.Enums.ImageType
    type AttrLabel EntryPrimaryIconStorageTypePropertyInfo = "primary-icon-storage-type"
    type AttrOrigin EntryPrimaryIconStorageTypePropertyInfo = Entry
    attrGet = getEntryPrimaryIconStorageType
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif
   
   
   
getEntryPrimaryIconTooltipMarkup :: (MonadIO m, IsEntry o) => o -> m (Maybe T.Text)
getEntryPrimaryIconTooltipMarkup :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Text)
getEntryPrimaryIconTooltipMarkup o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"primary-icon-tooltip-markup"
setEntryPrimaryIconTooltipMarkup :: (MonadIO m, IsEntry o) => o -> T.Text -> m ()
setEntryPrimaryIconTooltipMarkup :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Text -> m ()
setEntryPrimaryIconTooltipMarkup o
obj Text
val = IO () -> m ()
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"primary-icon-tooltip-markup" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructEntryPrimaryIconTooltipMarkup :: (IsEntry o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEntryPrimaryIconTooltipMarkup :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEntryPrimaryIconTooltipMarkup Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"primary-icon-tooltip-markup" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearEntryPrimaryIconTooltipMarkup :: (MonadIO m, IsEntry o) => o -> m ()
clearEntryPrimaryIconTooltipMarkup :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntryPrimaryIconTooltipMarkup o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"primary-icon-tooltip-markup" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data EntryPrimaryIconTooltipMarkupPropertyInfo
instance AttrInfo EntryPrimaryIconTooltipMarkupPropertyInfo where
    type AttrAllowedOps EntryPrimaryIconTooltipMarkupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryPrimaryIconTooltipMarkupPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryPrimaryIconTooltipMarkupPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EntryPrimaryIconTooltipMarkupPropertyInfo = (~) T.Text
    type AttrTransferType EntryPrimaryIconTooltipMarkupPropertyInfo = T.Text
    type AttrGetType EntryPrimaryIconTooltipMarkupPropertyInfo = (Maybe T.Text)
    type AttrLabel EntryPrimaryIconTooltipMarkupPropertyInfo = "primary-icon-tooltip-markup"
    type AttrOrigin EntryPrimaryIconTooltipMarkupPropertyInfo = Entry
    attrGet = getEntryPrimaryIconTooltipMarkup
    attrSet = setEntryPrimaryIconTooltipMarkup
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryPrimaryIconTooltipMarkup
    attrClear = clearEntryPrimaryIconTooltipMarkup
#endif
   
   
   
getEntryPrimaryIconTooltipText :: (MonadIO m, IsEntry o) => o -> m (Maybe T.Text)
getEntryPrimaryIconTooltipText :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Text)
getEntryPrimaryIconTooltipText o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"primary-icon-tooltip-text"
setEntryPrimaryIconTooltipText :: (MonadIO m, IsEntry o) => o -> T.Text -> m ()
setEntryPrimaryIconTooltipText :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Text -> m ()
setEntryPrimaryIconTooltipText o
obj Text
val = IO () -> m ()
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"primary-icon-tooltip-text" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructEntryPrimaryIconTooltipText :: (IsEntry o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEntryPrimaryIconTooltipText :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEntryPrimaryIconTooltipText Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"primary-icon-tooltip-text" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearEntryPrimaryIconTooltipText :: (MonadIO m, IsEntry o) => o -> m ()
clearEntryPrimaryIconTooltipText :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntryPrimaryIconTooltipText o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"primary-icon-tooltip-text" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data EntryPrimaryIconTooltipTextPropertyInfo
instance AttrInfo EntryPrimaryIconTooltipTextPropertyInfo where
    type AttrAllowedOps EntryPrimaryIconTooltipTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryPrimaryIconTooltipTextPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryPrimaryIconTooltipTextPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EntryPrimaryIconTooltipTextPropertyInfo = (~) T.Text
    type AttrTransferType EntryPrimaryIconTooltipTextPropertyInfo = T.Text
    type AttrGetType EntryPrimaryIconTooltipTextPropertyInfo = (Maybe T.Text)
    type AttrLabel EntryPrimaryIconTooltipTextPropertyInfo = "primary-icon-tooltip-text"
    type AttrOrigin EntryPrimaryIconTooltipTextPropertyInfo = Entry
    attrGet = getEntryPrimaryIconTooltipText
    attrSet = setEntryPrimaryIconTooltipText
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryPrimaryIconTooltipText
    attrClear = clearEntryPrimaryIconTooltipText
#endif
   
   
   
getEntryProgressFraction :: (MonadIO m, IsEntry o) => o -> m Double
getEntryProgressFraction :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Double
getEntryProgressFraction o
obj = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Double
forall a. GObject a => a -> String -> IO Double
B.Properties.getObjectPropertyDouble o
obj String
"progress-fraction"
setEntryProgressFraction :: (MonadIO m, IsEntry o) => o -> Double -> m ()
setEntryProgressFraction :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> Double -> m ()
setEntryProgressFraction o
obj Double
val = IO () -> m ()
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 -> Double -> IO ()
forall a. GObject a => a -> String -> Double -> IO ()
B.Properties.setObjectPropertyDouble o
obj String
"progress-fraction" Double
val
constructEntryProgressFraction :: (IsEntry o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructEntryProgressFraction :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructEntryProgressFraction Double
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Double -> IO (GValueConstruct o)
forall o. String -> Double -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyDouble String
"progress-fraction" Double
val
#if defined(ENABLE_OVERLOADING)
data EntryProgressFractionPropertyInfo
instance AttrInfo EntryProgressFractionPropertyInfo where
    type AttrAllowedOps EntryProgressFractionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryProgressFractionPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryProgressFractionPropertyInfo = (~) Double
    type AttrTransferTypeConstraint EntryProgressFractionPropertyInfo = (~) Double
    type AttrTransferType EntryProgressFractionPropertyInfo = Double
    type AttrGetType EntryProgressFractionPropertyInfo = Double
    type AttrLabel EntryProgressFractionPropertyInfo = "progress-fraction"
    type AttrOrigin EntryProgressFractionPropertyInfo = Entry
    attrGet = getEntryProgressFraction
    attrSet = setEntryProgressFraction
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryProgressFraction
    attrClear = undefined
#endif
   
   
   
getEntryProgressPulseStep :: (MonadIO m, IsEntry o) => o -> m Double
getEntryProgressPulseStep :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Double
getEntryProgressPulseStep o
obj = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Double
forall a. GObject a => a -> String -> IO Double
B.Properties.getObjectPropertyDouble o
obj String
"progress-pulse-step"
setEntryProgressPulseStep :: (MonadIO m, IsEntry o) => o -> Double -> m ()
setEntryProgressPulseStep :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> Double -> m ()
setEntryProgressPulseStep o
obj Double
val = IO () -> m ()
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 -> Double -> IO ()
forall a. GObject a => a -> String -> Double -> IO ()
B.Properties.setObjectPropertyDouble o
obj String
"progress-pulse-step" Double
val
constructEntryProgressPulseStep :: (IsEntry o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructEntryProgressPulseStep :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructEntryProgressPulseStep Double
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Double -> IO (GValueConstruct o)
forall o. String -> Double -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyDouble String
"progress-pulse-step" Double
val
#if defined(ENABLE_OVERLOADING)
data EntryProgressPulseStepPropertyInfo
instance AttrInfo EntryProgressPulseStepPropertyInfo where
    type AttrAllowedOps EntryProgressPulseStepPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryProgressPulseStepPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryProgressPulseStepPropertyInfo = (~) Double
    type AttrTransferTypeConstraint EntryProgressPulseStepPropertyInfo = (~) Double
    type AttrTransferType EntryProgressPulseStepPropertyInfo = Double
    type AttrGetType EntryProgressPulseStepPropertyInfo = Double
    type AttrLabel EntryProgressPulseStepPropertyInfo = "progress-pulse-step"
    type AttrOrigin EntryProgressPulseStepPropertyInfo = Entry
    attrGet = getEntryProgressPulseStep
    attrSet = setEntryProgressPulseStep
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryProgressPulseStep
    attrClear = undefined
#endif
   
   
   
getEntryScrollOffset :: (MonadIO m, IsEntry o) => o -> m Int32
getEntryScrollOffset :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Int32
getEntryScrollOffset o
obj = IO Int32 -> m Int32
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
"scroll-offset"
#if defined(ENABLE_OVERLOADING)
data EntryScrollOffsetPropertyInfo
instance AttrInfo EntryScrollOffsetPropertyInfo where
    type AttrAllowedOps EntryScrollOffsetPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint EntryScrollOffsetPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryScrollOffsetPropertyInfo = (~) ()
    type AttrTransferTypeConstraint EntryScrollOffsetPropertyInfo = (~) ()
    type AttrTransferType EntryScrollOffsetPropertyInfo = ()
    type AttrGetType EntryScrollOffsetPropertyInfo = Int32
    type AttrLabel EntryScrollOffsetPropertyInfo = "scroll-offset"
    type AttrOrigin EntryScrollOffsetPropertyInfo = Entry
    attrGet = getEntryScrollOffset
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif
   
   
   
getEntrySecondaryIconActivatable :: (MonadIO m, IsEntry o) => o -> m Bool
getEntrySecondaryIconActivatable :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntrySecondaryIconActivatable o
obj = IO Bool -> m Bool
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
"secondary-icon-activatable"
setEntrySecondaryIconActivatable :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntrySecondaryIconActivatable :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntrySecondaryIconActivatable o
obj Bool
val = IO () -> m ()
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
"secondary-icon-activatable" Bool
val
constructEntrySecondaryIconActivatable :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntrySecondaryIconActivatable :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntrySecondaryIconActivatable Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"secondary-icon-activatable" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntrySecondaryIconActivatablePropertyInfo
instance AttrInfo EntrySecondaryIconActivatablePropertyInfo where
    type AttrAllowedOps EntrySecondaryIconActivatablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntrySecondaryIconActivatablePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntrySecondaryIconActivatablePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntrySecondaryIconActivatablePropertyInfo = (~) Bool
    type AttrTransferType EntrySecondaryIconActivatablePropertyInfo = Bool
    type AttrGetType EntrySecondaryIconActivatablePropertyInfo = Bool
    type AttrLabel EntrySecondaryIconActivatablePropertyInfo = "secondary-icon-activatable"
    type AttrOrigin EntrySecondaryIconActivatablePropertyInfo = Entry
    attrGet = getEntrySecondaryIconActivatable
    attrSet = setEntrySecondaryIconActivatable
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntrySecondaryIconActivatable
    attrClear = undefined
#endif
   
   
   
getEntrySecondaryIconGicon :: (MonadIO m, IsEntry o) => o -> m (Maybe Gio.Icon.Icon)
getEntrySecondaryIconGicon :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Icon)
getEntrySecondaryIconGicon o
obj = IO (Maybe Icon) -> m (Maybe Icon)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Icon) -> m (Maybe Icon))
-> IO (Maybe Icon) -> m (Maybe Icon)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Icon -> Icon) -> IO (Maybe Icon)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"secondary-icon-gicon" ManagedPtr Icon -> Icon
Gio.Icon.Icon
setEntrySecondaryIconGicon :: (MonadIO m, IsEntry o, Gio.Icon.IsIcon a) => o -> a -> m ()
setEntrySecondaryIconGicon :: forall (m :: * -> *) o a.
(MonadIO m, IsEntry o, IsIcon a) =>
o -> a -> m ()
setEntrySecondaryIconGicon o
obj a
val = IO () -> m ()
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
"secondary-icon-gicon" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructEntrySecondaryIconGicon :: (IsEntry o, MIO.MonadIO m, Gio.Icon.IsIcon a) => a -> m (GValueConstruct o)
constructEntrySecondaryIconGicon :: forall o (m :: * -> *) a.
(IsEntry o, MonadIO m, IsIcon a) =>
a -> m (GValueConstruct o)
constructEntrySecondaryIconGicon a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"secondary-icon-gicon" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearEntrySecondaryIconGicon :: (MonadIO m, IsEntry o) => o -> m ()
clearEntrySecondaryIconGicon :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntrySecondaryIconGicon o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Icon -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"secondary-icon-gicon" (Maybe Icon
forall a. Maybe a
Nothing :: Maybe Gio.Icon.Icon)
#if defined(ENABLE_OVERLOADING)
data EntrySecondaryIconGiconPropertyInfo
instance AttrInfo EntrySecondaryIconGiconPropertyInfo where
    type AttrAllowedOps EntrySecondaryIconGiconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntrySecondaryIconGiconPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntrySecondaryIconGiconPropertyInfo = Gio.Icon.IsIcon
    type AttrTransferTypeConstraint EntrySecondaryIconGiconPropertyInfo = Gio.Icon.IsIcon
    type AttrTransferType EntrySecondaryIconGiconPropertyInfo = Gio.Icon.Icon
    type AttrGetType EntrySecondaryIconGiconPropertyInfo = (Maybe Gio.Icon.Icon)
    type AttrLabel EntrySecondaryIconGiconPropertyInfo = "secondary-icon-gicon"
    type AttrOrigin EntrySecondaryIconGiconPropertyInfo = Entry
    attrGet = getEntrySecondaryIconGicon
    attrSet = setEntrySecondaryIconGicon
    attrTransfer _ v = do
        unsafeCastTo Gio.Icon.Icon v
    attrConstruct = constructEntrySecondaryIconGicon
    attrClear = clearEntrySecondaryIconGicon
#endif
   
   
   
getEntrySecondaryIconName :: (MonadIO m, IsEntry o) => o -> m (Maybe T.Text)
getEntrySecondaryIconName :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Text)
getEntrySecondaryIconName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"secondary-icon-name"
setEntrySecondaryIconName :: (MonadIO m, IsEntry o) => o -> T.Text -> m ()
setEntrySecondaryIconName :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Text -> m ()
setEntrySecondaryIconName o
obj Text
val = IO () -> m ()
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"secondary-icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructEntrySecondaryIconName :: (IsEntry o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEntrySecondaryIconName :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEntrySecondaryIconName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"secondary-icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearEntrySecondaryIconName :: (MonadIO m, IsEntry o) => o -> m ()
clearEntrySecondaryIconName :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntrySecondaryIconName o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"secondary-icon-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data EntrySecondaryIconNamePropertyInfo
instance AttrInfo EntrySecondaryIconNamePropertyInfo where
    type AttrAllowedOps EntrySecondaryIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntrySecondaryIconNamePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntrySecondaryIconNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EntrySecondaryIconNamePropertyInfo = (~) T.Text
    type AttrTransferType EntrySecondaryIconNamePropertyInfo = T.Text
    type AttrGetType EntrySecondaryIconNamePropertyInfo = (Maybe T.Text)
    type AttrLabel EntrySecondaryIconNamePropertyInfo = "secondary-icon-name"
    type AttrOrigin EntrySecondaryIconNamePropertyInfo = Entry
    attrGet = getEntrySecondaryIconName
    attrSet = setEntrySecondaryIconName
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntrySecondaryIconName
    attrClear = clearEntrySecondaryIconName
#endif
   
   
   
getEntrySecondaryIconPaintable :: (MonadIO m, IsEntry o) => o -> m (Maybe Gdk.Paintable.Paintable)
getEntrySecondaryIconPaintable :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Paintable)
getEntrySecondaryIconPaintable o
obj = IO (Maybe Paintable) -> m (Maybe Paintable)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Paintable) -> m (Maybe Paintable))
-> IO (Maybe Paintable) -> m (Maybe Paintable)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Paintable -> Paintable)
-> IO (Maybe Paintable)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"secondary-icon-paintable" ManagedPtr Paintable -> Paintable
Gdk.Paintable.Paintable
setEntrySecondaryIconPaintable :: (MonadIO m, IsEntry o, Gdk.Paintable.IsPaintable a) => o -> a -> m ()
setEntrySecondaryIconPaintable :: forall (m :: * -> *) o a.
(MonadIO m, IsEntry o, IsPaintable a) =>
o -> a -> m ()
setEntrySecondaryIconPaintable o
obj a
val = IO () -> m ()
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
"secondary-icon-paintable" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructEntrySecondaryIconPaintable :: (IsEntry o, MIO.MonadIO m, Gdk.Paintable.IsPaintable a) => a -> m (GValueConstruct o)
constructEntrySecondaryIconPaintable :: forall o (m :: * -> *) a.
(IsEntry o, MonadIO m, IsPaintable a) =>
a -> m (GValueConstruct o)
constructEntrySecondaryIconPaintable a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"secondary-icon-paintable" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearEntrySecondaryIconPaintable :: (MonadIO m, IsEntry o) => o -> m ()
clearEntrySecondaryIconPaintable :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntrySecondaryIconPaintable o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Paintable -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"secondary-icon-paintable" (Maybe Paintable
forall a. Maybe a
Nothing :: Maybe Gdk.Paintable.Paintable)
#if defined(ENABLE_OVERLOADING)
data EntrySecondaryIconPaintablePropertyInfo
instance AttrInfo EntrySecondaryIconPaintablePropertyInfo where
    type AttrAllowedOps EntrySecondaryIconPaintablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntrySecondaryIconPaintablePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntrySecondaryIconPaintablePropertyInfo = Gdk.Paintable.IsPaintable
    type AttrTransferTypeConstraint EntrySecondaryIconPaintablePropertyInfo = Gdk.Paintable.IsPaintable
    type AttrTransferType EntrySecondaryIconPaintablePropertyInfo = Gdk.Paintable.Paintable
    type AttrGetType EntrySecondaryIconPaintablePropertyInfo = (Maybe Gdk.Paintable.Paintable)
    type AttrLabel EntrySecondaryIconPaintablePropertyInfo = "secondary-icon-paintable"
    type AttrOrigin EntrySecondaryIconPaintablePropertyInfo = Entry
    attrGet = getEntrySecondaryIconPaintable
    attrSet = setEntrySecondaryIconPaintable
    attrTransfer _ v = do
        unsafeCastTo Gdk.Paintable.Paintable v
    attrConstruct = constructEntrySecondaryIconPaintable
    attrClear = clearEntrySecondaryIconPaintable
#endif
   
   
   
getEntrySecondaryIconSensitive :: (MonadIO m, IsEntry o) => o -> m Bool
getEntrySecondaryIconSensitive :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntrySecondaryIconSensitive o
obj = IO Bool -> m Bool
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
"secondary-icon-sensitive"
setEntrySecondaryIconSensitive :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntrySecondaryIconSensitive :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntrySecondaryIconSensitive o
obj Bool
val = IO () -> m ()
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
"secondary-icon-sensitive" Bool
val
constructEntrySecondaryIconSensitive :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntrySecondaryIconSensitive :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntrySecondaryIconSensitive Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"secondary-icon-sensitive" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntrySecondaryIconSensitivePropertyInfo
instance AttrInfo EntrySecondaryIconSensitivePropertyInfo where
    type AttrAllowedOps EntrySecondaryIconSensitivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntrySecondaryIconSensitivePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntrySecondaryIconSensitivePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntrySecondaryIconSensitivePropertyInfo = (~) Bool
    type AttrTransferType EntrySecondaryIconSensitivePropertyInfo = Bool
    type AttrGetType EntrySecondaryIconSensitivePropertyInfo = Bool
    type AttrLabel EntrySecondaryIconSensitivePropertyInfo = "secondary-icon-sensitive"
    type AttrOrigin EntrySecondaryIconSensitivePropertyInfo = Entry
    attrGet = getEntrySecondaryIconSensitive
    attrSet = setEntrySecondaryIconSensitive
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntrySecondaryIconSensitive
    attrClear = undefined
#endif
   
   
   
getEntrySecondaryIconStorageType :: (MonadIO m, IsEntry o) => o -> m Gtk.Enums.ImageType
getEntrySecondaryIconStorageType :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ImageType
getEntrySecondaryIconStorageType o
obj = IO ImageType -> m ImageType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ImageType -> m ImageType) -> IO ImageType -> m ImageType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO ImageType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"secondary-icon-storage-type"
#if defined(ENABLE_OVERLOADING)
data EntrySecondaryIconStorageTypePropertyInfo
instance AttrInfo EntrySecondaryIconStorageTypePropertyInfo where
    type AttrAllowedOps EntrySecondaryIconStorageTypePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint EntrySecondaryIconStorageTypePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntrySecondaryIconStorageTypePropertyInfo = (~) ()
    type AttrTransferTypeConstraint EntrySecondaryIconStorageTypePropertyInfo = (~) ()
    type AttrTransferType EntrySecondaryIconStorageTypePropertyInfo = ()
    type AttrGetType EntrySecondaryIconStorageTypePropertyInfo = Gtk.Enums.ImageType
    type AttrLabel EntrySecondaryIconStorageTypePropertyInfo = "secondary-icon-storage-type"
    type AttrOrigin EntrySecondaryIconStorageTypePropertyInfo = Entry
    attrGet = getEntrySecondaryIconStorageType
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif
   
   
   
getEntrySecondaryIconTooltipMarkup :: (MonadIO m, IsEntry o) => o -> m (Maybe T.Text)
getEntrySecondaryIconTooltipMarkup :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Text)
getEntrySecondaryIconTooltipMarkup o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"secondary-icon-tooltip-markup"
setEntrySecondaryIconTooltipMarkup :: (MonadIO m, IsEntry o) => o -> T.Text -> m ()
setEntrySecondaryIconTooltipMarkup :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Text -> m ()
setEntrySecondaryIconTooltipMarkup o
obj Text
val = IO () -> m ()
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"secondary-icon-tooltip-markup" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructEntrySecondaryIconTooltipMarkup :: (IsEntry o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEntrySecondaryIconTooltipMarkup :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEntrySecondaryIconTooltipMarkup Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"secondary-icon-tooltip-markup" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearEntrySecondaryIconTooltipMarkup :: (MonadIO m, IsEntry o) => o -> m ()
clearEntrySecondaryIconTooltipMarkup :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntrySecondaryIconTooltipMarkup o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"secondary-icon-tooltip-markup" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data EntrySecondaryIconTooltipMarkupPropertyInfo
instance AttrInfo EntrySecondaryIconTooltipMarkupPropertyInfo where
    type AttrAllowedOps EntrySecondaryIconTooltipMarkupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntrySecondaryIconTooltipMarkupPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntrySecondaryIconTooltipMarkupPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EntrySecondaryIconTooltipMarkupPropertyInfo = (~) T.Text
    type AttrTransferType EntrySecondaryIconTooltipMarkupPropertyInfo = T.Text
    type AttrGetType EntrySecondaryIconTooltipMarkupPropertyInfo = (Maybe T.Text)
    type AttrLabel EntrySecondaryIconTooltipMarkupPropertyInfo = "secondary-icon-tooltip-markup"
    type AttrOrigin EntrySecondaryIconTooltipMarkupPropertyInfo = Entry
    attrGet = getEntrySecondaryIconTooltipMarkup
    attrSet = setEntrySecondaryIconTooltipMarkup
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntrySecondaryIconTooltipMarkup
    attrClear = clearEntrySecondaryIconTooltipMarkup
#endif
   
   
   
getEntrySecondaryIconTooltipText :: (MonadIO m, IsEntry o) => o -> m (Maybe T.Text)
getEntrySecondaryIconTooltipText :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe Text)
getEntrySecondaryIconTooltipText o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"secondary-icon-tooltip-text"
setEntrySecondaryIconTooltipText :: (MonadIO m, IsEntry o) => o -> T.Text -> m ()
setEntrySecondaryIconTooltipText :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Text -> m ()
setEntrySecondaryIconTooltipText o
obj Text
val = IO () -> m ()
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"secondary-icon-tooltip-text" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructEntrySecondaryIconTooltipText :: (IsEntry o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEntrySecondaryIconTooltipText :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEntrySecondaryIconTooltipText Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"secondary-icon-tooltip-text" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearEntrySecondaryIconTooltipText :: (MonadIO m, IsEntry o) => o -> m ()
clearEntrySecondaryIconTooltipText :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntrySecondaryIconTooltipText o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"secondary-icon-tooltip-text" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data EntrySecondaryIconTooltipTextPropertyInfo
instance AttrInfo EntrySecondaryIconTooltipTextPropertyInfo where
    type AttrAllowedOps EntrySecondaryIconTooltipTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntrySecondaryIconTooltipTextPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntrySecondaryIconTooltipTextPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EntrySecondaryIconTooltipTextPropertyInfo = (~) T.Text
    type AttrTransferType EntrySecondaryIconTooltipTextPropertyInfo = T.Text
    type AttrGetType EntrySecondaryIconTooltipTextPropertyInfo = (Maybe T.Text)
    type AttrLabel EntrySecondaryIconTooltipTextPropertyInfo = "secondary-icon-tooltip-text"
    type AttrOrigin EntrySecondaryIconTooltipTextPropertyInfo = Entry
    attrGet = getEntrySecondaryIconTooltipText
    attrSet = setEntrySecondaryIconTooltipText
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntrySecondaryIconTooltipText
    attrClear = clearEntrySecondaryIconTooltipText
#endif
   
   
   
getEntryShowEmojiIcon :: (MonadIO m, IsEntry o) => o -> m Bool
getEntryShowEmojiIcon :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntryShowEmojiIcon o
obj = IO Bool -> m Bool
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
"show-emoji-icon"
setEntryShowEmojiIcon :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryShowEmojiIcon :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryShowEmojiIcon o
obj Bool
val = IO () -> m ()
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
"show-emoji-icon" Bool
val
constructEntryShowEmojiIcon :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryShowEmojiIcon :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryShowEmojiIcon Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"show-emoji-icon" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntryShowEmojiIconPropertyInfo
instance AttrInfo EntryShowEmojiIconPropertyInfo where
    type AttrAllowedOps EntryShowEmojiIconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryShowEmojiIconPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryShowEmojiIconPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryShowEmojiIconPropertyInfo = (~) Bool
    type AttrTransferType EntryShowEmojiIconPropertyInfo = Bool
    type AttrGetType EntryShowEmojiIconPropertyInfo = Bool
    type AttrLabel EntryShowEmojiIconPropertyInfo = "show-emoji-icon"
    type AttrOrigin EntryShowEmojiIconPropertyInfo = Entry
    attrGet = getEntryShowEmojiIcon
    attrSet = setEntryShowEmojiIcon
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryShowEmojiIcon
    attrClear = undefined
#endif
   
   
   
getEntryTabs :: (MonadIO m, IsEntry o) => o -> m (Maybe Pango.TabArray.TabArray)
getEntryTabs :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> m (Maybe TabArray)
getEntryTabs o
obj = IO (Maybe TabArray) -> m (Maybe TabArray)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe TabArray) -> m (Maybe TabArray))
-> IO (Maybe TabArray) -> m (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TabArray -> TabArray)
-> IO (Maybe TabArray)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"tabs" ManagedPtr TabArray -> TabArray
Pango.TabArray.TabArray
setEntryTabs :: (MonadIO m, IsEntry o) => o -> Pango.TabArray.TabArray -> m ()
setEntryTabs :: forall (m :: * -> *) o.
(MonadIO m, IsEntry o) =>
o -> TabArray -> m ()
setEntryTabs o
obj TabArray
val = IO () -> m ()
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 TabArray -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"tabs" (TabArray -> Maybe TabArray
forall a. a -> Maybe a
Just TabArray
val)
constructEntryTabs :: (IsEntry o, MIO.MonadIO m) => Pango.TabArray.TabArray -> m (GValueConstruct o)
constructEntryTabs :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
TabArray -> m (GValueConstruct o)
constructEntryTabs TabArray
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 TabArray -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"tabs" (TabArray -> Maybe TabArray
forall a. a -> Maybe a
P.Just TabArray
val)
clearEntryTabs :: (MonadIO m, IsEntry o) => o -> m ()
clearEntryTabs :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m ()
clearEntryTabs o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe TabArray -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"tabs" (Maybe TabArray
forall a. Maybe a
Nothing :: Maybe Pango.TabArray.TabArray)
#if defined(ENABLE_OVERLOADING)
data EntryTabsPropertyInfo
instance AttrInfo EntryTabsPropertyInfo where
    type AttrAllowedOps EntryTabsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EntryTabsPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryTabsPropertyInfo = (~) Pango.TabArray.TabArray
    type AttrTransferTypeConstraint EntryTabsPropertyInfo = (~) Pango.TabArray.TabArray
    type AttrTransferType EntryTabsPropertyInfo = Pango.TabArray.TabArray
    type AttrGetType EntryTabsPropertyInfo = (Maybe Pango.TabArray.TabArray)
    type AttrLabel EntryTabsPropertyInfo = "tabs"
    type AttrOrigin EntryTabsPropertyInfo = Entry
    attrGet = getEntryTabs
    attrSet = setEntryTabs
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryTabs
    attrClear = clearEntryTabs
#endif
   
   
   
getEntryTextLength :: (MonadIO m, IsEntry o) => o -> m Word32
getEntryTextLength :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Word32
getEntryTextLength o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"text-length"
#if defined(ENABLE_OVERLOADING)
data EntryTextLengthPropertyInfo
instance AttrInfo EntryTextLengthPropertyInfo where
    type AttrAllowedOps EntryTextLengthPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint EntryTextLengthPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryTextLengthPropertyInfo = (~) ()
    type AttrTransferTypeConstraint EntryTextLengthPropertyInfo = (~) ()
    type AttrTransferType EntryTextLengthPropertyInfo = ()
    type AttrGetType EntryTextLengthPropertyInfo = Word32
    type AttrLabel EntryTextLengthPropertyInfo = "text-length"
    type AttrOrigin EntryTextLengthPropertyInfo = Entry
    attrGet = getEntryTextLength
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif
   
   
   
getEntryTruncateMultiline :: (MonadIO m, IsEntry o) => o -> m Bool
getEntryTruncateMultiline :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntryTruncateMultiline o
obj = IO Bool -> m Bool
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
"truncate-multiline"
setEntryTruncateMultiline :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryTruncateMultiline :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryTruncateMultiline o
obj Bool
val = IO () -> m ()
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
"truncate-multiline" Bool
val
constructEntryTruncateMultiline :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryTruncateMultiline :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryTruncateMultiline Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"truncate-multiline" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntryTruncateMultilinePropertyInfo
instance AttrInfo EntryTruncateMultilinePropertyInfo where
    type AttrAllowedOps EntryTruncateMultilinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryTruncateMultilinePropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryTruncateMultilinePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryTruncateMultilinePropertyInfo = (~) Bool
    type AttrTransferType EntryTruncateMultilinePropertyInfo = Bool
    type AttrGetType EntryTruncateMultilinePropertyInfo = Bool
    type AttrLabel EntryTruncateMultilinePropertyInfo = "truncate-multiline"
    type AttrOrigin EntryTruncateMultilinePropertyInfo = Entry
    attrGet = getEntryTruncateMultiline
    attrSet = setEntryTruncateMultiline
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryTruncateMultiline
    attrClear = undefined
#endif
   
   
   
getEntryVisibility :: (MonadIO m, IsEntry o) => o -> m Bool
getEntryVisibility :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> m Bool
getEntryVisibility o
obj = IO Bool -> m Bool
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
"visibility"
setEntryVisibility :: (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryVisibility :: forall (m :: * -> *) o. (MonadIO m, IsEntry o) => o -> Bool -> m ()
setEntryVisibility o
obj Bool
val = IO () -> m ()
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
"visibility" Bool
val
constructEntryVisibility :: (IsEntry o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructEntryVisibility :: forall o (m :: * -> *).
(IsEntry o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructEntryVisibility Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"visibility" Bool
val
#if defined(ENABLE_OVERLOADING)
data EntryVisibilityPropertyInfo
instance AttrInfo EntryVisibilityPropertyInfo where
    type AttrAllowedOps EntryVisibilityPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EntryVisibilityPropertyInfo = IsEntry
    type AttrSetTypeConstraint EntryVisibilityPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint EntryVisibilityPropertyInfo = (~) Bool
    type AttrTransferType EntryVisibilityPropertyInfo = Bool
    type AttrGetType EntryVisibilityPropertyInfo = Bool
    type AttrLabel EntryVisibilityPropertyInfo = "visibility"
    type AttrOrigin EntryVisibilityPropertyInfo = Entry
    attrGet = getEntryVisibility
    attrSet = setEntryVisibility
    attrTransfer _ v = do
        return v
    attrConstruct = constructEntryVisibility
    attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Entry
type instance O.AttributeList Entry = EntryAttributeList
type EntryAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("activatesDefault", EntryActivatesDefaultPropertyInfo), '("attributes", EntryAttributesPropertyInfo), '("buffer", EntryBufferPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("completion", EntryCompletionPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("cursorPosition", Gtk.Editable.EditableCursorPositionPropertyInfo), '("editable", Gtk.Editable.EditableEditablePropertyInfo), '("editingCanceled", Gtk.CellEditable.CellEditableEditingCanceledPropertyInfo), '("enableEmojiCompletion", EntryEnableEmojiCompletionPropertyInfo), '("enableUndo", Gtk.Editable.EditableEnableUndoPropertyInfo), '("extraMenu", EntryExtraMenuPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasFrame", EntryHasFramePropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("imModule", EntryImModulePropertyInfo), '("inputHints", EntryInputHintsPropertyInfo), '("inputPurpose", EntryInputPurposePropertyInfo), '("invisibleChar", EntryInvisibleCharPropertyInfo), '("invisibleCharSet", EntryInvisibleCharSetPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("maxLength", EntryMaxLengthPropertyInfo), '("maxWidthChars", Gtk.Editable.EditableMaxWidthCharsPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("overwriteMode", EntryOverwriteModePropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("placeholderText", EntryPlaceholderTextPropertyInfo), '("primaryIconActivatable", EntryPrimaryIconActivatablePropertyInfo), '("primaryIconGicon", EntryPrimaryIconGiconPropertyInfo), '("primaryIconName", EntryPrimaryIconNamePropertyInfo), '("primaryIconPaintable", EntryPrimaryIconPaintablePropertyInfo), '("primaryIconSensitive", EntryPrimaryIconSensitivePropertyInfo), '("primaryIconStorageType", EntryPrimaryIconStorageTypePropertyInfo), '("primaryIconTooltipMarkup", EntryPrimaryIconTooltipMarkupPropertyInfo), '("primaryIconTooltipText", EntryPrimaryIconTooltipTextPropertyInfo), '("progressFraction", EntryProgressFractionPropertyInfo), '("progressPulseStep", EntryProgressPulseStepPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("scrollOffset", EntryScrollOffsetPropertyInfo), '("secondaryIconActivatable", EntrySecondaryIconActivatablePropertyInfo), '("secondaryIconGicon", EntrySecondaryIconGiconPropertyInfo), '("secondaryIconName", EntrySecondaryIconNamePropertyInfo), '("secondaryIconPaintable", EntrySecondaryIconPaintablePropertyInfo), '("secondaryIconSensitive", EntrySecondaryIconSensitivePropertyInfo), '("secondaryIconStorageType", EntrySecondaryIconStorageTypePropertyInfo), '("secondaryIconTooltipMarkup", EntrySecondaryIconTooltipMarkupPropertyInfo), '("secondaryIconTooltipText", EntrySecondaryIconTooltipTextPropertyInfo), '("selectionBound", Gtk.Editable.EditableSelectionBoundPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("showEmojiIcon", EntryShowEmojiIconPropertyInfo), '("tabs", EntryTabsPropertyInfo), '("text", Gtk.Editable.EditableTextPropertyInfo), '("textLength", EntryTextLengthPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("truncateMultiline", EntryTruncateMultilinePropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visibility", EntryVisibilityPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthChars", Gtk.Editable.EditableWidthCharsPropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("xalign", Gtk.Editable.EditableXalignPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
entryActivatesDefault :: AttrLabelProxy "activatesDefault"
entryActivatesDefault = AttrLabelProxy
entryAttributes :: AttrLabelProxy "attributes"
entryAttributes = AttrLabelProxy
entryBuffer :: AttrLabelProxy "buffer"
entryBuffer = AttrLabelProxy
entryCompletion :: AttrLabelProxy "completion"
entryCompletion = AttrLabelProxy
entryEnableEmojiCompletion :: AttrLabelProxy "enableEmojiCompletion"
entryEnableEmojiCompletion = AttrLabelProxy
entryExtraMenu :: AttrLabelProxy "extraMenu"
entryExtraMenu = AttrLabelProxy
entryHasFrame :: AttrLabelProxy "hasFrame"
entryHasFrame = AttrLabelProxy
entryImModule :: AttrLabelProxy "imModule"
entryImModule = AttrLabelProxy
entryInputHints :: AttrLabelProxy "inputHints"
entryInputHints = AttrLabelProxy
entryInputPurpose :: AttrLabelProxy "inputPurpose"
entryInputPurpose = AttrLabelProxy
entryInvisibleChar :: AttrLabelProxy "invisibleChar"
entryInvisibleChar = AttrLabelProxy
entryInvisibleCharSet :: AttrLabelProxy "invisibleCharSet"
entryInvisibleCharSet = AttrLabelProxy
entryMaxLength :: AttrLabelProxy "maxLength"
entryMaxLength = AttrLabelProxy
entryOverwriteMode :: AttrLabelProxy "overwriteMode"
entryOverwriteMode = AttrLabelProxy
entryPlaceholderText :: AttrLabelProxy "placeholderText"
entryPlaceholderText = AttrLabelProxy
entryPrimaryIconActivatable :: AttrLabelProxy "primaryIconActivatable"
entryPrimaryIconActivatable = AttrLabelProxy
entryPrimaryIconGicon :: AttrLabelProxy "primaryIconGicon"
entryPrimaryIconGicon = AttrLabelProxy
entryPrimaryIconName :: AttrLabelProxy "primaryIconName"
entryPrimaryIconName = AttrLabelProxy
entryPrimaryIconPaintable :: AttrLabelProxy "primaryIconPaintable"
entryPrimaryIconPaintable = AttrLabelProxy
entryPrimaryIconSensitive :: AttrLabelProxy "primaryIconSensitive"
entryPrimaryIconSensitive = AttrLabelProxy
entryPrimaryIconStorageType :: AttrLabelProxy "primaryIconStorageType"
entryPrimaryIconStorageType = AttrLabelProxy
entryPrimaryIconTooltipMarkup :: AttrLabelProxy "primaryIconTooltipMarkup"
entryPrimaryIconTooltipMarkup = AttrLabelProxy
entryPrimaryIconTooltipText :: AttrLabelProxy "primaryIconTooltipText"
entryPrimaryIconTooltipText = AttrLabelProxy
entryProgressFraction :: AttrLabelProxy "progressFraction"
entryProgressFraction = AttrLabelProxy
entryProgressPulseStep :: AttrLabelProxy "progressPulseStep"
entryProgressPulseStep = AttrLabelProxy
entryScrollOffset :: AttrLabelProxy "scrollOffset"
entryScrollOffset = AttrLabelProxy
entrySecondaryIconActivatable :: AttrLabelProxy "secondaryIconActivatable"
entrySecondaryIconActivatable = AttrLabelProxy
entrySecondaryIconGicon :: AttrLabelProxy "secondaryIconGicon"
entrySecondaryIconGicon = AttrLabelProxy
entrySecondaryIconName :: AttrLabelProxy "secondaryIconName"
entrySecondaryIconName = AttrLabelProxy
entrySecondaryIconPaintable :: AttrLabelProxy "secondaryIconPaintable"
entrySecondaryIconPaintable = AttrLabelProxy
entrySecondaryIconSensitive :: AttrLabelProxy "secondaryIconSensitive"
entrySecondaryIconSensitive = AttrLabelProxy
entrySecondaryIconStorageType :: AttrLabelProxy "secondaryIconStorageType"
entrySecondaryIconStorageType = AttrLabelProxy
entrySecondaryIconTooltipMarkup :: AttrLabelProxy "secondaryIconTooltipMarkup"
entrySecondaryIconTooltipMarkup = AttrLabelProxy
entrySecondaryIconTooltipText :: AttrLabelProxy "secondaryIconTooltipText"
entrySecondaryIconTooltipText = AttrLabelProxy
entryShowEmojiIcon :: AttrLabelProxy "showEmojiIcon"
entryShowEmojiIcon = AttrLabelProxy
entryTabs :: AttrLabelProxy "tabs"
entryTabs = AttrLabelProxy
entryTextLength :: AttrLabelProxy "textLength"
entryTextLength = AttrLabelProxy
entryTruncateMultiline :: AttrLabelProxy "truncateMultiline"
entryTruncateMultiline = AttrLabelProxy
entryVisibility :: AttrLabelProxy "visibility"
entryVisibility = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Entry = EntrySignalList
type EntrySignalList = ('[ '("activate", EntryActivateSignalInfo), '("changed", Gtk.Editable.EditableChangedSignalInfo), '("deleteText", Gtk.Editable.EditableDeleteTextSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("editingDone", Gtk.CellEditable.CellEditableEditingDoneSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("iconPress", EntryIconPressSignalInfo), '("iconRelease", EntryIconReleaseSignalInfo), '("insertText", Gtk.Editable.EditableInsertTextSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("removeWidget", Gtk.CellEditable.CellEditableRemoveWidgetSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_entry_new" gtk_entry_new :: 
    IO (Ptr Entry)
entryNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Entry
    
entryNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Entry
entryNew  = IO Entry -> m Entry
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Entry -> m Entry) -> IO Entry -> m Entry
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
result <- IO (Ptr Entry)
gtk_entry_new
    Text -> Ptr Entry -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"entryNew" Ptr Entry
result
    Entry
result' <- ((ManagedPtr Entry -> Entry) -> Ptr Entry -> IO Entry
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Entry -> Entry
Entry) Ptr Entry
result
    Entry -> IO Entry
forall (m :: * -> *) a. Monad m => a -> m a
return Entry
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_entry_new_with_buffer" gtk_entry_new_with_buffer :: 
    Ptr Gtk.EntryBuffer.EntryBuffer ->      
    IO (Ptr Entry)
entryNewWithBuffer ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.EntryBuffer.IsEntryBuffer a) =>
    a
    
    -> m Entry
    
entryNewWithBuffer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntryBuffer a) =>
a -> m Entry
entryNewWithBuffer a
buffer = IO Entry -> m Entry
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Entry -> m Entry) -> IO Entry -> m Entry
forall a b. (a -> b) -> a -> b
$ do
    Ptr EntryBuffer
buffer' <- a -> IO (Ptr EntryBuffer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buffer
    Ptr Entry
result <- Ptr EntryBuffer -> IO (Ptr Entry)
gtk_entry_new_with_buffer Ptr EntryBuffer
buffer'
    Text -> Ptr Entry -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"entryNewWithBuffer" Ptr Entry
result
    Entry
result' <- ((ManagedPtr Entry -> Entry) -> Ptr Entry -> IO Entry
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Entry -> Entry
Entry) Ptr Entry
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buffer
    Entry -> IO Entry
forall (m :: * -> *) a. Monad m => a -> m a
return Entry
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_entry_get_activates_default" gtk_entry_get_activates_default :: 
    Ptr Entry ->                            
    IO CInt
entryGetActivatesDefault ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Bool
    
entryGetActivatesDefault :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Bool
entryGetActivatesDefault a
entry = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CInt
result <- Ptr Entry -> IO CInt
gtk_entry_get_activates_default Ptr Entry
entry'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetActivatesDefaultMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetActivatesDefaultMethodInfo a signature where
    overloadedMethod = entryGetActivatesDefault
instance O.OverloadedMethodInfo EntryGetActivatesDefaultMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetActivatesDefault",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetActivatesDefault"
        }
#endif
foreign import ccall "gtk_entry_get_alignment" gtk_entry_get_alignment :: 
    Ptr Entry ->                            
    IO CFloat
entryGetAlignment ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Float
    
entryGetAlignment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Float
entryGetAlignment a
entry = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CFloat
result <- Ptr Entry -> IO CFloat
gtk_entry_get_alignment Ptr Entry
entry'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetAlignmentMethodInfo
instance (signature ~ (m Float), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetAlignmentMethodInfo a signature where
    overloadedMethod = entryGetAlignment
instance O.OverloadedMethodInfo EntryGetAlignmentMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetAlignment",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetAlignment"
        }
#endif
foreign import ccall "gtk_entry_get_attributes" gtk_entry_get_attributes :: 
    Ptr Entry ->                            
    IO (Ptr Pango.AttrList.AttrList)
entryGetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m (Maybe Pango.AttrList.AttrList)
    
    
entryGetAttributes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m (Maybe AttrList)
entryGetAttributes a
entry = IO (Maybe AttrList) -> m (Maybe AttrList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe AttrList) -> m (Maybe AttrList))
-> IO (Maybe AttrList) -> m (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr AttrList
result <- Ptr Entry -> IO (Ptr AttrList)
gtk_entry_get_attributes Ptr Entry
entry'
    Maybe AttrList
maybeResult <- Ptr AttrList
-> (Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr AttrList
result ((Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList))
-> (Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ \Ptr AttrList
result' -> do
        AttrList
result'' <- ((ManagedPtr AttrList -> AttrList) -> Ptr AttrList -> IO AttrList
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr AttrList -> AttrList
Pango.AttrList.AttrList) Ptr AttrList
result'
        AttrList -> IO AttrList
forall (m :: * -> *) a. Monad m => a -> m a
return AttrList
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe AttrList -> IO (Maybe AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AttrList
maybeResult
#if defined(ENABLE_OVERLOADING)
data EntryGetAttributesMethodInfo
instance (signature ~ (m (Maybe Pango.AttrList.AttrList)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetAttributesMethodInfo a signature where
    overloadedMethod = entryGetAttributes
instance O.OverloadedMethodInfo EntryGetAttributesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetAttributes",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetAttributes"
        }
#endif
foreign import ccall "gtk_entry_get_buffer" gtk_entry_get_buffer :: 
    Ptr Entry ->                            
    IO (Ptr Gtk.EntryBuffer.EntryBuffer)
entryGetBuffer ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Gtk.EntryBuffer.EntryBuffer
    
entryGetBuffer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m EntryBuffer
entryGetBuffer a
entry = IO EntryBuffer -> m EntryBuffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EntryBuffer -> m EntryBuffer)
-> IO EntryBuffer -> m EntryBuffer
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr EntryBuffer
result <- Ptr Entry -> IO (Ptr EntryBuffer)
gtk_entry_get_buffer Ptr Entry
entry'
    Text -> Ptr EntryBuffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"entryGetBuffer" Ptr EntryBuffer
result
    EntryBuffer
result' <- ((ManagedPtr EntryBuffer -> EntryBuffer)
-> Ptr EntryBuffer -> IO EntryBuffer
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr EntryBuffer -> EntryBuffer
Gtk.EntryBuffer.EntryBuffer) Ptr EntryBuffer
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    EntryBuffer -> IO EntryBuffer
forall (m :: * -> *) a. Monad m => a -> m a
return EntryBuffer
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetBufferMethodInfo
instance (signature ~ (m Gtk.EntryBuffer.EntryBuffer), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetBufferMethodInfo a signature where
    overloadedMethod = entryGetBuffer
instance O.OverloadedMethodInfo EntryGetBufferMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetBuffer",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetBuffer"
        }
#endif
foreign import ccall "gtk_entry_get_completion" gtk_entry_get_completion :: 
    Ptr Entry ->                            
    IO (Ptr Gtk.EntryCompletion.EntryCompletion)
entryGetCompletion ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m (Maybe Gtk.EntryCompletion.EntryCompletion)
    
    
entryGetCompletion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m (Maybe EntryCompletion)
entryGetCompletion a
entry = IO (Maybe EntryCompletion) -> m (Maybe EntryCompletion)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe EntryCompletion) -> m (Maybe EntryCompletion))
-> IO (Maybe EntryCompletion) -> m (Maybe EntryCompletion)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr EntryCompletion
result <- Ptr Entry -> IO (Ptr EntryCompletion)
gtk_entry_get_completion Ptr Entry
entry'
    Maybe EntryCompletion
maybeResult <- Ptr EntryCompletion
-> (Ptr EntryCompletion -> IO EntryCompletion)
-> IO (Maybe EntryCompletion)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr EntryCompletion
result ((Ptr EntryCompletion -> IO EntryCompletion)
 -> IO (Maybe EntryCompletion))
-> (Ptr EntryCompletion -> IO EntryCompletion)
-> IO (Maybe EntryCompletion)
forall a b. (a -> b) -> a -> b
$ \Ptr EntryCompletion
result' -> do
        EntryCompletion
result'' <- ((ManagedPtr EntryCompletion -> EntryCompletion)
-> Ptr EntryCompletion -> IO EntryCompletion
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr EntryCompletion -> EntryCompletion
Gtk.EntryCompletion.EntryCompletion) Ptr EntryCompletion
result'
        EntryCompletion -> IO EntryCompletion
forall (m :: * -> *) a. Monad m => a -> m a
return EntryCompletion
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe EntryCompletion -> IO (Maybe EntryCompletion)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe EntryCompletion
maybeResult
#if defined(ENABLE_OVERLOADING)
data EntryGetCompletionMethodInfo
instance (signature ~ (m (Maybe Gtk.EntryCompletion.EntryCompletion)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetCompletionMethodInfo a signature where
    overloadedMethod = entryGetCompletion
instance O.OverloadedMethodInfo EntryGetCompletionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetCompletion",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetCompletion"
        }
#endif
foreign import ccall "gtk_entry_get_current_icon_drag_source" gtk_entry_get_current_icon_drag_source :: 
    Ptr Entry ->                            
    IO Int32
entryGetCurrentIconDragSource ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Int32
    
    
entryGetCurrentIconDragSource :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Int32
entryGetCurrentIconDragSource a
entry = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Int32
result <- Ptr Entry -> IO Int32
gtk_entry_get_current_icon_drag_source Ptr Entry
entry'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data EntryGetCurrentIconDragSourceMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetCurrentIconDragSourceMethodInfo a signature where
    overloadedMethod = entryGetCurrentIconDragSource
instance O.OverloadedMethodInfo EntryGetCurrentIconDragSourceMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetCurrentIconDragSource",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetCurrentIconDragSource"
        }
#endif
foreign import ccall "gtk_entry_get_extra_menu"  :: 
    Ptr Entry ->                            
    IO (Ptr Gio.MenuModel.MenuModel)
entryGetExtraMenu ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m (Maybe Gio.MenuModel.MenuModel)
    
 a
entry = IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MenuModel) -> m (Maybe MenuModel))
-> IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr MenuModel
result <- Ptr Entry -> IO (Ptr MenuModel)
gtk_entry_get_extra_menu Ptr Entry
entry'
    Maybe MenuModel
maybeResult <- Ptr MenuModel
-> (Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr MenuModel
result ((Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel))
-> (Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ \Ptr MenuModel
result' -> do
        MenuModel
result'' <- ((ManagedPtr MenuModel -> MenuModel)
-> Ptr MenuModel -> IO MenuModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel) Ptr MenuModel
result'
        MenuModel -> IO MenuModel
forall (m :: * -> *) a. Monad m => a -> m a
return MenuModel
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe MenuModel -> IO (Maybe MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MenuModel
maybeResult
#if defined(ENABLE_OVERLOADING)
data EntryGetExtraMenuMethodInfo
instance (signature ~ (m (Maybe Gio.MenuModel.MenuModel)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetExtraMenuMethodInfo a signature where
    overloadedMethod = entryGetExtraMenu
instance O.OverloadedMethodInfo EntryGetExtraMenuMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetExtraMenu",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetExtraMenu"
        }
#endif
foreign import ccall "gtk_entry_get_has_frame" gtk_entry_get_has_frame :: 
    Ptr Entry ->                            
    IO CInt
entryGetHasFrame ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Bool
    
entryGetHasFrame :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Bool
entryGetHasFrame a
entry = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CInt
result <- Ptr Entry -> IO CInt
gtk_entry_get_has_frame Ptr Entry
entry'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetHasFrameMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetHasFrameMethodInfo a signature where
    overloadedMethod = entryGetHasFrame
instance O.OverloadedMethodInfo EntryGetHasFrameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetHasFrame",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetHasFrame"
        }
#endif
foreign import ccall "gtk_entry_get_icon_activatable" gtk_entry_get_icon_activatable :: 
    Ptr Entry ->                            
    CUInt ->                                
    IO CInt
entryGetIconActivatable ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> m Bool
    
entryGetIconActivatable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> m Bool
entryGetIconActivatable a
entry EntryIconPosition
iconPos = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    CInt
result <- Ptr Entry -> CUInt -> IO CInt
gtk_entry_get_icon_activatable Ptr Entry
entry' CUInt
iconPos'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetIconActivatableMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> m Bool), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetIconActivatableMethodInfo a signature where
    overloadedMethod = entryGetIconActivatable
instance O.OverloadedMethodInfo EntryGetIconActivatableMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetIconActivatable",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetIconActivatable"
        }
#endif
foreign import ccall "gtk_entry_get_icon_area" gtk_entry_get_icon_area :: 
    Ptr Entry ->                            
    CUInt ->                                
    Ptr Gdk.Rectangle.Rectangle ->          
    IO ()
entryGetIconArea ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> m (Gdk.Rectangle.Rectangle)
entryGetIconArea :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> m Rectangle
entryGetIconArea a
entry EntryIconPosition
iconPos = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    Ptr Rectangle
iconArea <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Gdk.Rectangle.Rectangle)
    Ptr Entry -> CUInt -> Ptr Rectangle -> IO ()
gtk_entry_get_icon_area Ptr Entry
entry' CUInt
iconPos' Ptr Rectangle
iconArea
    Rectangle
iconArea' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Gdk.Rectangle.Rectangle) Ptr Rectangle
iconArea
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Rectangle -> IO Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
iconArea'
#if defined(ENABLE_OVERLOADING)
data EntryGetIconAreaMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> m (Gdk.Rectangle.Rectangle)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetIconAreaMethodInfo a signature where
    overloadedMethod = entryGetIconArea
instance O.OverloadedMethodInfo EntryGetIconAreaMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetIconArea",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetIconArea"
        }
#endif
foreign import ccall "gtk_entry_get_icon_at_pos" gtk_entry_get_icon_at_pos :: 
    Ptr Entry ->                            
    Int32 ->                                
    Int32 ->                                
    IO Int32
entryGetIconAtPos ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Int32
    
    -> Int32
    
    -> m Int32
    
entryGetIconAtPos :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Int32 -> Int32 -> m Int32
entryGetIconAtPos a
entry Int32
x Int32
y = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Int32
result <- Ptr Entry -> Int32 -> Int32 -> IO Int32
gtk_entry_get_icon_at_pos Ptr Entry
entry' Int32
x Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data EntryGetIconAtPosMethodInfo
instance (signature ~ (Int32 -> Int32 -> m Int32), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetIconAtPosMethodInfo a signature where
    overloadedMethod = entryGetIconAtPos
instance O.OverloadedMethodInfo EntryGetIconAtPosMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetIconAtPos",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetIconAtPos"
        }
#endif
foreign import ccall "gtk_entry_get_icon_gicon" gtk_entry_get_icon_gicon :: 
    Ptr Entry ->                            
    CUInt ->                                
    IO (Ptr Gio.Icon.Icon)
entryGetIconGicon ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> m (Maybe Gio.Icon.Icon)
    
    
entryGetIconGicon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> m (Maybe Icon)
entryGetIconGicon a
entry EntryIconPosition
iconPos = IO (Maybe Icon) -> m (Maybe Icon)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Icon) -> m (Maybe Icon))
-> IO (Maybe Icon) -> m (Maybe Icon)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    Ptr Icon
result <- Ptr Entry -> CUInt -> IO (Ptr Icon)
gtk_entry_get_icon_gicon Ptr Entry
entry' CUInt
iconPos'
    Maybe Icon
maybeResult <- Ptr Icon -> (Ptr Icon -> IO Icon) -> IO (Maybe Icon)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Icon
result ((Ptr Icon -> IO Icon) -> IO (Maybe Icon))
-> (Ptr Icon -> IO Icon) -> IO (Maybe Icon)
forall a b. (a -> b) -> a -> b
$ \Ptr Icon
result' -> do
        Icon
result'' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result'
        Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe Icon -> IO (Maybe Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Icon
maybeResult
#if defined(ENABLE_OVERLOADING)
data EntryGetIconGiconMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> m (Maybe Gio.Icon.Icon)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetIconGiconMethodInfo a signature where
    overloadedMethod = entryGetIconGicon
instance O.OverloadedMethodInfo EntryGetIconGiconMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetIconGicon",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetIconGicon"
        }
#endif
foreign import ccall "gtk_entry_get_icon_name" gtk_entry_get_icon_name :: 
    Ptr Entry ->                            
    CUInt ->                                
    IO CString
entryGetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> m (Maybe T.Text)
    
    
entryGetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> m (Maybe Text)
entryGetIconName a
entry EntryIconPosition
iconPos = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    CString
result <- Ptr Entry -> CUInt -> IO CString
gtk_entry_get_icon_name Ptr Entry
entry' CUInt
iconPos'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data EntryGetIconNameMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> m (Maybe T.Text)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetIconNameMethodInfo a signature where
    overloadedMethod = entryGetIconName
instance O.OverloadedMethodInfo EntryGetIconNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetIconName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetIconName"
        }
#endif
foreign import ccall "gtk_entry_get_icon_paintable" gtk_entry_get_icon_paintable :: 
    Ptr Entry ->                            
    CUInt ->                                
    IO (Ptr Gdk.Paintable.Paintable)
entryGetIconPaintable ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> m (Maybe Gdk.Paintable.Paintable)
    
    
entryGetIconPaintable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> m (Maybe Paintable)
entryGetIconPaintable a
entry EntryIconPosition
iconPos = IO (Maybe Paintable) -> m (Maybe Paintable)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Paintable) -> m (Maybe Paintable))
-> IO (Maybe Paintable) -> m (Maybe Paintable)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    Ptr Paintable
result <- Ptr Entry -> CUInt -> IO (Ptr Paintable)
gtk_entry_get_icon_paintable Ptr Entry
entry' CUInt
iconPos'
    Maybe Paintable
maybeResult <- Ptr Paintable
-> (Ptr Paintable -> IO Paintable) -> IO (Maybe Paintable)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Paintable
result ((Ptr Paintable -> IO Paintable) -> IO (Maybe Paintable))
-> (Ptr Paintable -> IO Paintable) -> IO (Maybe Paintable)
forall a b. (a -> b) -> a -> b
$ \Ptr Paintable
result' -> do
        Paintable
result'' <- ((ManagedPtr Paintable -> Paintable)
-> Ptr Paintable -> IO Paintable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Paintable -> Paintable
Gdk.Paintable.Paintable) Ptr Paintable
result'
        Paintable -> IO Paintable
forall (m :: * -> *) a. Monad m => a -> m a
return Paintable
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe Paintable -> IO (Maybe Paintable)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Paintable
maybeResult
#if defined(ENABLE_OVERLOADING)
data EntryGetIconPaintableMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> m (Maybe Gdk.Paintable.Paintable)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetIconPaintableMethodInfo a signature where
    overloadedMethod = entryGetIconPaintable
instance O.OverloadedMethodInfo EntryGetIconPaintableMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetIconPaintable",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetIconPaintable"
        }
#endif
foreign import ccall "gtk_entry_get_icon_sensitive" gtk_entry_get_icon_sensitive :: 
    Ptr Entry ->                            
    CUInt ->                                
    IO CInt
entryGetIconSensitive ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> m Bool
    
entryGetIconSensitive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> m Bool
entryGetIconSensitive a
entry EntryIconPosition
iconPos = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    CInt
result <- Ptr Entry -> CUInt -> IO CInt
gtk_entry_get_icon_sensitive Ptr Entry
entry' CUInt
iconPos'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetIconSensitiveMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> m Bool), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetIconSensitiveMethodInfo a signature where
    overloadedMethod = entryGetIconSensitive
instance O.OverloadedMethodInfo EntryGetIconSensitiveMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetIconSensitive",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetIconSensitive"
        }
#endif
foreign import ccall "gtk_entry_get_icon_storage_type" gtk_entry_get_icon_storage_type :: 
    Ptr Entry ->                            
    CUInt ->                                
    IO CUInt
entryGetIconStorageType ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> m Gtk.Enums.ImageType
    
entryGetIconStorageType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> m ImageType
entryGetIconStorageType a
entry EntryIconPosition
iconPos = IO ImageType -> m ImageType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ImageType -> m ImageType) -> IO ImageType -> m ImageType
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    CUInt
result <- Ptr Entry -> CUInt -> IO CUInt
gtk_entry_get_icon_storage_type Ptr Entry
entry' CUInt
iconPos'
    let result' :: ImageType
result' = (Int -> ImageType
forall a. Enum a => Int -> a
toEnum (Int -> ImageType) -> (CUInt -> Int) -> CUInt -> ImageType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    ImageType -> IO ImageType
forall (m :: * -> *) a. Monad m => a -> m a
return ImageType
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetIconStorageTypeMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> m Gtk.Enums.ImageType), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetIconStorageTypeMethodInfo a signature where
    overloadedMethod = entryGetIconStorageType
instance O.OverloadedMethodInfo EntryGetIconStorageTypeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetIconStorageType",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetIconStorageType"
        }
#endif
foreign import ccall "gtk_entry_get_icon_tooltip_markup" gtk_entry_get_icon_tooltip_markup :: 
    Ptr Entry ->                            
    CUInt ->                                
    IO CString
entryGetIconTooltipMarkup ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> m (Maybe T.Text)
    
    
entryGetIconTooltipMarkup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> m (Maybe Text)
entryGetIconTooltipMarkup a
entry EntryIconPosition
iconPos = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    CString
result <- Ptr Entry -> CUInt -> IO CString
gtk_entry_get_icon_tooltip_markup Ptr Entry
entry' CUInt
iconPos'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data EntryGetIconTooltipMarkupMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> m (Maybe T.Text)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetIconTooltipMarkupMethodInfo a signature where
    overloadedMethod = entryGetIconTooltipMarkup
instance O.OverloadedMethodInfo EntryGetIconTooltipMarkupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetIconTooltipMarkup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetIconTooltipMarkup"
        }
#endif
foreign import ccall "gtk_entry_get_icon_tooltip_text" gtk_entry_get_icon_tooltip_text :: 
    Ptr Entry ->                            
    CUInt ->                                
    IO CString
entryGetIconTooltipText ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> m (Maybe T.Text)
    
    
entryGetIconTooltipText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> m (Maybe Text)
entryGetIconTooltipText a
entry EntryIconPosition
iconPos = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    CString
result <- Ptr Entry -> CUInt -> IO CString
gtk_entry_get_icon_tooltip_text Ptr Entry
entry' CUInt
iconPos'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data EntryGetIconTooltipTextMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> m (Maybe T.Text)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetIconTooltipTextMethodInfo a signature where
    overloadedMethod = entryGetIconTooltipText
instance O.OverloadedMethodInfo EntryGetIconTooltipTextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetIconTooltipText",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetIconTooltipText"
        }
#endif
foreign import ccall "gtk_entry_get_input_hints" gtk_entry_get_input_hints :: 
    Ptr Entry ->                            
    IO CUInt
entryGetInputHints ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m [Gtk.Flags.InputHints]
entryGetInputHints :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m [InputHints]
entryGetInputHints a
entry = IO [InputHints] -> m [InputHints]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [InputHints] -> m [InputHints])
-> IO [InputHints] -> m [InputHints]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CUInt
result <- Ptr Entry -> IO CUInt
gtk_entry_get_input_hints Ptr Entry
entry'
    let result' :: [InputHints]
result' = CUInt -> [InputHints]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    [InputHints] -> IO [InputHints]
forall (m :: * -> *) a. Monad m => a -> m a
return [InputHints]
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetInputHintsMethodInfo
instance (signature ~ (m [Gtk.Flags.InputHints]), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetInputHintsMethodInfo a signature where
    overloadedMethod = entryGetInputHints
instance O.OverloadedMethodInfo EntryGetInputHintsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetInputHints",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetInputHints"
        }
#endif
foreign import ccall "gtk_entry_get_input_purpose" gtk_entry_get_input_purpose :: 
    Ptr Entry ->                            
    IO CUInt
entryGetInputPurpose ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Gtk.Enums.InputPurpose
entryGetInputPurpose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m InputPurpose
entryGetInputPurpose a
entry = IO InputPurpose -> m InputPurpose
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputPurpose -> m InputPurpose)
-> IO InputPurpose -> m InputPurpose
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CUInt
result <- Ptr Entry -> IO CUInt
gtk_entry_get_input_purpose Ptr Entry
entry'
    let result' :: InputPurpose
result' = (Int -> InputPurpose
forall a. Enum a => Int -> a
toEnum (Int -> InputPurpose) -> (CUInt -> Int) -> CUInt -> InputPurpose
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    InputPurpose -> IO InputPurpose
forall (m :: * -> *) a. Monad m => a -> m a
return InputPurpose
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetInputPurposeMethodInfo
instance (signature ~ (m Gtk.Enums.InputPurpose), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetInputPurposeMethodInfo a signature where
    overloadedMethod = entryGetInputPurpose
instance O.OverloadedMethodInfo EntryGetInputPurposeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetInputPurpose",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetInputPurpose"
        }
#endif
foreign import ccall "gtk_entry_get_invisible_char" gtk_entry_get_invisible_char :: 
    Ptr Entry ->                            
    IO CInt
entryGetInvisibleChar ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Char
    
    
entryGetInvisibleChar :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Char
entryGetInvisibleChar a
entry = IO Char -> m Char
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Char -> m Char) -> IO Char -> m Char
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CInt
result <- Ptr Entry -> IO CInt
gtk_entry_get_invisible_char Ptr Entry
entry'
    let result' :: Char
result' = (Int -> Char
chr (Int -> Char) -> (CInt -> Int) -> CInt -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Char -> IO Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetInvisibleCharMethodInfo
instance (signature ~ (m Char), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetInvisibleCharMethodInfo a signature where
    overloadedMethod = entryGetInvisibleChar
instance O.OverloadedMethodInfo EntryGetInvisibleCharMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetInvisibleChar",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetInvisibleChar"
        }
#endif
foreign import ccall "gtk_entry_get_max_length" gtk_entry_get_max_length :: 
    Ptr Entry ->                            
    IO Int32
entryGetMaxLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Int32
    
    
entryGetMaxLength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Int32
entryGetMaxLength a
entry = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Int32
result <- Ptr Entry -> IO Int32
gtk_entry_get_max_length Ptr Entry
entry'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data EntryGetMaxLengthMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetMaxLengthMethodInfo a signature where
    overloadedMethod = entryGetMaxLength
instance O.OverloadedMethodInfo EntryGetMaxLengthMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetMaxLength",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetMaxLength"
        }
#endif
foreign import ccall "gtk_entry_get_overwrite_mode" gtk_entry_get_overwrite_mode :: 
    Ptr Entry ->                            
    IO CInt
entryGetOverwriteMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Bool
    
entryGetOverwriteMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Bool
entryGetOverwriteMode a
entry = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CInt
result <- Ptr Entry -> IO CInt
gtk_entry_get_overwrite_mode Ptr Entry
entry'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetOverwriteModeMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetOverwriteModeMethodInfo a signature where
    overloadedMethod = entryGetOverwriteMode
instance O.OverloadedMethodInfo EntryGetOverwriteModeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetOverwriteMode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetOverwriteMode"
        }
#endif
foreign import ccall "gtk_entry_get_placeholder_text" gtk_entry_get_placeholder_text :: 
    Ptr Entry ->                            
    IO CString
entryGetPlaceholderText ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m (Maybe T.Text)
    
    
    
    
entryGetPlaceholderText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m (Maybe Text)
entryGetPlaceholderText a
entry = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CString
result <- Ptr Entry -> IO CString
gtk_entry_get_placeholder_text Ptr Entry
entry'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data EntryGetPlaceholderTextMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetPlaceholderTextMethodInfo a signature where
    overloadedMethod = entryGetPlaceholderText
instance O.OverloadedMethodInfo EntryGetPlaceholderTextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetPlaceholderText",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetPlaceholderText"
        }
#endif
foreign import ccall "gtk_entry_get_progress_fraction" gtk_entry_get_progress_fraction :: 
    Ptr Entry ->                            
    IO CDouble
entryGetProgressFraction ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Double
    
entryGetProgressFraction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Double
entryGetProgressFraction a
entry = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CDouble
result <- Ptr Entry -> IO CDouble
gtk_entry_get_progress_fraction Ptr Entry
entry'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetProgressFractionMethodInfo
instance (signature ~ (m Double), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetProgressFractionMethodInfo a signature where
    overloadedMethod = entryGetProgressFraction
instance O.OverloadedMethodInfo EntryGetProgressFractionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetProgressFraction",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetProgressFraction"
        }
#endif
foreign import ccall "gtk_entry_get_progress_pulse_step" gtk_entry_get_progress_pulse_step :: 
    Ptr Entry ->                            
    IO CDouble
entryGetProgressPulseStep ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Double
    
entryGetProgressPulseStep :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Double
entryGetProgressPulseStep a
entry = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CDouble
result <- Ptr Entry -> IO CDouble
gtk_entry_get_progress_pulse_step Ptr Entry
entry'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetProgressPulseStepMethodInfo
instance (signature ~ (m Double), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetProgressPulseStepMethodInfo a signature where
    overloadedMethod = entryGetProgressPulseStep
instance O.OverloadedMethodInfo EntryGetProgressPulseStepMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetProgressPulseStep",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetProgressPulseStep"
        }
#endif
foreign import ccall "gtk_entry_get_tabs" gtk_entry_get_tabs :: 
    Ptr Entry ->                            
    IO (Ptr Pango.TabArray.TabArray)
entryGetTabs ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m (Maybe Pango.TabArray.TabArray)
    
entryGetTabs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m (Maybe TabArray)
entryGetTabs a
entry = IO (Maybe TabArray) -> m (Maybe TabArray)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TabArray) -> m (Maybe TabArray))
-> IO (Maybe TabArray) -> m (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr TabArray
result <- Ptr Entry -> IO (Ptr TabArray)
gtk_entry_get_tabs Ptr Entry
entry'
    Maybe TabArray
maybeResult <- Ptr TabArray
-> (Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TabArray
result ((Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray))
-> (Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ \Ptr TabArray
result' -> do
        TabArray
result'' <- ((ManagedPtr TabArray -> TabArray) -> Ptr TabArray -> IO TabArray
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr TabArray -> TabArray
Pango.TabArray.TabArray) Ptr TabArray
result'
        TabArray -> IO TabArray
forall (m :: * -> *) a. Monad m => a -> m a
return TabArray
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe TabArray -> IO (Maybe TabArray)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TabArray
maybeResult
#if defined(ENABLE_OVERLOADING)
data EntryGetTabsMethodInfo
instance (signature ~ (m (Maybe Pango.TabArray.TabArray)), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetTabsMethodInfo a signature where
    overloadedMethod = entryGetTabs
instance O.OverloadedMethodInfo EntryGetTabsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetTabs",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetTabs"
        }
#endif
foreign import ccall "gtk_entry_get_text_length" gtk_entry_get_text_length :: 
    Ptr Entry ->                            
    IO Word16
entryGetTextLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Word16
    
    
entryGetTextLength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Word16
entryGetTextLength a
entry = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Word16
result <- Ptr Entry -> IO Word16
gtk_entry_get_text_length Ptr Entry
entry'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
result
#if defined(ENABLE_OVERLOADING)
data EntryGetTextLengthMethodInfo
instance (signature ~ (m Word16), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetTextLengthMethodInfo a signature where
    overloadedMethod = entryGetTextLength
instance O.OverloadedMethodInfo EntryGetTextLengthMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetTextLength",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetTextLength"
        }
#endif
foreign import ccall "gtk_entry_get_visibility" gtk_entry_get_visibility :: 
    Ptr Entry ->                            
    IO CInt
entryGetVisibility ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Bool
    
entryGetVisibility :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Bool
entryGetVisibility a
entry = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CInt
result <- Ptr Entry -> IO CInt
gtk_entry_get_visibility Ptr Entry
entry'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data EntryGetVisibilityMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGetVisibilityMethodInfo a signature where
    overloadedMethod = entryGetVisibility
instance O.OverloadedMethodInfo EntryGetVisibilityMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGetVisibility",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGetVisibility"
        }
#endif
foreign import ccall "gtk_entry_grab_focus_without_selecting" gtk_entry_grab_focus_without_selecting :: 
    Ptr Entry ->                            
    IO CInt
entryGrabFocusWithoutSelecting ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m Bool
    
entryGrabFocusWithoutSelecting :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m Bool
entryGrabFocusWithoutSelecting a
entry = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CInt
result <- Ptr Entry -> IO CInt
gtk_entry_grab_focus_without_selecting Ptr Entry
entry'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data EntryGrabFocusWithoutSelectingMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsEntry a) => O.OverloadedMethod EntryGrabFocusWithoutSelectingMethodInfo a signature where
    overloadedMethod = entryGrabFocusWithoutSelecting
instance O.OverloadedMethodInfo EntryGrabFocusWithoutSelectingMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryGrabFocusWithoutSelecting",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryGrabFocusWithoutSelecting"
        }
#endif
foreign import ccall "gtk_entry_progress_pulse" gtk_entry_progress_pulse :: 
    Ptr Entry ->                            
    IO ()
entryProgressPulse ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m ()
entryProgressPulse :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m ()
entryProgressPulse a
entry = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr Entry -> IO ()
gtk_entry_progress_pulse Ptr Entry
entry'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntryProgressPulseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntryProgressPulseMethodInfo a signature where
    overloadedMethod = entryProgressPulse
instance O.OverloadedMethodInfo EntryProgressPulseMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryProgressPulse",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryProgressPulse"
        }
#endif
foreign import ccall "gtk_entry_reset_im_context" gtk_entry_reset_im_context :: 
    Ptr Entry ->                            
    IO ()
entryResetImContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m ()
entryResetImContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m ()
entryResetImContext a
entry = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr Entry -> IO ()
gtk_entry_reset_im_context Ptr Entry
entry'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntryResetImContextMethodInfo
instance (signature ~ (m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntryResetImContextMethodInfo a signature where
    overloadedMethod = entryResetImContext
instance O.OverloadedMethodInfo EntryResetImContextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryResetImContext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryResetImContext"
        }
#endif
foreign import ccall "gtk_entry_set_activates_default" gtk_entry_set_activates_default :: 
    Ptr Entry ->                            
    CInt ->                                 
    IO ()
entrySetActivatesDefault ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Bool
    
    -> m ()
entrySetActivatesDefault :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Bool -> m ()
entrySetActivatesDefault a
entry Bool
setting = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let setting' :: CInt
setting' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
setting
    Ptr Entry -> CInt -> IO ()
gtk_entry_set_activates_default Ptr Entry
entry' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetActivatesDefaultMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetActivatesDefaultMethodInfo a signature where
    overloadedMethod = entrySetActivatesDefault
instance O.OverloadedMethodInfo EntrySetActivatesDefaultMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetActivatesDefault",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetActivatesDefault"
        }
#endif
foreign import ccall "gtk_entry_set_alignment" gtk_entry_set_alignment :: 
    Ptr Entry ->                            
    CFloat ->                               
    IO ()
entrySetAlignment ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Float
    
    
    -> m ()
entrySetAlignment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Float -> m ()
entrySetAlignment a
entry Float
xalign = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let xalign' :: CFloat
xalign' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
xalign
    Ptr Entry -> CFloat -> IO ()
gtk_entry_set_alignment Ptr Entry
entry' CFloat
xalign'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetAlignmentMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetAlignmentMethodInfo a signature where
    overloadedMethod = entrySetAlignment
instance O.OverloadedMethodInfo EntrySetAlignmentMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetAlignment",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetAlignment"
        }
#endif
foreign import ccall "gtk_entry_set_attributes" gtk_entry_set_attributes :: 
    Ptr Entry ->                            
    Ptr Pango.AttrList.AttrList ->          
    IO ()
entrySetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Pango.AttrList.AttrList
    
    -> m ()
entrySetAttributes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> AttrList -> m ()
entrySetAttributes a
entry AttrList
attrs = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr AttrList
attrs' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
attrs
    Ptr Entry -> Ptr AttrList -> IO ()
gtk_entry_set_attributes Ptr Entry
entry' Ptr AttrList
attrs'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
attrs
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetAttributesMethodInfo
instance (signature ~ (Pango.AttrList.AttrList -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetAttributesMethodInfo a signature where
    overloadedMethod = entrySetAttributes
instance O.OverloadedMethodInfo EntrySetAttributesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetAttributes",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetAttributes"
        }
#endif
foreign import ccall "gtk_entry_set_buffer" gtk_entry_set_buffer :: 
    Ptr Entry ->                            
    Ptr Gtk.EntryBuffer.EntryBuffer ->      
    IO ()
entrySetBuffer ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a, Gtk.EntryBuffer.IsEntryBuffer b) =>
    a
    
    -> b
    
    -> m ()
entrySetBuffer :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsEntry a, IsEntryBuffer b) =>
a -> b -> m ()
entrySetBuffer a
entry b
buffer = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr EntryBuffer
buffer' <- b -> IO (Ptr EntryBuffer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
buffer
    Ptr Entry -> Ptr EntryBuffer -> IO ()
gtk_entry_set_buffer Ptr Entry
entry' Ptr EntryBuffer
buffer'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
buffer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetBufferMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsEntry a, Gtk.EntryBuffer.IsEntryBuffer b) => O.OverloadedMethod EntrySetBufferMethodInfo a signature where
    overloadedMethod = entrySetBuffer
instance O.OverloadedMethodInfo EntrySetBufferMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetBuffer",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetBuffer"
        }
#endif
foreign import ccall "gtk_entry_set_completion" gtk_entry_set_completion :: 
    Ptr Entry ->                            
    Ptr Gtk.EntryCompletion.EntryCompletion -> 
    IO ()
entrySetCompletion ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a, Gtk.EntryCompletion.IsEntryCompletion b) =>
    a
    
    -> Maybe (b)
    
    -> m ()
entrySetCompletion :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsEntry a, IsEntryCompletion b) =>
a -> Maybe b -> m ()
entrySetCompletion a
entry Maybe b
completion = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr EntryCompletion
maybeCompletion <- case Maybe b
completion of
        Maybe b
Nothing -> Ptr EntryCompletion -> IO (Ptr EntryCompletion)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr EntryCompletion
forall a. Ptr a
nullPtr
        Just b
jCompletion -> do
            Ptr EntryCompletion
jCompletion' <- b -> IO (Ptr EntryCompletion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCompletion
            Ptr EntryCompletion -> IO (Ptr EntryCompletion)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr EntryCompletion
jCompletion'
    Ptr Entry -> Ptr EntryCompletion -> IO ()
gtk_entry_set_completion Ptr Entry
entry' Ptr EntryCompletion
maybeCompletion
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
completion b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetCompletionMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsEntry a, Gtk.EntryCompletion.IsEntryCompletion b) => O.OverloadedMethod EntrySetCompletionMethodInfo a signature where
    overloadedMethod = entrySetCompletion
instance O.OverloadedMethodInfo EntrySetCompletionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetCompletion",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetCompletion"
        }
#endif
foreign import ccall "gtk_entry_set_extra_menu"  :: 
    Ptr Entry ->                            
    Ptr Gio.MenuModel.MenuModel ->          
    IO ()
entrySetExtraMenu ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a, Gio.MenuModel.IsMenuModel b) =>
    a
    
    -> Maybe (b)
    
    -> m ()
 a
entry Maybe b
model = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr MenuModel
maybeModel <- case Maybe b
model of
        Maybe b
Nothing -> Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
forall a. Ptr a
nullPtr
        Just b
jModel -> do
            Ptr MenuModel
jModel' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
            Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
jModel'
    Ptr Entry -> Ptr MenuModel -> IO ()
gtk_entry_set_extra_menu Ptr Entry
entry' Ptr MenuModel
maybeModel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
model b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetExtraMenuMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsEntry a, Gio.MenuModel.IsMenuModel b) => O.OverloadedMethod EntrySetExtraMenuMethodInfo a signature where
    overloadedMethod = entrySetExtraMenu
instance O.OverloadedMethodInfo EntrySetExtraMenuMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetExtraMenu",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetExtraMenu"
        }
#endif
foreign import ccall "gtk_entry_set_has_frame" gtk_entry_set_has_frame :: 
    Ptr Entry ->                            
    CInt ->                                 
    IO ()
entrySetHasFrame ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Bool
    
    -> m ()
entrySetHasFrame :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Bool -> m ()
entrySetHasFrame a
entry Bool
setting = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let setting' :: CInt
setting' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
setting
    Ptr Entry -> CInt -> IO ()
gtk_entry_set_has_frame Ptr Entry
entry' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetHasFrameMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetHasFrameMethodInfo a signature where
    overloadedMethod = entrySetHasFrame
instance O.OverloadedMethodInfo EntrySetHasFrameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetHasFrame",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetHasFrame"
        }
#endif
foreign import ccall "gtk_entry_set_icon_activatable" gtk_entry_set_icon_activatable :: 
    Ptr Entry ->                            
    CUInt ->                                
    CInt ->                                 
    IO ()
entrySetIconActivatable ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> Bool
    
    -> m ()
entrySetIconActivatable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> Bool -> m ()
entrySetIconActivatable a
entry EntryIconPosition
iconPos Bool
activatable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    let activatable' :: CInt
activatable' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
activatable
    Ptr Entry -> CUInt -> CInt -> IO ()
gtk_entry_set_icon_activatable Ptr Entry
entry' CUInt
iconPos' CInt
activatable'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetIconActivatableMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> Bool -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetIconActivatableMethodInfo a signature where
    overloadedMethod = entrySetIconActivatable
instance O.OverloadedMethodInfo EntrySetIconActivatableMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetIconActivatable",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetIconActivatable"
        }
#endif
foreign import ccall "gtk_entry_set_icon_drag_source" gtk_entry_set_icon_drag_source :: 
    Ptr Entry ->                            
    CUInt ->                                
    Ptr Gdk.ContentProvider.ContentProvider -> 
    CUInt ->                                
    IO ()
entrySetIconDragSource ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a, Gdk.ContentProvider.IsContentProvider b) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> b
    
    -> [Gdk.Flags.DragAction]
    
    -> m ()
entrySetIconDragSource :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsEntry a, IsContentProvider b) =>
a -> EntryIconPosition -> b -> [DragAction] -> m ()
entrySetIconDragSource a
entry EntryIconPosition
iconPos b
provider [DragAction]
actions = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    Ptr ContentProvider
provider' <- b -> IO (Ptr ContentProvider)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
provider
    let actions' :: CUInt
actions' = [DragAction] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DragAction]
actions
    Ptr Entry -> CUInt -> Ptr ContentProvider -> CUInt -> IO ()
gtk_entry_set_icon_drag_source Ptr Entry
entry' CUInt
iconPos' Ptr ContentProvider
provider' CUInt
actions'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
provider
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetIconDragSourceMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> b -> [Gdk.Flags.DragAction] -> m ()), MonadIO m, IsEntry a, Gdk.ContentProvider.IsContentProvider b) => O.OverloadedMethod EntrySetIconDragSourceMethodInfo a signature where
    overloadedMethod = entrySetIconDragSource
instance O.OverloadedMethodInfo EntrySetIconDragSourceMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetIconDragSource",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetIconDragSource"
        }
#endif
foreign import ccall "gtk_entry_set_icon_from_gicon" gtk_entry_set_icon_from_gicon :: 
    Ptr Entry ->                            
    CUInt ->                                
    Ptr Gio.Icon.Icon ->                    
    IO ()
entrySetIconFromGicon ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a, Gio.Icon.IsIcon b) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> Maybe (b)
    
    -> m ()
entrySetIconFromGicon :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsEntry a, IsIcon b) =>
a -> EntryIconPosition -> Maybe b -> m ()
entrySetIconFromGicon a
entry EntryIconPosition
iconPos Maybe b
icon = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    Ptr Icon
maybeIcon <- case Maybe b
icon of
        Maybe b
Nothing -> Ptr Icon -> IO (Ptr Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
forall a. Ptr a
nullPtr
        Just b
jIcon -> do
            Ptr Icon
jIcon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jIcon
            Ptr Icon -> IO (Ptr Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
jIcon'
    Ptr Entry -> CUInt -> Ptr Icon -> IO ()
gtk_entry_set_icon_from_gicon Ptr Entry
entry' CUInt
iconPos' Ptr Icon
maybeIcon
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
icon b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetIconFromGiconMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> Maybe (b) -> m ()), MonadIO m, IsEntry a, Gio.Icon.IsIcon b) => O.OverloadedMethod EntrySetIconFromGiconMethodInfo a signature where
    overloadedMethod = entrySetIconFromGicon
instance O.OverloadedMethodInfo EntrySetIconFromGiconMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetIconFromGicon",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetIconFromGicon"
        }
#endif
foreign import ccall "gtk_entry_set_icon_from_icon_name" gtk_entry_set_icon_from_icon_name :: 
    Ptr Entry ->                            
    CUInt ->                                
    CString ->                              
    IO ()
entrySetIconFromIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> Maybe (T.Text)
    
    -> m ()
entrySetIconFromIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> Maybe Text -> m ()
entrySetIconFromIconName a
entry EntryIconPosition
iconPos Maybe Text
iconName = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    CString
maybeIconName <- case Maybe Text
iconName of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jIconName -> do
            CString
jIconName' <- Text -> IO CString
textToCString Text
jIconName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jIconName'
    Ptr Entry -> CUInt -> CString -> IO ()
gtk_entry_set_icon_from_icon_name Ptr Entry
entry' CUInt
iconPos' CString
maybeIconName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeIconName
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetIconFromIconNameMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> Maybe (T.Text) -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetIconFromIconNameMethodInfo a signature where
    overloadedMethod = entrySetIconFromIconName
instance O.OverloadedMethodInfo EntrySetIconFromIconNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetIconFromIconName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetIconFromIconName"
        }
#endif
foreign import ccall "gtk_entry_set_icon_from_paintable" gtk_entry_set_icon_from_paintable :: 
    Ptr Entry ->                            
    CUInt ->                                
    Ptr Gdk.Paintable.Paintable ->          
    IO ()
entrySetIconFromPaintable ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a, Gdk.Paintable.IsPaintable b) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> Maybe (b)
    
    -> m ()
entrySetIconFromPaintable :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsEntry a, IsPaintable b) =>
a -> EntryIconPosition -> Maybe b -> m ()
entrySetIconFromPaintable a
entry EntryIconPosition
iconPos Maybe b
paintable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    Ptr Paintable
maybePaintable <- case Maybe b
paintable of
        Maybe b
Nothing -> Ptr Paintable -> IO (Ptr Paintable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Paintable
forall a. Ptr a
nullPtr
        Just b
jPaintable -> do
            Ptr Paintable
jPaintable' <- b -> IO (Ptr Paintable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jPaintable
            Ptr Paintable -> IO (Ptr Paintable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Paintable
jPaintable'
    Ptr Entry -> CUInt -> Ptr Paintable -> IO ()
gtk_entry_set_icon_from_paintable Ptr Entry
entry' CUInt
iconPos' Ptr Paintable
maybePaintable
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
paintable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetIconFromPaintableMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> Maybe (b) -> m ()), MonadIO m, IsEntry a, Gdk.Paintable.IsPaintable b) => O.OverloadedMethod EntrySetIconFromPaintableMethodInfo a signature where
    overloadedMethod = entrySetIconFromPaintable
instance O.OverloadedMethodInfo EntrySetIconFromPaintableMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetIconFromPaintable",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetIconFromPaintable"
        }
#endif
foreign import ccall "gtk_entry_set_icon_sensitive" gtk_entry_set_icon_sensitive :: 
    Ptr Entry ->                            
    CUInt ->                                
    CInt ->                                 
    IO ()
entrySetIconSensitive ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> Bool
    
    
    -> m ()
entrySetIconSensitive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> Bool -> m ()
entrySetIconSensitive a
entry EntryIconPosition
iconPos Bool
sensitive = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    let sensitive' :: CInt
sensitive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
sensitive
    Ptr Entry -> CUInt -> CInt -> IO ()
gtk_entry_set_icon_sensitive Ptr Entry
entry' CUInt
iconPos' CInt
sensitive'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetIconSensitiveMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> Bool -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetIconSensitiveMethodInfo a signature where
    overloadedMethod = entrySetIconSensitive
instance O.OverloadedMethodInfo EntrySetIconSensitiveMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetIconSensitive",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetIconSensitive"
        }
#endif
foreign import ccall "gtk_entry_set_icon_tooltip_markup" gtk_entry_set_icon_tooltip_markup :: 
    Ptr Entry ->                            
    CUInt ->                                
    CString ->                              
    IO ()
entrySetIconTooltipMarkup ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> Maybe (T.Text)
    
    -> m ()
entrySetIconTooltipMarkup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> Maybe Text -> m ()
entrySetIconTooltipMarkup a
entry EntryIconPosition
iconPos Maybe Text
tooltip = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    CString
maybeTooltip <- case Maybe Text
tooltip of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jTooltip -> do
            CString
jTooltip' <- Text -> IO CString
textToCString Text
jTooltip
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jTooltip'
    Ptr Entry -> CUInt -> CString -> IO ()
gtk_entry_set_icon_tooltip_markup Ptr Entry
entry' CUInt
iconPos' CString
maybeTooltip
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeTooltip
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetIconTooltipMarkupMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> Maybe (T.Text) -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetIconTooltipMarkupMethodInfo a signature where
    overloadedMethod = entrySetIconTooltipMarkup
instance O.OverloadedMethodInfo EntrySetIconTooltipMarkupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetIconTooltipMarkup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetIconTooltipMarkup"
        }
#endif
foreign import ccall "gtk_entry_set_icon_tooltip_text" gtk_entry_set_icon_tooltip_text :: 
    Ptr Entry ->                            
    CUInt ->                                
    CString ->                              
    IO ()
entrySetIconTooltipText ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.EntryIconPosition
    
    -> Maybe (T.Text)
    
    -> m ()
entrySetIconTooltipText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> EntryIconPosition -> Maybe Text -> m ()
entrySetIconTooltipText a
entry EntryIconPosition
iconPos Maybe Text
tooltip = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let iconPos' :: CUInt
iconPos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (EntryIconPosition -> Int) -> EntryIconPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntryIconPosition -> Int
forall a. Enum a => a -> Int
fromEnum) EntryIconPosition
iconPos
    CString
maybeTooltip <- case Maybe Text
tooltip of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jTooltip -> do
            CString
jTooltip' <- Text -> IO CString
textToCString Text
jTooltip
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jTooltip'
    Ptr Entry -> CUInt -> CString -> IO ()
gtk_entry_set_icon_tooltip_text Ptr Entry
entry' CUInt
iconPos' CString
maybeTooltip
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeTooltip
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetIconTooltipTextMethodInfo
instance (signature ~ (Gtk.Enums.EntryIconPosition -> Maybe (T.Text) -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetIconTooltipTextMethodInfo a signature where
    overloadedMethod = entrySetIconTooltipText
instance O.OverloadedMethodInfo EntrySetIconTooltipTextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetIconTooltipText",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetIconTooltipText"
        }
#endif
foreign import ccall "gtk_entry_set_input_hints" gtk_entry_set_input_hints :: 
    Ptr Entry ->                            
    CUInt ->                                
    IO ()
entrySetInputHints ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> [Gtk.Flags.InputHints]
    
    -> m ()
entrySetInputHints :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> [InputHints] -> m ()
entrySetInputHints a
entry [InputHints]
hints = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let hints' :: CUInt
hints' = [InputHints] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [InputHints]
hints
    Ptr Entry -> CUInt -> IO ()
gtk_entry_set_input_hints Ptr Entry
entry' CUInt
hints'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetInputHintsMethodInfo
instance (signature ~ ([Gtk.Flags.InputHints] -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetInputHintsMethodInfo a signature where
    overloadedMethod = entrySetInputHints
instance O.OverloadedMethodInfo EntrySetInputHintsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetInputHints",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetInputHints"
        }
#endif
foreign import ccall "gtk_entry_set_input_purpose" gtk_entry_set_input_purpose :: 
    Ptr Entry ->                            
    CUInt ->                                
    IO ()
entrySetInputPurpose ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Gtk.Enums.InputPurpose
    
    -> m ()
entrySetInputPurpose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> InputPurpose -> m ()
entrySetInputPurpose a
entry InputPurpose
purpose = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let purpose' :: CUInt
purpose' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (InputPurpose -> Int) -> InputPurpose -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputPurpose -> Int
forall a. Enum a => a -> Int
fromEnum) InputPurpose
purpose
    Ptr Entry -> CUInt -> IO ()
gtk_entry_set_input_purpose Ptr Entry
entry' CUInt
purpose'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetInputPurposeMethodInfo
instance (signature ~ (Gtk.Enums.InputPurpose -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetInputPurposeMethodInfo a signature where
    overloadedMethod = entrySetInputPurpose
instance O.OverloadedMethodInfo EntrySetInputPurposeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetInputPurpose",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetInputPurpose"
        }
#endif
foreign import ccall "gtk_entry_set_invisible_char" gtk_entry_set_invisible_char :: 
    Ptr Entry ->                            
    CInt ->                                 
    IO ()
entrySetInvisibleChar ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Char
    
    -> m ()
entrySetInvisibleChar :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Char -> m ()
entrySetInvisibleChar a
entry Char
ch = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let ch' :: CInt
ch' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Char -> Int) -> Char -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord) Char
ch
    Ptr Entry -> CInt -> IO ()
gtk_entry_set_invisible_char Ptr Entry
entry' CInt
ch'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetInvisibleCharMethodInfo
instance (signature ~ (Char -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetInvisibleCharMethodInfo a signature where
    overloadedMethod = entrySetInvisibleChar
instance O.OverloadedMethodInfo EntrySetInvisibleCharMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetInvisibleChar",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetInvisibleChar"
        }
#endif
foreign import ccall "gtk_entry_set_max_length" gtk_entry_set_max_length :: 
    Ptr Entry ->                            
    Int32 ->                                
    IO ()
entrySetMaxLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Int32
    
    
    
    -> m ()
entrySetMaxLength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Int32 -> m ()
entrySetMaxLength a
entry Int32
max = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr Entry -> Int32 -> IO ()
gtk_entry_set_max_length Ptr Entry
entry' Int32
max
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetMaxLengthMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetMaxLengthMethodInfo a signature where
    overloadedMethod = entrySetMaxLength
instance O.OverloadedMethodInfo EntrySetMaxLengthMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetMaxLength",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetMaxLength"
        }
#endif
foreign import ccall "gtk_entry_set_overwrite_mode" gtk_entry_set_overwrite_mode :: 
    Ptr Entry ->                            
    CInt ->                                 
    IO ()
entrySetOverwriteMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Bool
    
    -> m ()
entrySetOverwriteMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Bool -> m ()
entrySetOverwriteMode a
entry Bool
overwrite = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let overwrite' :: CInt
overwrite' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
overwrite
    Ptr Entry -> CInt -> IO ()
gtk_entry_set_overwrite_mode Ptr Entry
entry' CInt
overwrite'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetOverwriteModeMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetOverwriteModeMethodInfo a signature where
    overloadedMethod = entrySetOverwriteMode
instance O.OverloadedMethodInfo EntrySetOverwriteModeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetOverwriteMode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetOverwriteMode"
        }
#endif
foreign import ccall "gtk_entry_set_placeholder_text" gtk_entry_set_placeholder_text :: 
    Ptr Entry ->                            
    CString ->                              
    IO ()
entrySetPlaceholderText ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Maybe (T.Text)
    
    -> m ()
entrySetPlaceholderText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Maybe Text -> m ()
entrySetPlaceholderText a
entry Maybe Text
text = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    CString
maybeText <- case Maybe Text
text of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jText -> do
            CString
jText' <- Text -> IO CString
textToCString Text
jText
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jText'
    Ptr Entry -> CString -> IO ()
gtk_entry_set_placeholder_text Ptr Entry
entry' CString
maybeText
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeText
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetPlaceholderTextMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetPlaceholderTextMethodInfo a signature where
    overloadedMethod = entrySetPlaceholderText
instance O.OverloadedMethodInfo EntrySetPlaceholderTextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetPlaceholderText",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetPlaceholderText"
        }
#endif
foreign import ccall "gtk_entry_set_progress_fraction" gtk_entry_set_progress_fraction :: 
    Ptr Entry ->                            
    CDouble ->                              
    IO ()
entrySetProgressFraction ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Double
    
    -> m ()
entrySetProgressFraction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Double -> m ()
entrySetProgressFraction a
entry Double
fraction = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let fraction' :: CDouble
fraction' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
fraction
    Ptr Entry -> CDouble -> IO ()
gtk_entry_set_progress_fraction Ptr Entry
entry' CDouble
fraction'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetProgressFractionMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetProgressFractionMethodInfo a signature where
    overloadedMethod = entrySetProgressFraction
instance O.OverloadedMethodInfo EntrySetProgressFractionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetProgressFraction",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetProgressFraction"
        }
#endif
foreign import ccall "gtk_entry_set_progress_pulse_step" gtk_entry_set_progress_pulse_step :: 
    Ptr Entry ->                            
    CDouble ->                              
    IO ()
entrySetProgressPulseStep ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Double
    
    -> m ()
entrySetProgressPulseStep :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Double -> m ()
entrySetProgressPulseStep a
entry Double
fraction = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let fraction' :: CDouble
fraction' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
fraction
    Ptr Entry -> CDouble -> IO ()
gtk_entry_set_progress_pulse_step Ptr Entry
entry' CDouble
fraction'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetProgressPulseStepMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetProgressPulseStepMethodInfo a signature where
    overloadedMethod = entrySetProgressPulseStep
instance O.OverloadedMethodInfo EntrySetProgressPulseStepMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetProgressPulseStep",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetProgressPulseStep"
        }
#endif
foreign import ccall "gtk_entry_set_tabs" gtk_entry_set_tabs :: 
    Ptr Entry ->                            
    Ptr Pango.TabArray.TabArray ->          
    IO ()
entrySetTabs ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Maybe (Pango.TabArray.TabArray)
    
    -> m ()
entrySetTabs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Maybe TabArray -> m ()
entrySetTabs a
entry Maybe TabArray
tabs = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr TabArray
maybeTabs <- case Maybe TabArray
tabs of
        Maybe TabArray
Nothing -> Ptr TabArray -> IO (Ptr TabArray)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TabArray
forall a. Ptr a
nullPtr
        Just TabArray
jTabs -> do
            Ptr TabArray
jTabs' <- TabArray -> IO (Ptr TabArray)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TabArray
jTabs
            Ptr TabArray -> IO (Ptr TabArray)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TabArray
jTabs'
    Ptr Entry -> Ptr TabArray -> IO ()
gtk_entry_set_tabs Ptr Entry
entry' Ptr TabArray
maybeTabs
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    Maybe TabArray -> (TabArray -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TabArray
tabs TabArray -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetTabsMethodInfo
instance (signature ~ (Maybe (Pango.TabArray.TabArray) -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetTabsMethodInfo a signature where
    overloadedMethod = entrySetTabs
instance O.OverloadedMethodInfo EntrySetTabsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetTabs",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetTabs"
        }
#endif
foreign import ccall "gtk_entry_set_visibility" gtk_entry_set_visibility :: 
    Ptr Entry ->                            
    CInt ->                                 
    IO ()
entrySetVisibility ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> Bool
    
    
    -> m ()
entrySetVisibility :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> Bool -> m ()
entrySetVisibility a
entry Bool
visible = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    let visible' :: CInt
visible' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
visible
    Ptr Entry -> CInt -> IO ()
gtk_entry_set_visibility Ptr Entry
entry' CInt
visible'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntrySetVisibilityMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntrySetVisibilityMethodInfo a signature where
    overloadedMethod = entrySetVisibility
instance O.OverloadedMethodInfo EntrySetVisibilityMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entrySetVisibility",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entrySetVisibility"
        }
#endif
foreign import ccall "gtk_entry_unset_invisible_char" gtk_entry_unset_invisible_char :: 
    Ptr Entry ->                            
    IO ()
entryUnsetInvisibleChar ::
    (B.CallStack.HasCallStack, MonadIO m, IsEntry a) =>
    a
    
    -> m ()
entryUnsetInvisibleChar :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEntry a) =>
a -> m ()
entryUnsetInvisibleChar a
entry = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Entry
entry' <- a -> IO (Ptr Entry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
entry
    Ptr Entry -> IO ()
gtk_entry_unset_invisible_char Ptr Entry
entry'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data EntryUnsetInvisibleCharMethodInfo
instance (signature ~ (m ()), MonadIO m, IsEntry a) => O.OverloadedMethod EntryUnsetInvisibleCharMethodInfo a signature where
    overloadedMethod = entryUnsetInvisibleChar
instance O.OverloadedMethodInfo EntryUnsetInvisibleCharMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Entry.entryUnsetInvisibleChar",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Entry.html#v:entryUnsetInvisibleChar"
        }
#endif