{-# 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.InfoBar.InfoBar' is a widget that can be used to show messages to
-- the user without showing a dialog. It is often temporarily shown
-- at the top or bottom of a document. In contrast to t'GI.Gtk.Objects.Dialog.Dialog', which
-- has an action area at the bottom, t'GI.Gtk.Objects.InfoBar.InfoBar' has an action area
-- at the side.
-- 
-- The API of t'GI.Gtk.Objects.InfoBar.InfoBar' is very similar to t'GI.Gtk.Objects.Dialog.Dialog', allowing you
-- to add buttons to the action area with 'GI.Gtk.Objects.InfoBar.infoBarAddButton' or
-- @/gtk_info_bar_new_with_buttons()/@. The sensitivity of action widgets
-- can be controlled with 'GI.Gtk.Objects.InfoBar.infoBarSetResponseSensitive'.
-- 
-- To add widgets to the main content area of a t'GI.Gtk.Objects.InfoBar.InfoBar', use
-- 'GI.Gtk.Objects.InfoBar.infoBarAddChild'.
-- 
-- Similar to t'GI.Gtk.Objects.MessageDialog.MessageDialog', the contents of a t'GI.Gtk.Objects.InfoBar.InfoBar' can by
-- classified as error message, warning, informational message, etc,
-- by using 'GI.Gtk.Objects.InfoBar.infoBarSetMessageType'. GTK+ may use the message type
-- to determine how the message is displayed.
-- 
-- A simple example for using a t'GI.Gtk.Objects.InfoBar.InfoBar':
-- 
-- === /C code/
-- >
-- >GtkWidget *message_label;
-- >GtkWidget *widget;
-- >GtkWidget *grid;
-- >GtkInfoBar *bar;
-- >
-- >// set up info bar
-- >widget = gtk_info_bar_new ();
-- >bar = GTK_INFO_BAR (widget);
-- >grid = gtk_grid_new ();
-- >
-- >message_label = gtk_label_new ("");
-- >gtk_info_bar_add_child (bar, message_label);
-- >gtk_info_bar_add_button (bar,
-- >                         _("_OK"),
-- >                         GTK_RESPONSE_OK);
-- >g_signal_connect (bar,
-- >                  "response",
-- >                  G_CALLBACK (gtk_widget_hide),
-- >                  NULL);
-- >gtk_grid_attach (GTK_GRID (grid),
-- >                 widget,
-- >                 0, 2, 1, 1);
-- >
-- >// ...
-- >
-- >// show an error message
-- >gtk_label_set_text (GTK_LABEL (message_label), "An error occurred!");
-- >gtk_info_bar_set_message_type (bar, GTK_MESSAGE_ERROR);
-- >gtk_widget_show (bar);
-- 
-- 
-- = GtkInfoBar as GtkBuildable
-- 
-- The GtkInfoBar implementation of the GtkBuildable interface exposes
-- the content area and action area as internal children with the names
-- “content_area” and “action_area”.
-- 
-- GtkInfoBar supports a custom \<action-widgets> element, which can contain
-- multiple \<action-widget> elements. The “response” attribute specifies a
-- numeric response, and the content of the element is the id of widget
-- (which should be a child of the dialogs /@actionArea@/).
-- 
-- = CSS nodes
-- 
-- GtkInfoBar has a single CSS node with name infobar. The node may get
-- one of the style classes .info, .warning, .error or .question, depending
-- on the message type.
-- If the info bar shows a close button, that button will have the .close
-- style class applied.

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

module GI.Gtk.Objects.InfoBar
    ( 

-- * Exported types
    InfoBar(..)                             ,
    IsInfoBar                               ,
    toInfoBar                               ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveInfoBarMethod                    ,
#endif


-- ** addActionWidget #method:addActionWidget#

#if defined(ENABLE_OVERLOADING)
    InfoBarAddActionWidgetMethodInfo        ,
#endif
    infoBarAddActionWidget                  ,


-- ** addButton #method:addButton#

#if defined(ENABLE_OVERLOADING)
    InfoBarAddButtonMethodInfo              ,
#endif
    infoBarAddButton                        ,


-- ** addChild #method:addChild#

#if defined(ENABLE_OVERLOADING)
    InfoBarAddChildMethodInfo               ,
#endif
    infoBarAddChild                         ,


-- ** getMessageType #method:getMessageType#

#if defined(ENABLE_OVERLOADING)
    InfoBarGetMessageTypeMethodInfo         ,
#endif
    infoBarGetMessageType                   ,


-- ** getRevealed #method:getRevealed#

#if defined(ENABLE_OVERLOADING)
    InfoBarGetRevealedMethodInfo            ,
#endif
    infoBarGetRevealed                      ,


-- ** getShowCloseButton #method:getShowCloseButton#

#if defined(ENABLE_OVERLOADING)
    InfoBarGetShowCloseButtonMethodInfo     ,
#endif
    infoBarGetShowCloseButton               ,


-- ** new #method:new#

    infoBarNew                              ,


-- ** removeActionWidget #method:removeActionWidget#

#if defined(ENABLE_OVERLOADING)
    InfoBarRemoveActionWidgetMethodInfo     ,
#endif
    infoBarRemoveActionWidget               ,


-- ** removeChild #method:removeChild#

#if defined(ENABLE_OVERLOADING)
    InfoBarRemoveChildMethodInfo            ,
#endif
    infoBarRemoveChild                      ,


-- ** response #method:response#

#if defined(ENABLE_OVERLOADING)
    InfoBarResponseMethodInfo               ,
#endif
    infoBarResponse                         ,


-- ** setDefaultResponse #method:setDefaultResponse#

#if defined(ENABLE_OVERLOADING)
    InfoBarSetDefaultResponseMethodInfo     ,
#endif
    infoBarSetDefaultResponse               ,


-- ** setMessageType #method:setMessageType#

#if defined(ENABLE_OVERLOADING)
    InfoBarSetMessageTypeMethodInfo         ,
#endif
    infoBarSetMessageType                   ,


-- ** setResponseSensitive #method:setResponseSensitive#

#if defined(ENABLE_OVERLOADING)
    InfoBarSetResponseSensitiveMethodInfo   ,
#endif
    infoBarSetResponseSensitive             ,


-- ** setRevealed #method:setRevealed#

#if defined(ENABLE_OVERLOADING)
    InfoBarSetRevealedMethodInfo            ,
#endif
    infoBarSetRevealed                      ,


-- ** setShowCloseButton #method:setShowCloseButton#

#if defined(ENABLE_OVERLOADING)
    InfoBarSetShowCloseButtonMethodInfo     ,
#endif
    infoBarSetShowCloseButton               ,




 -- * Properties
-- ** messageType #attr:messageType#
-- | The type of the message.
-- 
-- The type may be used to determine the appearance of the info bar.

#if defined(ENABLE_OVERLOADING)
    InfoBarMessageTypePropertyInfo          ,
#endif
    constructInfoBarMessageType             ,
    getInfoBarMessageType                   ,
#if defined(ENABLE_OVERLOADING)
    infoBarMessageType                      ,
#endif
    setInfoBarMessageType                   ,


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

#if defined(ENABLE_OVERLOADING)
    InfoBarRevealedPropertyInfo             ,
#endif
    constructInfoBarRevealed                ,
    getInfoBarRevealed                      ,
#if defined(ENABLE_OVERLOADING)
    infoBarRevealed                         ,
#endif
    setInfoBarRevealed                      ,


-- ** showCloseButton #attr:showCloseButton#
-- | Whether to include a standard close button.

#if defined(ENABLE_OVERLOADING)
    InfoBarShowCloseButtonPropertyInfo      ,
#endif
    constructInfoBarShowCloseButton         ,
    getInfoBarShowCloseButton               ,
#if defined(ENABLE_OVERLOADING)
    infoBarShowCloseButton                  ,
#endif
    setInfoBarShowCloseButton               ,




 -- * Signals
-- ** close #signal:close#

    C_InfoBarCloseCallback                  ,
    InfoBarCloseCallback                    ,
#if defined(ENABLE_OVERLOADING)
    InfoBarCloseSignalInfo                  ,
#endif
    afterInfoBarClose                       ,
    genClosure_InfoBarClose                 ,
    mk_InfoBarCloseCallback                 ,
    noInfoBarCloseCallback                  ,
    onInfoBarClose                          ,
    wrap_InfoBarCloseCallback               ,


-- ** response #signal:response#

    C_InfoBarResponseCallback               ,
    InfoBarResponseCallback                 ,
#if defined(ENABLE_OVERLOADING)
    InfoBarResponseSignalInfo               ,
#endif
    afterInfoBarResponse                    ,
    genClosure_InfoBarResponse              ,
    mk_InfoBarResponseCallback              ,
    noInfoBarResponseCallback               ,
    onInfoBarResponse                       ,
    wrap_InfoBarResponseCallback            ,




    ) 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.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 GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Button as Gtk.Button
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_info_bar_get_type"
    c_gtk_info_bar_get_type :: IO B.Types.GType

instance B.Types.TypedObject InfoBar where
    glibType :: IO GType
glibType = IO GType
c_gtk_info_bar_get_type

instance B.Types.GObject InfoBar

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

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

instance O.HasParentTypes InfoBar
type instance O.ParentTypes InfoBar = '[Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveInfoBarMethod (t :: Symbol) (o :: *) :: * where
    ResolveInfoBarMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveInfoBarMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveInfoBarMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveInfoBarMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveInfoBarMethod "addActionWidget" o = InfoBarAddActionWidgetMethodInfo
    ResolveInfoBarMethod "addButton" o = InfoBarAddButtonMethodInfo
    ResolveInfoBarMethod "addChild" o = InfoBarAddChildMethodInfo
    ResolveInfoBarMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveInfoBarMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveInfoBarMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveInfoBarMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveInfoBarMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveInfoBarMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveInfoBarMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveInfoBarMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveInfoBarMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveInfoBarMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveInfoBarMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveInfoBarMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveInfoBarMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveInfoBarMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveInfoBarMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveInfoBarMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveInfoBarMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveInfoBarMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveInfoBarMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveInfoBarMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveInfoBarMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveInfoBarMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveInfoBarMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveInfoBarMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveInfoBarMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveInfoBarMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveInfoBarMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveInfoBarMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveInfoBarMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveInfoBarMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveInfoBarMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveInfoBarMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveInfoBarMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveInfoBarMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveInfoBarMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveInfoBarMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveInfoBarMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveInfoBarMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveInfoBarMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveInfoBarMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveInfoBarMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveInfoBarMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveInfoBarMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveInfoBarMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveInfoBarMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveInfoBarMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveInfoBarMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveInfoBarMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveInfoBarMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveInfoBarMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveInfoBarMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveInfoBarMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveInfoBarMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveInfoBarMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveInfoBarMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveInfoBarMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveInfoBarMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveInfoBarMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveInfoBarMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveInfoBarMethod "removeActionWidget" o = InfoBarRemoveActionWidgetMethodInfo
    ResolveInfoBarMethod "removeChild" o = InfoBarRemoveChildMethodInfo
    ResolveInfoBarMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveInfoBarMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveInfoBarMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveInfoBarMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveInfoBarMethod "response" o = InfoBarResponseMethodInfo
    ResolveInfoBarMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveInfoBarMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveInfoBarMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveInfoBarMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveInfoBarMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveInfoBarMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveInfoBarMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveInfoBarMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveInfoBarMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveInfoBarMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveInfoBarMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveInfoBarMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveInfoBarMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveInfoBarMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveInfoBarMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveInfoBarMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveInfoBarMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveInfoBarMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveInfoBarMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveInfoBarMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveInfoBarMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveInfoBarMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveInfoBarMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveInfoBarMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveInfoBarMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveInfoBarMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveInfoBarMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveInfoBarMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveInfoBarMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveInfoBarMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveInfoBarMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveInfoBarMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveInfoBarMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveInfoBarMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveInfoBarMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveInfoBarMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveInfoBarMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveInfoBarMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveInfoBarMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveInfoBarMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveInfoBarMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveInfoBarMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveInfoBarMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveInfoBarMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveInfoBarMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveInfoBarMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveInfoBarMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveInfoBarMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveInfoBarMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveInfoBarMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveInfoBarMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveInfoBarMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveInfoBarMethod "getMessageType" o = InfoBarGetMessageTypeMethodInfo
    ResolveInfoBarMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveInfoBarMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveInfoBarMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveInfoBarMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveInfoBarMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveInfoBarMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveInfoBarMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveInfoBarMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveInfoBarMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveInfoBarMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveInfoBarMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveInfoBarMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveInfoBarMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveInfoBarMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveInfoBarMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveInfoBarMethod "getRevealed" o = InfoBarGetRevealedMethodInfo
    ResolveInfoBarMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveInfoBarMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveInfoBarMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveInfoBarMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveInfoBarMethod "getShowCloseButton" o = InfoBarGetShowCloseButtonMethodInfo
    ResolveInfoBarMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveInfoBarMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveInfoBarMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveInfoBarMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveInfoBarMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveInfoBarMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveInfoBarMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveInfoBarMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveInfoBarMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveInfoBarMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveInfoBarMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveInfoBarMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveInfoBarMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveInfoBarMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveInfoBarMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveInfoBarMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveInfoBarMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveInfoBarMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveInfoBarMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveInfoBarMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveInfoBarMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveInfoBarMethod "setDefaultResponse" o = InfoBarSetDefaultResponseMethodInfo
    ResolveInfoBarMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveInfoBarMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveInfoBarMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveInfoBarMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveInfoBarMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveInfoBarMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveInfoBarMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveInfoBarMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveInfoBarMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveInfoBarMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveInfoBarMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveInfoBarMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveInfoBarMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveInfoBarMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveInfoBarMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveInfoBarMethod "setMessageType" o = InfoBarSetMessageTypeMethodInfo
    ResolveInfoBarMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveInfoBarMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveInfoBarMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveInfoBarMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveInfoBarMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveInfoBarMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveInfoBarMethod "setResponseSensitive" o = InfoBarSetResponseSensitiveMethodInfo
    ResolveInfoBarMethod "setRevealed" o = InfoBarSetRevealedMethodInfo
    ResolveInfoBarMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveInfoBarMethod "setShowCloseButton" o = InfoBarSetShowCloseButtonMethodInfo
    ResolveInfoBarMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveInfoBarMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveInfoBarMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveInfoBarMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveInfoBarMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveInfoBarMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveInfoBarMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveInfoBarMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveInfoBarMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveInfoBarMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal InfoBar::close
-- | The [close](#g:signal:close) signal is a
-- [keybinding signal][GtkBindingSignal]
-- which gets emitted when the user uses a keybinding to dismiss
-- the info bar.
-- 
-- The default binding for this signal is the Escape key.
type InfoBarCloseCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `InfoBarCloseCallback`@.
noInfoBarCloseCallback :: Maybe InfoBarCloseCallback
noInfoBarCloseCallback :: Maybe (IO ())
noInfoBarCloseCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_InfoBarCloseCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_InfoBarClose :: MonadIO m => InfoBarCloseCallback -> m (GClosure C_InfoBarCloseCallback)
genClosure_InfoBarClose :: IO () -> m (GClosure C_InfoBarCloseCallback)
genClosure_InfoBarClose IO ()
cb = IO (GClosure C_InfoBarCloseCallback)
-> m (GClosure C_InfoBarCloseCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_InfoBarCloseCallback)
 -> m (GClosure C_InfoBarCloseCallback))
-> IO (GClosure C_InfoBarCloseCallback)
-> m (GClosure C_InfoBarCloseCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_InfoBarCloseCallback
cb' = IO () -> C_InfoBarCloseCallback
wrap_InfoBarCloseCallback IO ()
cb
    C_InfoBarCloseCallback -> IO (FunPtr C_InfoBarCloseCallback)
mk_InfoBarCloseCallback C_InfoBarCloseCallback
cb' IO (FunPtr C_InfoBarCloseCallback)
-> (FunPtr C_InfoBarCloseCallback
    -> IO (GClosure C_InfoBarCloseCallback))
-> IO (GClosure C_InfoBarCloseCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_InfoBarCloseCallback
-> IO (GClosure C_InfoBarCloseCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `InfoBarCloseCallback` into a `C_InfoBarCloseCallback`.
wrap_InfoBarCloseCallback ::
    InfoBarCloseCallback ->
    C_InfoBarCloseCallback
wrap_InfoBarCloseCallback :: IO () -> C_InfoBarCloseCallback
wrap_InfoBarCloseCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [close](#signal:close) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' infoBar #close callback
-- @
-- 
-- 
onInfoBarClose :: (IsInfoBar a, MonadIO m) => a -> InfoBarCloseCallback -> m SignalHandlerId
onInfoBarClose :: a -> IO () -> m SignalHandlerId
onInfoBarClose 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_InfoBarCloseCallback
cb' = IO () -> C_InfoBarCloseCallback
wrap_InfoBarCloseCallback IO ()
cb
    FunPtr C_InfoBarCloseCallback
cb'' <- C_InfoBarCloseCallback -> IO (FunPtr C_InfoBarCloseCallback)
mk_InfoBarCloseCallback C_InfoBarCloseCallback
cb'
    a
-> Text
-> FunPtr C_InfoBarCloseCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"close" FunPtr C_InfoBarCloseCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [close](#signal:close) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' infoBar #close callback
-- @
-- 
-- 
afterInfoBarClose :: (IsInfoBar a, MonadIO m) => a -> InfoBarCloseCallback -> m SignalHandlerId
afterInfoBarClose :: a -> IO () -> m SignalHandlerId
afterInfoBarClose 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_InfoBarCloseCallback
cb' = IO () -> C_InfoBarCloseCallback
wrap_InfoBarCloseCallback IO ()
cb
    FunPtr C_InfoBarCloseCallback
cb'' <- C_InfoBarCloseCallback -> IO (FunPtr C_InfoBarCloseCallback)
mk_InfoBarCloseCallback C_InfoBarCloseCallback
cb'
    a
-> Text
-> FunPtr C_InfoBarCloseCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"close" FunPtr C_InfoBarCloseCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data InfoBarCloseSignalInfo
instance SignalInfo InfoBarCloseSignalInfo where
    type HaskellCallbackType InfoBarCloseSignalInfo = InfoBarCloseCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_InfoBarCloseCallback cb
        cb'' <- mk_InfoBarCloseCallback cb'
        connectSignalFunPtr obj "close" cb'' connectMode detail

#endif

-- signal InfoBar::response
-- | Emitted when an action widget is clicked or the application programmer
-- calls 'GI.Gtk.Objects.InfoBar.infoBarResponse'. The /@responseId@/ depends on which action
-- widget was clicked.
type InfoBarResponseCallback =
    Int32
    -- ^ /@responseId@/: the response ID
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `InfoBarResponseCallback`@.
noInfoBarResponseCallback :: Maybe InfoBarResponseCallback
noInfoBarResponseCallback :: Maybe InfoBarResponseCallback
noInfoBarResponseCallback = Maybe InfoBarResponseCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_InfoBarResponseCallback =
    Ptr () ->                               -- object
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_InfoBarResponse :: MonadIO m => InfoBarResponseCallback -> m (GClosure C_InfoBarResponseCallback)
genClosure_InfoBarResponse :: InfoBarResponseCallback -> m (GClosure C_InfoBarResponseCallback)
genClosure_InfoBarResponse InfoBarResponseCallback
cb = IO (GClosure C_InfoBarResponseCallback)
-> m (GClosure C_InfoBarResponseCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_InfoBarResponseCallback)
 -> m (GClosure C_InfoBarResponseCallback))
-> IO (GClosure C_InfoBarResponseCallback)
-> m (GClosure C_InfoBarResponseCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_InfoBarResponseCallback
cb' = InfoBarResponseCallback -> C_InfoBarResponseCallback
wrap_InfoBarResponseCallback InfoBarResponseCallback
cb
    C_InfoBarResponseCallback -> IO (FunPtr C_InfoBarResponseCallback)
mk_InfoBarResponseCallback C_InfoBarResponseCallback
cb' IO (FunPtr C_InfoBarResponseCallback)
-> (FunPtr C_InfoBarResponseCallback
    -> IO (GClosure C_InfoBarResponseCallback))
-> IO (GClosure C_InfoBarResponseCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_InfoBarResponseCallback
-> IO (GClosure C_InfoBarResponseCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `InfoBarResponseCallback` into a `C_InfoBarResponseCallback`.
wrap_InfoBarResponseCallback ::
    InfoBarResponseCallback ->
    C_InfoBarResponseCallback
wrap_InfoBarResponseCallback :: InfoBarResponseCallback -> C_InfoBarResponseCallback
wrap_InfoBarResponseCallback InfoBarResponseCallback
_cb Ptr ()
_ Int32
responseId Ptr ()
_ = do
    InfoBarResponseCallback
_cb  Int32
responseId


-- | Connect a signal handler for the [response](#signal:response) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' infoBar #response callback
-- @
-- 
-- 
onInfoBarResponse :: (IsInfoBar a, MonadIO m) => a -> InfoBarResponseCallback -> m SignalHandlerId
onInfoBarResponse :: a -> InfoBarResponseCallback -> m SignalHandlerId
onInfoBarResponse a
obj InfoBarResponseCallback
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_InfoBarResponseCallback
cb' = InfoBarResponseCallback -> C_InfoBarResponseCallback
wrap_InfoBarResponseCallback InfoBarResponseCallback
cb
    FunPtr C_InfoBarResponseCallback
cb'' <- C_InfoBarResponseCallback -> IO (FunPtr C_InfoBarResponseCallback)
mk_InfoBarResponseCallback C_InfoBarResponseCallback
cb'
    a
-> Text
-> FunPtr C_InfoBarResponseCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"response" FunPtr C_InfoBarResponseCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [response](#signal:response) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' infoBar #response callback
-- @
-- 
-- 
afterInfoBarResponse :: (IsInfoBar a, MonadIO m) => a -> InfoBarResponseCallback -> m SignalHandlerId
afterInfoBarResponse :: a -> InfoBarResponseCallback -> m SignalHandlerId
afterInfoBarResponse a
obj InfoBarResponseCallback
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_InfoBarResponseCallback
cb' = InfoBarResponseCallback -> C_InfoBarResponseCallback
wrap_InfoBarResponseCallback InfoBarResponseCallback
cb
    FunPtr C_InfoBarResponseCallback
cb'' <- C_InfoBarResponseCallback -> IO (FunPtr C_InfoBarResponseCallback)
mk_InfoBarResponseCallback C_InfoBarResponseCallback
cb'
    a
-> Text
-> FunPtr C_InfoBarResponseCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"response" FunPtr C_InfoBarResponseCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data InfoBarResponseSignalInfo
instance SignalInfo InfoBarResponseSignalInfo where
    type HaskellCallbackType InfoBarResponseSignalInfo = InfoBarResponseCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_InfoBarResponseCallback cb
        cb'' <- mk_InfoBarResponseCallback cb'
        connectSignalFunPtr obj "response" cb'' connectMode detail

#endif

-- VVV Prop "message-type"
   -- Type: TInterface (Name {namespace = "Gtk", name = "MessageType"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@message-type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' infoBar #messageType
-- @
getInfoBarMessageType :: (MonadIO m, IsInfoBar o) => o -> m Gtk.Enums.MessageType
getInfoBarMessageType :: o -> m MessageType
getInfoBarMessageType o
obj = IO MessageType -> m MessageType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MessageType -> m MessageType)
-> IO MessageType -> m MessageType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO MessageType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"message-type"

-- | Set the value of the “@message-type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' infoBar [ #messageType 'Data.GI.Base.Attributes.:=' value ]
-- @
setInfoBarMessageType :: (MonadIO m, IsInfoBar o) => o -> Gtk.Enums.MessageType -> m ()
setInfoBarMessageType :: o -> MessageType -> m ()
setInfoBarMessageType o
obj MessageType
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 -> MessageType -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"message-type" MessageType
val

-- | Construct a `GValueConstruct` with valid value for the “@message-type@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructInfoBarMessageType :: (IsInfoBar o, MIO.MonadIO m) => Gtk.Enums.MessageType -> m (GValueConstruct o)
constructInfoBarMessageType :: MessageType -> m (GValueConstruct o)
constructInfoBarMessageType MessageType
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
$ String -> MessageType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"message-type" MessageType
val

#if defined(ENABLE_OVERLOADING)
data InfoBarMessageTypePropertyInfo
instance AttrInfo InfoBarMessageTypePropertyInfo where
    type AttrAllowedOps InfoBarMessageTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint InfoBarMessageTypePropertyInfo = IsInfoBar
    type AttrSetTypeConstraint InfoBarMessageTypePropertyInfo = (~) Gtk.Enums.MessageType
    type AttrTransferTypeConstraint InfoBarMessageTypePropertyInfo = (~) Gtk.Enums.MessageType
    type AttrTransferType InfoBarMessageTypePropertyInfo = Gtk.Enums.MessageType
    type AttrGetType InfoBarMessageTypePropertyInfo = Gtk.Enums.MessageType
    type AttrLabel InfoBarMessageTypePropertyInfo = "message-type"
    type AttrOrigin InfoBarMessageTypePropertyInfo = InfoBar
    attrGet = getInfoBarMessageType
    attrSet = setInfoBarMessageType
    attrTransfer _ v = do
        return v
    attrConstruct = constructInfoBarMessageType
    attrClear = undefined
#endif

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

-- | Get the value of the “@revealed@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' infoBar #revealed
-- @
getInfoBarRevealed :: (MonadIO m, IsInfoBar o) => o -> m Bool
getInfoBarRevealed :: o -> m Bool
getInfoBarRevealed 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 String
"revealed"

-- | Set the value of the “@revealed@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' infoBar [ #revealed 'Data.GI.Base.Attributes.:=' value ]
-- @
setInfoBarRevealed :: (MonadIO m, IsInfoBar o) => o -> Bool -> m ()
setInfoBarRevealed :: o -> Bool -> m ()
setInfoBarRevealed o
obj 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 String
"revealed" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@revealed@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructInfoBarRevealed :: (IsInfoBar o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructInfoBarRevealed :: Bool -> m (GValueConstruct o)
constructInfoBarRevealed 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
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"revealed" Bool
val

#if defined(ENABLE_OVERLOADING)
data InfoBarRevealedPropertyInfo
instance AttrInfo InfoBarRevealedPropertyInfo where
    type AttrAllowedOps InfoBarRevealedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint InfoBarRevealedPropertyInfo = IsInfoBar
    type AttrSetTypeConstraint InfoBarRevealedPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint InfoBarRevealedPropertyInfo = (~) Bool
    type AttrTransferType InfoBarRevealedPropertyInfo = Bool
    type AttrGetType InfoBarRevealedPropertyInfo = Bool
    type AttrLabel InfoBarRevealedPropertyInfo = "revealed"
    type AttrOrigin InfoBarRevealedPropertyInfo = InfoBar
    attrGet = getInfoBarRevealed
    attrSet = setInfoBarRevealed
    attrTransfer _ v = do
        return v
    attrConstruct = constructInfoBarRevealed
    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' infoBar #showCloseButton
-- @
getInfoBarShowCloseButton :: (MonadIO m, IsInfoBar o) => o -> m Bool
getInfoBarShowCloseButton :: o -> m Bool
getInfoBarShowCloseButton 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 String
"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' infoBar [ #showCloseButton 'Data.GI.Base.Attributes.:=' value ]
-- @
setInfoBarShowCloseButton :: (MonadIO m, IsInfoBar o) => o -> Bool -> m ()
setInfoBarShowCloseButton :: o -> Bool -> m ()
setInfoBarShowCloseButton o
obj 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 String
"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`.
constructInfoBarShowCloseButton :: (IsInfoBar o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructInfoBarShowCloseButton :: Bool -> m (GValueConstruct o)
constructInfoBarShowCloseButton 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
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"show-close-button" Bool
val

#if defined(ENABLE_OVERLOADING)
data InfoBarShowCloseButtonPropertyInfo
instance AttrInfo InfoBarShowCloseButtonPropertyInfo where
    type AttrAllowedOps InfoBarShowCloseButtonPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint InfoBarShowCloseButtonPropertyInfo = IsInfoBar
    type AttrSetTypeConstraint InfoBarShowCloseButtonPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint InfoBarShowCloseButtonPropertyInfo = (~) Bool
    type AttrTransferType InfoBarShowCloseButtonPropertyInfo = Bool
    type AttrGetType InfoBarShowCloseButtonPropertyInfo = Bool
    type AttrLabel InfoBarShowCloseButtonPropertyInfo = "show-close-button"
    type AttrOrigin InfoBarShowCloseButtonPropertyInfo = InfoBar
    attrGet = getInfoBarShowCloseButton
    attrSet = setInfoBarShowCloseButton
    attrTransfer _ v = do
        return v
    attrConstruct = constructInfoBarShowCloseButton
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList InfoBar
type instance O.AttributeList InfoBar = InfoBarAttributeList
type InfoBarAttributeList = ('[ '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("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), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("messageType", InfoBarMessageTypePropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("revealed", InfoBarRevealedPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("showCloseButton", InfoBarShowCloseButtonPropertyInfo), '("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)
infoBarMessageType :: AttrLabelProxy "messageType"
infoBarMessageType = AttrLabelProxy

infoBarRevealed :: AttrLabelProxy "revealed"
infoBarRevealed = AttrLabelProxy

infoBarShowCloseButton :: AttrLabelProxy "showCloseButton"
infoBarShowCloseButton = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList InfoBar = InfoBarSignalList
type InfoBarSignalList = ('[ '("close", InfoBarCloseSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("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), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("response", InfoBarResponseSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_info_bar_new" gtk_info_bar_new :: 
    IO (Ptr InfoBar)

-- | Creates a new t'GI.Gtk.Objects.InfoBar.InfoBar' object.
infoBarNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m InfoBar
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.InfoBar.InfoBar' object
infoBarNew :: m InfoBar
infoBarNew  = IO InfoBar -> m InfoBar
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InfoBar -> m InfoBar) -> IO InfoBar -> m InfoBar
forall a b. (a -> b) -> a -> b
$ do
    Ptr InfoBar
result <- IO (Ptr InfoBar)
gtk_info_bar_new
    Text -> Ptr InfoBar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"infoBarNew" Ptr InfoBar
result
    InfoBar
result' <- ((ManagedPtr InfoBar -> InfoBar) -> Ptr InfoBar -> IO InfoBar
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InfoBar -> InfoBar
InfoBar) Ptr InfoBar
result
    InfoBar -> IO InfoBar
forall (m :: * -> *) a. Monad m => a -> m a
return InfoBar
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method InfoBar::add_action_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an activatable widget"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "response_id"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "response ID for @child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_add_action_widget" gtk_info_bar_add_action_widget :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    Int32 ->                                -- response_id : TBasicType TInt
    IO ()

-- | Add an activatable widget to the action area of a t'GI.Gtk.Objects.InfoBar.InfoBar',
-- connecting a signal handler that will emit the [response]("GI.Gtk.Objects.InfoBar#g:signal:response")
-- signal on the message area when the widget is activated. The widget
-- is appended to the end of the message areas action area.
infoBarAddActionWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> b
    -- ^ /@child@/: an activatable widget
    -> Int32
    -- ^ /@responseId@/: response ID for /@child@/
    -> m ()
infoBarAddActionWidget :: a -> b -> Int32 -> m ()
infoBarAddActionWidget a
infoBar b
child Int32
responseId = 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr InfoBar -> Ptr Widget -> InfoBarResponseCallback
gtk_info_bar_add_action_widget Ptr InfoBar
infoBar' Ptr Widget
child' Int32
responseId
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data InfoBarAddActionWidgetMethodInfo
instance (signature ~ (b -> Int32 -> m ()), MonadIO m, IsInfoBar a, Gtk.Widget.IsWidget b) => O.MethodInfo InfoBarAddActionWidgetMethodInfo a signature where
    overloadedMethod = infoBarAddActionWidget

#endif

-- method InfoBar::add_button
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "button_text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "text of button" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "response_id"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "response ID for the button"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Button" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_add_button" gtk_info_bar_add_button :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    CString ->                              -- button_text : TBasicType TUTF8
    Int32 ->                                -- response_id : TBasicType TInt
    IO (Ptr Gtk.Button.Button)

-- | Adds a button with the given text and sets things up so that
-- clicking the button will emit the “response” signal with the given
-- response_id. The button is appended to the end of the info bars\'s
-- action area. The button widget is returned, but usually you don\'t
-- need it.
infoBarAddButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> T.Text
    -- ^ /@buttonText@/: text of button
    -> Int32
    -- ^ /@responseId@/: response ID for the button
    -> m Gtk.Button.Button
    -- ^ __Returns:__ the t'GI.Gtk.Objects.Button.Button' widget
    -- that was added
infoBarAddButton :: a -> Text -> Int32 -> m Button
infoBarAddButton a
infoBar Text
buttonText Int32
responseId = IO Button -> m Button
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Button -> m Button) -> IO Button -> m Button
forall a b. (a -> b) -> a -> b
$ do
    Ptr InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    CString
buttonText' <- Text -> IO CString
textToCString Text
buttonText
    Ptr Button
result <- Ptr InfoBar -> CString -> Int32 -> IO (Ptr Button)
gtk_info_bar_add_button Ptr InfoBar
infoBar' CString
buttonText' Int32
responseId
    Text -> Ptr Button -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"infoBarAddButton" Ptr Button
result
    Button
result' <- ((ManagedPtr Button -> Button) -> Ptr Button -> IO Button
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Button -> Button
Gtk.Button.Button) Ptr Button
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
buttonText'
    Button -> IO Button
forall (m :: * -> *) a. Monad m => a -> m a
return Button
result'

#if defined(ENABLE_OVERLOADING)
data InfoBarAddButtonMethodInfo
instance (signature ~ (T.Text -> Int32 -> m Gtk.Button.Button), MonadIO m, IsInfoBar a) => O.MethodInfo InfoBarAddButtonMethodInfo a signature where
    overloadedMethod = infoBarAddButton

#endif

-- method InfoBar::add_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the child to be added"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_add_child" gtk_info_bar_add_child :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Adds a widget to the content area of the info bar.
infoBarAddChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> b
    -- ^ /@widget@/: the child to be added
    -> m ()
infoBarAddChild :: a -> b -> m ()
infoBarAddChild a
infoBar 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr InfoBar -> Ptr Widget -> IO ()
gtk_info_bar_add_child Ptr InfoBar
infoBar' Ptr Widget
widget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data InfoBarAddChildMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsInfoBar a, Gtk.Widget.IsWidget b) => O.MethodInfo InfoBarAddChildMethodInfo a signature where
    overloadedMethod = infoBarAddChild

#endif

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

foreign import ccall "gtk_info_bar_get_message_type" gtk_info_bar_get_message_type :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    IO CUInt

-- | Returns the message type of the message area.
infoBarGetMessageType ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> m Gtk.Enums.MessageType
    -- ^ __Returns:__ the message type of the message area.
infoBarGetMessageType :: a -> m MessageType
infoBarGetMessageType a
infoBar = IO MessageType -> m MessageType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MessageType -> m MessageType)
-> IO MessageType -> m MessageType
forall a b. (a -> b) -> a -> b
$ do
    Ptr InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    CUInt
result <- Ptr InfoBar -> IO CUInt
gtk_info_bar_get_message_type Ptr InfoBar
infoBar'
    let result' :: MessageType
result' = (Int -> MessageType
forall a. Enum a => Int -> a
toEnum (Int -> MessageType) -> (CUInt -> Int) -> CUInt -> MessageType
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
infoBar
    MessageType -> IO MessageType
forall (m :: * -> *) a. Monad m => a -> m a
return MessageType
result'

#if defined(ENABLE_OVERLOADING)
data InfoBarGetMessageTypeMethodInfo
instance (signature ~ (m Gtk.Enums.MessageType), MonadIO m, IsInfoBar a) => O.MethodInfo InfoBarGetMessageTypeMethodInfo a signature where
    overloadedMethod = infoBarGetMessageType

#endif

-- method InfoBar::get_revealed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , 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_info_bar_get_revealed" gtk_info_bar_get_revealed :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    IO CInt

-- | Returns whether the info bar is currently revealed.
infoBarGetRevealed ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> m Bool
    -- ^ __Returns:__ the current value of the t'GI.Gtk.Objects.InfoBar.InfoBar':@/revealed/@ property
infoBarGetRevealed :: a -> m Bool
infoBarGetRevealed a
infoBar = 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    CInt
result <- Ptr InfoBar -> IO CInt
gtk_info_bar_get_revealed Ptr InfoBar
infoBar'
    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
infoBar
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InfoBarGetRevealedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInfoBar a) => O.MethodInfo InfoBarGetRevealedMethodInfo a signature where
    overloadedMethod = infoBarGetRevealed

#endif

-- method InfoBar::get_show_close_button
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , 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_info_bar_get_show_close_button" gtk_info_bar_get_show_close_button :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    IO CInt

-- | Returns whether the widget will display a standard close button.
infoBarGetShowCloseButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the widget displays standard close button
infoBarGetShowCloseButton :: a -> m Bool
infoBarGetShowCloseButton a
infoBar = 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    CInt
result <- Ptr InfoBar -> IO CInt
gtk_info_bar_get_show_close_button Ptr InfoBar
infoBar'
    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
infoBar
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data InfoBarGetShowCloseButtonMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsInfoBar a) => O.MethodInfo InfoBarGetShowCloseButtonMethodInfo a signature where
    overloadedMethod = infoBarGetShowCloseButton

#endif

-- method InfoBar::remove_action_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an action widget to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_remove_action_widget" gtk_info_bar_remove_action_widget :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Removes a widget from the action area of /@infoBar@/, after
-- it been put there by a call to 'GI.Gtk.Objects.InfoBar.infoBarAddActionWidget'
-- or 'GI.Gtk.Objects.InfoBar.infoBarAddButton'.
infoBarRemoveActionWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> b
    -- ^ /@widget@/: an action widget to remove
    -> m ()
infoBarRemoveActionWidget :: a -> b -> m ()
infoBarRemoveActionWidget a
infoBar 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr InfoBar -> Ptr Widget -> IO ()
gtk_info_bar_remove_action_widget Ptr InfoBar
infoBar' Ptr Widget
widget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data InfoBarRemoveActionWidgetMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsInfoBar a, Gtk.Widget.IsWidget b) => O.MethodInfo InfoBarRemoveActionWidgetMethodInfo a signature where
    overloadedMethod = infoBarRemoveActionWidget

#endif

-- method InfoBar::remove_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a child that has been added to the content area"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_remove_child" gtk_info_bar_remove_child :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Removes a widget from the content area of the info bar,
-- after it has been added with 'GI.Gtk.Objects.InfoBar.infoBarAddChild'.
infoBarRemoveChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> b
    -- ^ /@widget@/: a child that has been added to the content area
    -> m ()
infoBarRemoveChild :: a -> b -> m ()
infoBarRemoveChild a
infoBar 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr InfoBar -> Ptr Widget -> IO ()
gtk_info_bar_remove_child Ptr InfoBar
infoBar' Ptr Widget
widget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data InfoBarRemoveChildMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsInfoBar a, Gtk.Widget.IsWidget b) => O.MethodInfo InfoBarRemoveChildMethodInfo a signature where
    overloadedMethod = infoBarRemoveChild

#endif

-- method InfoBar::response
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "response_id"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a response ID" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_response" gtk_info_bar_response :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    Int32 ->                                -- response_id : TBasicType TInt
    IO ()

-- | Emits the “response” signal with the given /@responseId@/.
infoBarResponse ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> Int32
    -- ^ /@responseId@/: a response ID
    -> m ()
infoBarResponse :: a -> Int32 -> m ()
infoBarResponse a
infoBar Int32
responseId = 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    Ptr InfoBar -> InfoBarResponseCallback
gtk_info_bar_response Ptr InfoBar
infoBar' Int32
responseId
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data InfoBarResponseMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsInfoBar a) => O.MethodInfo InfoBarResponseMethodInfo a signature where
    overloadedMethod = infoBarResponse

#endif

-- method InfoBar::set_default_response
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "response_id"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a response ID" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_set_default_response" gtk_info_bar_set_default_response :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    Int32 ->                                -- response_id : TBasicType TInt
    IO ()

-- | Sets the last widget in the info bar’s action area with
-- the given response_id as the default widget for the dialog.
-- Pressing “Enter” normally activates the default widget.
-- 
-- Note that this function currently requires /@infoBar@/ to
-- be added to a widget hierarchy.
infoBarSetDefaultResponse ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> Int32
    -- ^ /@responseId@/: a response ID
    -> m ()
infoBarSetDefaultResponse :: a -> Int32 -> m ()
infoBarSetDefaultResponse a
infoBar Int32
responseId = 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    Ptr InfoBar -> InfoBarResponseCallback
gtk_info_bar_set_default_response Ptr InfoBar
infoBar' Int32
responseId
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data InfoBarSetDefaultResponseMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsInfoBar a) => O.MethodInfo InfoBarSetDefaultResponseMethodInfo a signature where
    overloadedMethod = infoBarSetDefaultResponse

#endif

-- method InfoBar::set_message_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "message_type"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "MessageType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkMessageType" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_set_message_type" gtk_info_bar_set_message_type :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    CUInt ->                                -- message_type : TInterface (Name {namespace = "Gtk", name = "MessageType"})
    IO ()

-- | Sets the message type of the message area.
-- 
-- GTK+ uses this type to determine how the message is displayed.
infoBarSetMessageType ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> Gtk.Enums.MessageType
    -- ^ /@messageType@/: a t'GI.Gtk.Enums.MessageType'
    -> m ()
infoBarSetMessageType :: a -> MessageType -> m ()
infoBarSetMessageType a
infoBar MessageType
messageType = 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    let messageType' :: CUInt
messageType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (MessageType -> Int) -> MessageType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MessageType -> Int
forall a. Enum a => a -> Int
fromEnum) MessageType
messageType
    Ptr InfoBar -> CUInt -> IO ()
gtk_info_bar_set_message_type Ptr InfoBar
infoBar' CUInt
messageType'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data InfoBarSetMessageTypeMethodInfo
instance (signature ~ (Gtk.Enums.MessageType -> m ()), MonadIO m, IsInfoBar a) => O.MethodInfo InfoBarSetMessageTypeMethodInfo a signature where
    overloadedMethod = infoBarSetMessageType

#endif

-- method InfoBar::set_response_sensitive
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "response_id"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a response ID" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setting"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "TRUE for sensitive" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_set_response_sensitive" gtk_info_bar_set_response_sensitive :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    Int32 ->                                -- response_id : TBasicType TInt
    CInt ->                                 -- setting : TBasicType TBoolean
    IO ()

-- | Calls gtk_widget_set_sensitive (widget, setting) for each
-- widget in the info bars’s action area with the given response_id.
-- A convenient way to sensitize\/desensitize dialog buttons.
infoBarSetResponseSensitive ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> Int32
    -- ^ /@responseId@/: a response ID
    -> Bool
    -- ^ /@setting@/: TRUE for sensitive
    -> m ()
infoBarSetResponseSensitive :: a -> Int32 -> Bool -> m ()
infoBarSetResponseSensitive a
infoBar Int32
responseId 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    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 InfoBar -> Int32 -> CInt -> IO ()
gtk_info_bar_set_response_sensitive Ptr InfoBar
infoBar' Int32
responseId CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data InfoBarSetResponseSensitiveMethodInfo
instance (signature ~ (Int32 -> Bool -> m ()), MonadIO m, IsInfoBar a) => O.MethodInfo InfoBarSetResponseSensitiveMethodInfo a signature where
    overloadedMethod = infoBarSetResponseSensitive

#endif

-- method InfoBar::set_revealed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "revealed"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The new value of the property"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_set_revealed" gtk_info_bar_set_revealed :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    CInt ->                                 -- revealed : TBasicType TBoolean
    IO ()

-- | Sets the t'GI.Gtk.Objects.InfoBar.InfoBar':@/revealed/@ property to /@revealed@/. Changing this will make
-- /@infoBar@/ reveal ('P.True') or conceal ('P.False') itself via a sliding transition.
-- 
-- Note: this does not show or hide /@infoBar@/ in the t'GI.Gtk.Objects.Widget.Widget':@/visible/@ sense,
-- so revealing has no effect if t'GI.Gtk.Objects.Widget.Widget':@/visible/@ is 'P.False'.
infoBarSetRevealed ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> Bool
    -- ^ /@revealed@/: The new value of the property
    -> m ()
infoBarSetRevealed :: a -> Bool -> m ()
infoBarSetRevealed a
infoBar Bool
revealed = 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    let revealed' :: CInt
revealed' = (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
revealed
    Ptr InfoBar -> CInt -> IO ()
gtk_info_bar_set_revealed Ptr InfoBar
infoBar' CInt
revealed'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data InfoBarSetRevealedMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsInfoBar a) => O.MethodInfo InfoBarSetRevealedMethodInfo a signature where
    overloadedMethod = infoBarSetRevealed

#endif

-- method InfoBar::set_show_close_button
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_bar"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "InfoBar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkInfoBar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setting"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to include a close button"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_info_bar_set_show_close_button" gtk_info_bar_set_show_close_button :: 
    Ptr InfoBar ->                          -- info_bar : TInterface (Name {namespace = "Gtk", name = "InfoBar"})
    CInt ->                                 -- setting : TBasicType TBoolean
    IO ()

-- | If true, a standard close button is shown. When clicked it emits
-- the response 'GI.Gtk.Enums.ResponseTypeClose'.
infoBarSetShowCloseButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsInfoBar a) =>
    a
    -- ^ /@infoBar@/: a t'GI.Gtk.Objects.InfoBar.InfoBar'
    -> Bool
    -- ^ /@setting@/: 'P.True' to include a close button
    -> m ()
infoBarSetShowCloseButton :: a -> Bool -> m ()
infoBarSetShowCloseButton a
infoBar 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 InfoBar
infoBar' <- a -> IO (Ptr InfoBar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
infoBar
    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 InfoBar -> CInt -> IO ()
gtk_info_bar_set_show_close_button Ptr InfoBar
infoBar' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
infoBar
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data InfoBarSetShowCloseButtonMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsInfoBar a) => O.MethodInfo InfoBarSetShowCloseButtonMethodInfo a signature where
    overloadedMethod = infoBarSetShowCloseButton

#endif