{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gtk.Objects.SearchBar.SearchBar' is a container made to have a search entry (possibly
-- with additional connex widgets, such as drop-down menus, or buttons)
-- built-in. The search bar would appear when a search is started through
-- typing on the keyboard, or the application’s search mode is toggled on.
-- 
-- For keyboard presses to start a search, the search bar must be told
-- of a widget to capture key events from through
-- 'GI.Gtk.Objects.SearchBar.searchBarSetKeyCaptureWidget'. This widget will typically
-- be the top-level window, or a parent container of the search bar. Common
-- shortcuts such as Ctrl+F should be handled as an application action, or
-- through the menu items.
-- 
-- You will also need to tell the search bar about which entry you
-- are using as your search entry using 'GI.Gtk.Objects.SearchBar.searchBarConnectEntry'.
-- The following example shows you how to create a more complex search
-- entry.
-- 
-- = CSS nodes
-- 
-- 
-- === /plain code/
-- >
-- >searchbar
-- >╰── revealer
-- >    ╰── box
-- >         ├── [child]
-- >         ╰── [button.close]
-- 
-- 
-- GtkSearchBar has a main CSS node with name searchbar. It has a child node
-- with name revealer that contains a node with name box. The box node contains both the
-- CSS node of the child widget as well as an optional button node which gets the .close
-- style class applied.
-- 
-- == Creating a search bar
-- 
-- <https://gitlab.gnome.org/GNOME/gtk/tree/master/examples/search-bar.c A simple example>

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

module GI.Gtk.Objects.SearchBar
    ( 

-- * Exported types
    SearchBar(..)                           ,
    IsSearchBar                             ,
    toSearchBar                             ,
    noSearchBar                             ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveSearchBarMethod                  ,
#endif


-- ** connectEntry #method:connectEntry#

#if defined(ENABLE_OVERLOADING)
    SearchBarConnectEntryMethodInfo         ,
#endif
    searchBarConnectEntry                   ,


-- ** getKeyCaptureWidget #method:getKeyCaptureWidget#

#if defined(ENABLE_OVERLOADING)
    SearchBarGetKeyCaptureWidgetMethodInfo  ,
#endif
    searchBarGetKeyCaptureWidget            ,


-- ** getSearchMode #method:getSearchMode#

#if defined(ENABLE_OVERLOADING)
    SearchBarGetSearchModeMethodInfo        ,
#endif
    searchBarGetSearchMode                  ,


-- ** getShowCloseButton #method:getShowCloseButton#

#if defined(ENABLE_OVERLOADING)
    SearchBarGetShowCloseButtonMethodInfo   ,
#endif
    searchBarGetShowCloseButton             ,


-- ** new #method:new#

    searchBarNew                            ,


-- ** setKeyCaptureWidget #method:setKeyCaptureWidget#

#if defined(ENABLE_OVERLOADING)
    SearchBarSetKeyCaptureWidgetMethodInfo  ,
#endif
    searchBarSetKeyCaptureWidget            ,


-- ** setSearchMode #method:setSearchMode#

#if defined(ENABLE_OVERLOADING)
    SearchBarSetSearchModeMethodInfo        ,
#endif
    searchBarSetSearchMode                  ,


-- ** setShowCloseButton #method:setShowCloseButton#

#if defined(ENABLE_OVERLOADING)
    SearchBarSetShowCloseButtonMethodInfo   ,
#endif
    searchBarSetShowCloseButton             ,




 -- * Properties
-- ** searchModeEnabled #attr:searchModeEnabled#
-- | Whether the search mode is on and the search bar shown.
-- 
-- See 'GI.Gtk.Objects.SearchBar.searchBarSetSearchMode' for details.

#if defined(ENABLE_OVERLOADING)
    SearchBarSearchModeEnabledPropertyInfo  ,
#endif
    constructSearchBarSearchModeEnabled     ,
    getSearchBarSearchModeEnabled           ,
#if defined(ENABLE_OVERLOADING)
    searchBarSearchModeEnabled              ,
#endif
    setSearchBarSearchModeEnabled           ,


-- ** showCloseButton #attr:showCloseButton#
-- | Whether to show the close button in the search bar.

#if defined(ENABLE_OVERLOADING)
    SearchBarShowCloseButtonPropertyInfo    ,
#endif
    constructSearchBarShowCloseButton       ,
    getSearchBarShowCloseButton             ,
#if defined(ENABLE_OVERLOADING)
    searchBarShowCloseButton                ,
#endif
    setSearchBarShowCloseButton             ,




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified 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 GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Editable as Gtk.Editable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Bin as Gtk.Bin
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

-- | Memory-managed wrapper type.
newtype SearchBar = SearchBar (ManagedPtr SearchBar)
    deriving (SearchBar -> SearchBar -> Bool
(SearchBar -> SearchBar -> Bool)
-> (SearchBar -> SearchBar -> Bool) -> Eq SearchBar
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchBar -> SearchBar -> Bool
$c/= :: SearchBar -> SearchBar -> Bool
== :: SearchBar -> SearchBar -> Bool
$c== :: SearchBar -> SearchBar -> Bool
Eq)
foreign import ccall "gtk_search_bar_get_type"
    c_gtk_search_bar_get_type :: IO GType

instance GObject SearchBar where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_search_bar_get_type
    

-- | Convert 'SearchBar' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue SearchBar where
    toGValue :: SearchBar -> IO GValue
toGValue o :: SearchBar
o = do
        GType
gtype <- IO GType
c_gtk_search_bar_get_type
        SearchBar -> (Ptr SearchBar -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SearchBar
o (GType
-> (GValue -> Ptr SearchBar -> IO ()) -> Ptr SearchBar -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr SearchBar -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO SearchBar
fromGValue gv :: GValue
gv = do
        Ptr SearchBar
ptr <- GValue -> IO (Ptr SearchBar)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr SearchBar)
        (ManagedPtr SearchBar -> SearchBar)
-> Ptr SearchBar -> IO SearchBar
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SearchBar -> SearchBar
SearchBar Ptr SearchBar
ptr
        
    

-- | Type class for types which can be safely cast to `SearchBar`, for instance with `toSearchBar`.
class (GObject o, O.IsDescendantOf SearchBar o) => IsSearchBar o
instance (GObject o, O.IsDescendantOf SearchBar o) => IsSearchBar o

instance O.HasParentTypes SearchBar
type instance O.ParentTypes SearchBar = '[Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable]

-- | Cast to `SearchBar`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toSearchBar :: (MonadIO m, IsSearchBar o) => o -> m SearchBar
toSearchBar :: o -> m SearchBar
toSearchBar = IO SearchBar -> m SearchBar
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SearchBar -> m SearchBar)
-> (o -> IO SearchBar) -> o -> m SearchBar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SearchBar -> SearchBar) -> o -> IO SearchBar
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr SearchBar -> SearchBar
SearchBar

-- | A convenience alias for `Nothing` :: `Maybe` `SearchBar`.
noSearchBar :: Maybe SearchBar
noSearchBar :: Maybe SearchBar
noSearchBar = Maybe SearchBar
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveSearchBarMethod (t :: Symbol) (o :: *) :: * where
    ResolveSearchBarMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveSearchBarMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveSearchBarMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveSearchBarMethod "add" o = Gtk.Container.ContainerAddMethodInfo
    ResolveSearchBarMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveSearchBarMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveSearchBarMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveSearchBarMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveSearchBarMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveSearchBarMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveSearchBarMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSearchBarMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSearchBarMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveSearchBarMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveSearchBarMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
    ResolveSearchBarMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveSearchBarMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveSearchBarMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveSearchBarMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveSearchBarMethod "connectEntry" o = SearchBarConnectEntryMethodInfo
    ResolveSearchBarMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveSearchBarMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveSearchBarMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveSearchBarMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveSearchBarMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveSearchBarMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveSearchBarMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveSearchBarMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveSearchBarMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveSearchBarMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveSearchBarMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveSearchBarMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveSearchBarMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveSearchBarMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveSearchBarMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveSearchBarMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveSearchBarMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveSearchBarMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveSearchBarMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveSearchBarMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveSearchBarMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveSearchBarMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveSearchBarMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveSearchBarMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveSearchBarMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveSearchBarMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveSearchBarMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveSearchBarMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveSearchBarMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveSearchBarMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveSearchBarMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveSearchBarMethod "dragSourceSetIconPaintable" o = Gtk.Widget.WidgetDragSourceSetIconPaintableMethodInfo
    ResolveSearchBarMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveSearchBarMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveSearchBarMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveSearchBarMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveSearchBarMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveSearchBarMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
    ResolveSearchBarMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSearchBarMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
    ResolveSearchBarMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSearchBarMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSearchBarMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveSearchBarMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveSearchBarMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveSearchBarMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveSearchBarMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveSearchBarMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolveSearchBarMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveSearchBarMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveSearchBarMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveSearchBarMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveSearchBarMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolveSearchBarMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveSearchBarMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveSearchBarMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveSearchBarMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveSearchBarMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveSearchBarMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSearchBarMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveSearchBarMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveSearchBarMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveSearchBarMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveSearchBarMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveSearchBarMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveSearchBarMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolveSearchBarMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveSearchBarMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveSearchBarMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveSearchBarMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveSearchBarMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSearchBarMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSearchBarMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveSearchBarMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveSearchBarMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveSearchBarMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveSearchBarMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveSearchBarMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveSearchBarMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveSearchBarMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveSearchBarMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveSearchBarMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveSearchBarMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSearchBarMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSearchBarMethod "registerSurface" o = Gtk.Widget.WidgetRegisterSurfaceMethodInfo
    ResolveSearchBarMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
    ResolveSearchBarMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveSearchBarMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveSearchBarMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveSearchBarMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveSearchBarMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveSearchBarMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSearchBarMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveSearchBarMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveSearchBarMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveSearchBarMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSearchBarMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSearchBarMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSearchBarMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveSearchBarMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveSearchBarMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveSearchBarMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveSearchBarMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveSearchBarMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSearchBarMethod "unregisterSurface" o = Gtk.Widget.WidgetUnregisterSurfaceMethodInfo
    ResolveSearchBarMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveSearchBarMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSearchBarMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveSearchBarMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolveSearchBarMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveSearchBarMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveSearchBarMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveSearchBarMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveSearchBarMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveSearchBarMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveSearchBarMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveSearchBarMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
    ResolveSearchBarMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveSearchBarMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
    ResolveSearchBarMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveSearchBarMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveSearchBarMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSearchBarMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveSearchBarMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveSearchBarMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveSearchBarMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveSearchBarMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
    ResolveSearchBarMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveSearchBarMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
    ResolveSearchBarMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveSearchBarMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveSearchBarMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveSearchBarMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveSearchBarMethod "getHasSurface" o = Gtk.Widget.WidgetGetHasSurfaceMethodInfo
    ResolveSearchBarMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveSearchBarMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveSearchBarMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveSearchBarMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveSearchBarMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveSearchBarMethod "getKeyCaptureWidget" o = SearchBarGetKeyCaptureWidgetMethodInfo
    ResolveSearchBarMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveSearchBarMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveSearchBarMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveSearchBarMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveSearchBarMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveSearchBarMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveSearchBarMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveSearchBarMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveSearchBarMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveSearchBarMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveSearchBarMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveSearchBarMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveSearchBarMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveSearchBarMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveSearchBarMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveSearchBarMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
    ResolveSearchBarMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveSearchBarMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveSearchBarMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveSearchBarMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSearchBarMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSearchBarMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveSearchBarMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveSearchBarMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveSearchBarMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveSearchBarMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveSearchBarMethod "getSearchMode" o = SearchBarGetSearchModeMethodInfo
    ResolveSearchBarMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveSearchBarMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveSearchBarMethod "getShowCloseButton" o = SearchBarGetShowCloseButtonMethodInfo
    ResolveSearchBarMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveSearchBarMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveSearchBarMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveSearchBarMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveSearchBarMethod "getSurface" o = Gtk.Widget.WidgetGetSurfaceMethodInfo
    ResolveSearchBarMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveSearchBarMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveSearchBarMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveSearchBarMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveSearchBarMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolveSearchBarMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveSearchBarMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveSearchBarMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveSearchBarMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveSearchBarMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveSearchBarMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveSearchBarMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveSearchBarMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveSearchBarMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveSearchBarMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveSearchBarMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveSearchBarMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveSearchBarMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSearchBarMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSearchBarMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveSearchBarMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveSearchBarMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
    ResolveSearchBarMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveSearchBarMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
    ResolveSearchBarMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveSearchBarMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveSearchBarMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveSearchBarMethod "setHasSurface" o = Gtk.Widget.WidgetSetHasSurfaceMethodInfo
    ResolveSearchBarMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveSearchBarMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveSearchBarMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveSearchBarMethod "setKeyCaptureWidget" o = SearchBarSetKeyCaptureWidgetMethodInfo
    ResolveSearchBarMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveSearchBarMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveSearchBarMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveSearchBarMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveSearchBarMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveSearchBarMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveSearchBarMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveSearchBarMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveSearchBarMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveSearchBarMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSearchBarMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveSearchBarMethod "setSearchMode" o = SearchBarSetSearchModeMethodInfo
    ResolveSearchBarMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveSearchBarMethod "setShowCloseButton" o = SearchBarSetShowCloseButtonMethodInfo
    ResolveSearchBarMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveSearchBarMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveSearchBarMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveSearchBarMethod "setSurface" o = Gtk.Widget.WidgetSetSurfaceMethodInfo
    ResolveSearchBarMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveSearchBarMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveSearchBarMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolveSearchBarMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveSearchBarMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveSearchBarMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveSearchBarMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveSearchBarMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "search-mode-enabled"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@search-mode-enabled@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' searchBar #searchModeEnabled
-- @
getSearchBarSearchModeEnabled :: (MonadIO m, IsSearchBar o) => o -> m Bool
getSearchBarSearchModeEnabled :: o -> m Bool
getSearchBarSearchModeEnabled obj :: o
obj = 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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "search-mode-enabled"

-- | Set the value of the “@search-mode-enabled@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' searchBar [ #searchModeEnabled 'Data.GI.Base.Attributes.:=' value ]
-- @
setSearchBarSearchModeEnabled :: (MonadIO m, IsSearchBar o) => o -> Bool -> m ()
setSearchBarSearchModeEnabled :: o -> Bool -> m ()
setSearchBarSearchModeEnabled obj :: o
obj val :: Bool
val = 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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "search-mode-enabled" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@search-mode-enabled@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSearchBarSearchModeEnabled :: (IsSearchBar o) => Bool -> IO (GValueConstruct o)
constructSearchBarSearchModeEnabled :: Bool -> IO (GValueConstruct o)
constructSearchBarSearchModeEnabled val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "search-mode-enabled" Bool
val

#if defined(ENABLE_OVERLOADING)
data SearchBarSearchModeEnabledPropertyInfo
instance AttrInfo SearchBarSearchModeEnabledPropertyInfo where
    type AttrAllowedOps SearchBarSearchModeEnabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SearchBarSearchModeEnabledPropertyInfo = IsSearchBar
    type AttrSetTypeConstraint SearchBarSearchModeEnabledPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SearchBarSearchModeEnabledPropertyInfo = (~) Bool
    type AttrTransferType SearchBarSearchModeEnabledPropertyInfo = Bool
    type AttrGetType SearchBarSearchModeEnabledPropertyInfo = Bool
    type AttrLabel SearchBarSearchModeEnabledPropertyInfo = "search-mode-enabled"
    type AttrOrigin SearchBarSearchModeEnabledPropertyInfo = SearchBar
    attrGet = getSearchBarSearchModeEnabled
    attrSet = setSearchBarSearchModeEnabled
    attrTransfer _ v = do
        return v
    attrConstruct = constructSearchBarSearchModeEnabled
    attrClear = undefined
#endif

-- VVV Prop "show-close-button"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@show-close-button@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' searchBar #showCloseButton
-- @
getSearchBarShowCloseButton :: (MonadIO m, IsSearchBar o) => o -> m Bool
getSearchBarShowCloseButton :: o -> m Bool
getSearchBarShowCloseButton obj :: o
obj = 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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "show-close-button"

-- | Set the value of the “@show-close-button@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' searchBar [ #showCloseButton 'Data.GI.Base.Attributes.:=' value ]
-- @
setSearchBarShowCloseButton :: (MonadIO m, IsSearchBar o) => o -> Bool -> m ()
setSearchBarShowCloseButton :: o -> Bool -> m ()
setSearchBarShowCloseButton obj :: o
obj val :: Bool
val = 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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "show-close-button" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@show-close-button@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSearchBarShowCloseButton :: (IsSearchBar o) => Bool -> IO (GValueConstruct o)
constructSearchBarShowCloseButton :: Bool -> IO (GValueConstruct o)
constructSearchBarShowCloseButton val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "show-close-button" Bool
val

#if defined(ENABLE_OVERLOADING)
data SearchBarShowCloseButtonPropertyInfo
instance AttrInfo SearchBarShowCloseButtonPropertyInfo where
    type AttrAllowedOps SearchBarShowCloseButtonPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SearchBarShowCloseButtonPropertyInfo = IsSearchBar
    type AttrSetTypeConstraint SearchBarShowCloseButtonPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SearchBarShowCloseButtonPropertyInfo = (~) Bool
    type AttrTransferType SearchBarShowCloseButtonPropertyInfo = Bool
    type AttrGetType SearchBarShowCloseButtonPropertyInfo = Bool
    type AttrLabel SearchBarShowCloseButtonPropertyInfo = "show-close-button"
    type AttrOrigin SearchBarShowCloseButtonPropertyInfo = SearchBar
    attrGet = getSearchBarShowCloseButton
    attrSet = setSearchBarShowCloseButton
    attrTransfer _ v = do
        return v
    attrConstruct = constructSearchBarShowCloseButton
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SearchBar
type instance O.AttributeList SearchBar = SearchBarAttributeList
type SearchBarAttributeList = ('[ '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("searchModeEnabled", SearchBarSearchModeEnabledPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("showCloseButton", SearchBarShowCloseButtonPropertyInfo), '("surface", Gtk.Widget.WidgetSurfacePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
searchBarSearchModeEnabled :: AttrLabelProxy "searchModeEnabled"
searchBarSearchModeEnabled = AttrLabelProxy

searchBarShowCloseButton :: AttrLabelProxy "showCloseButton"
searchBarShowCloseButton = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SearchBar = SearchBarSignalList
type SearchBarSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_search_bar_new" gtk_search_bar_new :: 
    IO (Ptr SearchBar)

-- | Creates a t'GI.Gtk.Objects.SearchBar.SearchBar'. You will need to tell it about
-- which widget is going to be your text entry using
-- 'GI.Gtk.Objects.SearchBar.searchBarConnectEntry'.
searchBarNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m SearchBar
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.SearchBar.SearchBar'
searchBarNew :: m SearchBar
searchBarNew  = IO SearchBar -> m SearchBar
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SearchBar -> m SearchBar) -> IO SearchBar -> m SearchBar
forall a b. (a -> b) -> a -> b
$ do
    Ptr SearchBar
result <- IO (Ptr SearchBar)
gtk_search_bar_new
    Text -> Ptr SearchBar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "searchBarNew" Ptr SearchBar
result
    SearchBar
result' <- ((ManagedPtr SearchBar -> SearchBar)
-> Ptr SearchBar -> IO SearchBar
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr SearchBar -> SearchBar
SearchBar) Ptr SearchBar
result
    SearchBar -> IO SearchBar
forall (m :: * -> *) a. Monad m => a -> m a
return SearchBar
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method SearchBar::connect_entry
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SearchBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSearchBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "entry"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Editable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkEditable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_search_bar_connect_entry" gtk_search_bar_connect_entry :: 
    Ptr SearchBar ->                        -- bar : TInterface (Name {namespace = "Gtk", name = "SearchBar"})
    Ptr Gtk.Editable.Editable ->            -- entry : TInterface (Name {namespace = "Gtk", name = "Editable"})
    IO ()

-- | Connects the t'GI.Gtk.Objects.Entry.Entry' widget passed as the one to be used in
-- this search bar. The entry should be a descendant of the search bar.
-- This is only required if the entry isn’t the direct child of the
-- search bar (as in our main example).
searchBarConnectEntry ::
    (B.CallStack.HasCallStack, MonadIO m, IsSearchBar a, Gtk.Editable.IsEditable b) =>
    a
    -- ^ /@bar@/: a t'GI.Gtk.Objects.SearchBar.SearchBar'
    -> b
    -- ^ /@entry@/: a t'GI.Gtk.Interfaces.Editable.Editable'
    -> m ()
searchBarConnectEntry :: a -> b -> m ()
searchBarConnectEntry bar :: a
bar entry :: b
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 SearchBar
bar' <- a -> IO (Ptr SearchBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    Ptr Editable
entry' <- b -> IO (Ptr Editable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
entry
    Ptr SearchBar -> Ptr Editable -> IO ()
gtk_search_bar_connect_entry Ptr SearchBar
bar' Ptr Editable
entry'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
bar
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
entry
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SearchBarConnectEntryMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsSearchBar a, Gtk.Editable.IsEditable b) => O.MethodInfo SearchBarConnectEntryMethodInfo a signature where
    overloadedMethod = searchBarConnectEntry

#endif

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

foreign import ccall "gtk_search_bar_get_key_capture_widget" gtk_search_bar_get_key_capture_widget :: 
    Ptr SearchBar ->                        -- bar : TInterface (Name {namespace = "Gtk", name = "SearchBar"})
    IO (Ptr Gtk.Widget.Widget)

-- | Gets the widget that /@bar@/ is capturing key events from.
searchBarGetKeyCaptureWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsSearchBar a) =>
    a
    -- ^ /@bar@/: a t'GI.Gtk.Objects.SearchBar.SearchBar'
    -> m Gtk.Widget.Widget
    -- ^ __Returns:__ The key capture widget.
searchBarGetKeyCaptureWidget :: a -> m Widget
searchBarGetKeyCaptureWidget bar :: a
bar = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
    Ptr SearchBar
bar' <- a -> IO (Ptr SearchBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    Ptr Widget
result <- Ptr SearchBar -> IO (Ptr Widget)
gtk_search_bar_get_key_capture_widget Ptr SearchBar
bar'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "searchBarGetKeyCaptureWidget" Ptr Widget
result
    Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
bar
    Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'

#if defined(ENABLE_OVERLOADING)
data SearchBarGetKeyCaptureWidgetMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsSearchBar a) => O.MethodInfo SearchBarGetKeyCaptureWidgetMethodInfo a signature where
    overloadedMethod = searchBarGetKeyCaptureWidget

#endif

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

foreign import ccall "gtk_search_bar_get_search_mode" gtk_search_bar_get_search_mode :: 
    Ptr SearchBar ->                        -- bar : TInterface (Name {namespace = "Gtk", name = "SearchBar"})
    IO CInt

-- | Returns whether the search mode is on or off.
searchBarGetSearchMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsSearchBar a) =>
    a
    -- ^ /@bar@/: a t'GI.Gtk.Objects.SearchBar.SearchBar'
    -> m Bool
    -- ^ __Returns:__ whether search mode is toggled on
searchBarGetSearchMode :: a -> m Bool
searchBarGetSearchMode bar :: a
bar = 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 SearchBar
bar' <- a -> IO (Ptr SearchBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    CInt
result <- Ptr SearchBar -> IO CInt
gtk_search_bar_get_search_mode Ptr SearchBar
bar'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
bar
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SearchBarGetSearchModeMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSearchBar a) => O.MethodInfo SearchBarGetSearchModeMethodInfo a signature where
    overloadedMethod = searchBarGetSearchMode

#endif

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

foreign import ccall "gtk_search_bar_get_show_close_button" gtk_search_bar_get_show_close_button :: 
    Ptr SearchBar ->                        -- bar : TInterface (Name {namespace = "Gtk", name = "SearchBar"})
    IO CInt

-- | Returns whether the close button is shown.
searchBarGetShowCloseButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsSearchBar a) =>
    a
    -- ^ /@bar@/: a t'GI.Gtk.Objects.SearchBar.SearchBar'
    -> m Bool
    -- ^ __Returns:__ whether the close button is shown
searchBarGetShowCloseButton :: a -> m Bool
searchBarGetShowCloseButton bar :: a
bar = 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 SearchBar
bar' <- a -> IO (Ptr SearchBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    CInt
result <- Ptr SearchBar -> IO CInt
gtk_search_bar_get_show_close_button Ptr SearchBar
bar'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
bar
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SearchBarGetShowCloseButtonMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSearchBar a) => O.MethodInfo SearchBarGetShowCloseButtonMethodInfo a signature where
    overloadedMethod = searchBarGetShowCloseButton

#endif

-- method SearchBar::set_key_capture_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SearchBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSearchBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidget" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_search_bar_set_key_capture_widget" gtk_search_bar_set_key_capture_widget :: 
    Ptr SearchBar ->                        -- bar : TInterface (Name {namespace = "Gtk", name = "SearchBar"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Sets /@widget@/ as the widget that /@bar@/ will capture key events from.
-- 
-- If key events are handled by the search bar, the bar will
-- be shown, and the entry populated with the entered text.
searchBarSetKeyCaptureWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsSearchBar a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@bar@/: a t'GI.Gtk.Objects.SearchBar.SearchBar'
    -> Maybe (b)
    -- ^ /@widget@/: a t'GI.Gtk.Objects.Widget.Widget'
    -> m ()
searchBarSetKeyCaptureWidget :: a -> Maybe b -> m ()
searchBarSetKeyCaptureWidget bar :: a
bar widget :: Maybe b
widget = 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 SearchBar
bar' <- a -> IO (Ptr SearchBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    Ptr Widget
maybeWidget <- case Maybe b
widget of
        Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just jWidget :: b
jWidget -> do
            Ptr Widget
jWidget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWidget
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jWidget'
    Ptr SearchBar -> Ptr Widget -> IO ()
gtk_search_bar_set_key_capture_widget Ptr SearchBar
bar' Ptr Widget
maybeWidget
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
bar
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
widget b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SearchBarSetKeyCaptureWidgetMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsSearchBar a, Gtk.Widget.IsWidget b) => O.MethodInfo SearchBarSetKeyCaptureWidgetMethodInfo a signature where
    overloadedMethod = searchBarSetKeyCaptureWidget

#endif

-- method SearchBar::set_search_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SearchBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSearchBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "search_mode"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new state of the search mode"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_search_bar_set_search_mode" gtk_search_bar_set_search_mode :: 
    Ptr SearchBar ->                        -- bar : TInterface (Name {namespace = "Gtk", name = "SearchBar"})
    CInt ->                                 -- search_mode : TBasicType TBoolean
    IO ()

-- | Switches the search mode on or off.
searchBarSetSearchMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsSearchBar a) =>
    a
    -- ^ /@bar@/: a t'GI.Gtk.Objects.SearchBar.SearchBar'
    -> Bool
    -- ^ /@searchMode@/: the new state of the search mode
    -> m ()
searchBarSetSearchMode :: a -> Bool -> m ()
searchBarSetSearchMode bar :: a
bar searchMode :: Bool
searchMode = 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 SearchBar
bar' <- a -> IO (Ptr SearchBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    let searchMode' :: CInt
searchMode' = (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
searchMode
    Ptr SearchBar -> CInt -> IO ()
gtk_search_bar_set_search_mode Ptr SearchBar
bar' CInt
searchMode'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
bar
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SearchBarSetSearchModeMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSearchBar a) => O.MethodInfo SearchBarSetSearchModeMethodInfo a signature where
    overloadedMethod = searchBarSetSearchMode

#endif

-- method SearchBar::set_show_close_button
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SearchBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSearchBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "visible"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether the close button will be shown or not"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_search_bar_set_show_close_button" gtk_search_bar_set_show_close_button :: 
    Ptr SearchBar ->                        -- bar : TInterface (Name {namespace = "Gtk", name = "SearchBar"})
    CInt ->                                 -- visible : TBasicType TBoolean
    IO ()

-- | Shows or hides the close button. Applications that
-- already have a “search” toggle button should not show a close
-- button in their search bar, as it duplicates the role of the
-- toggle button.
searchBarSetShowCloseButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsSearchBar a) =>
    a
    -- ^ /@bar@/: a t'GI.Gtk.Objects.SearchBar.SearchBar'
    -> Bool
    -- ^ /@visible@/: whether the close button will be shown or not
    -> m ()
searchBarSetShowCloseButton :: a -> Bool -> m ()
searchBarSetShowCloseButton bar :: a
bar visible :: 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 SearchBar
bar' <- a -> IO (Ptr SearchBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bar
    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 SearchBar -> CInt -> IO ()
gtk_search_bar_set_show_close_button Ptr SearchBar
bar' CInt
visible'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
bar
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SearchBarSetShowCloseButtonMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSearchBar a) => O.MethodInfo SearchBarSetShowCloseButtonMethodInfo a signature where
    overloadedMethod = searchBarSetShowCloseButton

#endif