{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gtk.Objects.FileChooserButton.FileChooserButton' is a widget that lets the user select a
-- file.  It implements the t'GI.Gtk.Interfaces.FileChooser.FileChooser' interface.  Visually, it is a
-- file name with a button to bring up a t'GI.Gtk.Objects.FileChooserDialog.FileChooserDialog'.
-- The user can then use that dialog to change the file associated with
-- that button.  This widget does not support setting the
-- t'GI.Gtk.Interfaces.FileChooser.FileChooser':@/select-multiple/@ property to 'P.True'.
-- 
-- == Create a button to let the user select a file in \/etc
-- 
-- 
-- === /C code/
-- >
-- >{
-- >  GtkWidget *button;
-- >  GFile *cwd = g_file_new_for_path ("/etc");
-- >
-- >  button = gtk_file_chooser_button_new (_("Select a file"),
-- >                                        GTK_FILE_CHOOSER_ACTION_OPEN);
-- >  gtk_file_chooser_set_current_folder (GTK_FILE_CHOOSER (button), cwd);
-- >  g_object_unref (cwd);
-- >}
-- 
-- 
-- The t'GI.Gtk.Objects.FileChooserButton.FileChooserButton' supports the @/GtkFileChooserActions/@
-- 'GI.Gtk.Enums.FileChooserActionOpen' and 'GI.Gtk.Enums.FileChooserActionSelectFolder'.
-- 
-- > The t'GI.Gtk.Objects.FileChooserButton.FileChooserButton' will ellipsize the label, and will thus
-- > request little horizontal space.  To give the button more space,
-- > you should call 'GI.Gtk.Objects.Widget.widgetGetPreferredSize',
-- > 'GI.Gtk.Objects.FileChooserButton.fileChooserButtonSetWidthChars', or pack the button in
-- > such a way that other interface elements give space to the
-- > widget.
-- 
-- = CSS nodes
-- 
-- GtkFileChooserButton has a single CSS node with the name “filechooserbutton”.

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

module GI.Gtk.Objects.FileChooserButton
    ( 

-- * Exported types
    FileChooserButton(..)                   ,
    IsFileChooserButton                     ,
    toFileChooserButton                     ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveFileChooserButtonMethod          ,
#endif


-- ** getModal #method:getModal#

#if defined(ENABLE_OVERLOADING)
    FileChooserButtonGetModalMethodInfo     ,
#endif
    fileChooserButtonGetModal               ,


-- ** getTitle #method:getTitle#

#if defined(ENABLE_OVERLOADING)
    FileChooserButtonGetTitleMethodInfo     ,
#endif
    fileChooserButtonGetTitle               ,


-- ** getWidthChars #method:getWidthChars#

#if defined(ENABLE_OVERLOADING)
    FileChooserButtonGetWidthCharsMethodInfo,
#endif
    fileChooserButtonGetWidthChars          ,


-- ** new #method:new#

    fileChooserButtonNew                    ,


-- ** newWithDialog #method:newWithDialog#

    fileChooserButtonNewWithDialog          ,


-- ** setModal #method:setModal#

#if defined(ENABLE_OVERLOADING)
    FileChooserButtonSetModalMethodInfo     ,
#endif
    fileChooserButtonSetModal               ,


-- ** setTitle #method:setTitle#

#if defined(ENABLE_OVERLOADING)
    FileChooserButtonSetTitleMethodInfo     ,
#endif
    fileChooserButtonSetTitle               ,


-- ** setWidthChars #method:setWidthChars#

#if defined(ENABLE_OVERLOADING)
    FileChooserButtonSetWidthCharsMethodInfo,
#endif
    fileChooserButtonSetWidthChars          ,




 -- * Properties
-- ** dialog #attr:dialog#
-- | Instance of the t'GI.Gtk.Objects.FileChooserDialog.FileChooserDialog' associated with the button.

#if defined(ENABLE_OVERLOADING)
    FileChooserButtonDialogPropertyInfo     ,
#endif
    constructFileChooserButtonDialog        ,
#if defined(ENABLE_OVERLOADING)
    fileChooserButtonDialog                 ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    FileChooserButtonModalPropertyInfo      ,
#endif
    constructFileChooserButtonModal         ,
#if defined(ENABLE_OVERLOADING)
    fileChooserButtonModal                  ,
#endif
    getFileChooserButtonModal               ,
    setFileChooserButtonModal               ,


-- ** title #attr:title#
-- | Title to put on the t'GI.Gtk.Objects.FileChooserDialog.FileChooserDialog' associated with the button.

#if defined(ENABLE_OVERLOADING)
    FileChooserButtonTitlePropertyInfo      ,
#endif
    constructFileChooserButtonTitle         ,
#if defined(ENABLE_OVERLOADING)
    fileChooserButtonTitle                  ,
#endif
    getFileChooserButtonTitle               ,
    setFileChooserButtonTitle               ,


-- ** widthChars #attr:widthChars#
-- | The width of the entry and label inside the button, in characters.

#if defined(ENABLE_OVERLOADING)
    FileChooserButtonWidthCharsPropertyInfo ,
#endif
    constructFileChooserButtonWidthChars    ,
#if defined(ENABLE_OVERLOADING)
    fileChooserButtonWidthChars             ,
#endif
    getFileChooserButtonWidthChars          ,
    setFileChooserButtonWidthChars          ,




 -- * Signals
-- ** fileSet #signal:fileSet#

    C_FileChooserButtonFileSetCallback      ,
    FileChooserButtonFileSetCallback        ,
#if defined(ENABLE_OVERLOADING)
    FileChooserButtonFileSetSignalInfo      ,
#endif
    afterFileChooserButtonFileSet           ,
    genClosure_FileChooserButtonFileSet     ,
    mk_FileChooserButtonFileSetCallback     ,
    noFileChooserButtonFileSetCallback      ,
    onFileChooserButtonFileSet              ,
    wrap_FileChooserButtonFileSetCallback   ,




    ) 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.Interfaces.FileChooser as Gtk.FileChooser
import {-# SOURCE #-} qualified GI.Gtk.Objects.Dialog as Gtk.Dialog
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_file_chooser_button_get_type"
    c_gtk_file_chooser_button_get_type :: IO B.Types.GType

instance B.Types.TypedObject FileChooserButton where
    glibType :: IO GType
glibType = IO GType
c_gtk_file_chooser_button_get_type

instance B.Types.GObject FileChooserButton

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

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

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

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

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

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

#endif

-- signal FileChooserButton::file-set
-- | The [fileSet](#g:signal:fileSet) signal is emitted when the user selects a file.
-- 
-- Note that this signal is only emitted when the user
-- changes the file.
type FileChooserButtonFileSetCallback =
    IO ()

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

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_FileChooserButtonFileSet :: MonadIO m => FileChooserButtonFileSetCallback -> m (GClosure C_FileChooserButtonFileSetCallback)
genClosure_FileChooserButtonFileSet :: IO () -> m (GClosure C_FileChooserButtonFileSetCallback)
genClosure_FileChooserButtonFileSet IO ()
cb = IO (GClosure C_FileChooserButtonFileSetCallback)
-> m (GClosure C_FileChooserButtonFileSetCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FileChooserButtonFileSetCallback)
 -> m (GClosure C_FileChooserButtonFileSetCallback))
-> IO (GClosure C_FileChooserButtonFileSetCallback)
-> m (GClosure C_FileChooserButtonFileSetCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_FileChooserButtonFileSetCallback
cb' = IO () -> C_FileChooserButtonFileSetCallback
wrap_FileChooserButtonFileSetCallback IO ()
cb
    C_FileChooserButtonFileSetCallback
-> IO (FunPtr C_FileChooserButtonFileSetCallback)
mk_FileChooserButtonFileSetCallback C_FileChooserButtonFileSetCallback
cb' IO (FunPtr C_FileChooserButtonFileSetCallback)
-> (FunPtr C_FileChooserButtonFileSetCallback
    -> IO (GClosure C_FileChooserButtonFileSetCallback))
-> IO (GClosure C_FileChooserButtonFileSetCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FileChooserButtonFileSetCallback
-> IO (GClosure C_FileChooserButtonFileSetCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `FileChooserButtonFileSetCallback` into a `C_FileChooserButtonFileSetCallback`.
wrap_FileChooserButtonFileSetCallback ::
    FileChooserButtonFileSetCallback ->
    C_FileChooserButtonFileSetCallback
wrap_FileChooserButtonFileSetCallback :: IO () -> C_FileChooserButtonFileSetCallback
wrap_FileChooserButtonFileSetCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [fileSet](#signal:fileSet) 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' fileChooserButton #fileSet callback
-- @
-- 
-- 
onFileChooserButtonFileSet :: (IsFileChooserButton a, MonadIO m) => a -> FileChooserButtonFileSetCallback -> m SignalHandlerId
onFileChooserButtonFileSet :: a -> IO () -> m SignalHandlerId
onFileChooserButtonFileSet 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_FileChooserButtonFileSetCallback
cb' = IO () -> C_FileChooserButtonFileSetCallback
wrap_FileChooserButtonFileSetCallback IO ()
cb
    FunPtr C_FileChooserButtonFileSetCallback
cb'' <- C_FileChooserButtonFileSetCallback
-> IO (FunPtr C_FileChooserButtonFileSetCallback)
mk_FileChooserButtonFileSetCallback C_FileChooserButtonFileSetCallback
cb'
    a
-> Text
-> FunPtr C_FileChooserButtonFileSetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"file-set" FunPtr C_FileChooserButtonFileSetCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [fileSet](#signal:fileSet) 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' fileChooserButton #fileSet callback
-- @
-- 
-- 
afterFileChooserButtonFileSet :: (IsFileChooserButton a, MonadIO m) => a -> FileChooserButtonFileSetCallback -> m SignalHandlerId
afterFileChooserButtonFileSet :: a -> IO () -> m SignalHandlerId
afterFileChooserButtonFileSet 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_FileChooserButtonFileSetCallback
cb' = IO () -> C_FileChooserButtonFileSetCallback
wrap_FileChooserButtonFileSetCallback IO ()
cb
    FunPtr C_FileChooserButtonFileSetCallback
cb'' <- C_FileChooserButtonFileSetCallback
-> IO (FunPtr C_FileChooserButtonFileSetCallback)
mk_FileChooserButtonFileSetCallback C_FileChooserButtonFileSetCallback
cb'
    a
-> Text
-> FunPtr C_FileChooserButtonFileSetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"file-set" FunPtr C_FileChooserButtonFileSetCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data FileChooserButtonFileSetSignalInfo
instance SignalInfo FileChooserButtonFileSetSignalInfo where
    type HaskellCallbackType FileChooserButtonFileSetSignalInfo = FileChooserButtonFileSetCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_FileChooserButtonFileSetCallback cb
        cb'' <- mk_FileChooserButtonFileSetCallback cb'
        connectSignalFunPtr obj "file-set" cb'' connectMode detail

#endif

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

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

#if defined(ENABLE_OVERLOADING)
data FileChooserButtonDialogPropertyInfo
instance AttrInfo FileChooserButtonDialogPropertyInfo where
    type AttrAllowedOps FileChooserButtonDialogPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint FileChooserButtonDialogPropertyInfo = IsFileChooserButton
    type AttrSetTypeConstraint FileChooserButtonDialogPropertyInfo = Gtk.FileChooser.IsFileChooser
    type AttrTransferTypeConstraint FileChooserButtonDialogPropertyInfo = Gtk.FileChooser.IsFileChooser
    type AttrTransferType FileChooserButtonDialogPropertyInfo = Gtk.FileChooser.FileChooser
    type AttrGetType FileChooserButtonDialogPropertyInfo = ()
    type AttrLabel FileChooserButtonDialogPropertyInfo = "dialog"
    type AttrOrigin FileChooserButtonDialogPropertyInfo = FileChooserButton
    attrGet = undefined
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.FileChooser.FileChooser v
    attrConstruct = constructFileChooserButtonDialog
    attrClear = undefined
#endif

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@modal@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFileChooserButtonModal :: (IsFileChooserButton o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructFileChooserButtonModal :: Bool -> m (GValueConstruct o)
constructFileChooserButtonModal 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
"modal" Bool
val

#if defined(ENABLE_OVERLOADING)
data FileChooserButtonModalPropertyInfo
instance AttrInfo FileChooserButtonModalPropertyInfo where
    type AttrAllowedOps FileChooserButtonModalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint FileChooserButtonModalPropertyInfo = IsFileChooserButton
    type AttrSetTypeConstraint FileChooserButtonModalPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint FileChooserButtonModalPropertyInfo = (~) Bool
    type AttrTransferType FileChooserButtonModalPropertyInfo = Bool
    type AttrGetType FileChooserButtonModalPropertyInfo = Bool
    type AttrLabel FileChooserButtonModalPropertyInfo = "modal"
    type AttrOrigin FileChooserButtonModalPropertyInfo = FileChooserButton
    attrGet = getFileChooserButtonModal
    attrSet = setFileChooserButtonModal
    attrTransfer _ v = do
        return v
    attrConstruct = constructFileChooserButtonModal
    attrClear = undefined
#endif

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

-- | Get the value of the “@title@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' fileChooserButton #title
-- @
getFileChooserButtonTitle :: (MonadIO m, IsFileChooserButton o) => o -> m T.Text
getFileChooserButtonTitle :: o -> m Text
getFileChooserButtonTitle o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getFileChooserButtonTitle" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"title"

-- | Set the value of the “@title@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' fileChooserButton [ #title 'Data.GI.Base.Attributes.:=' value ]
-- @
setFileChooserButtonTitle :: (MonadIO m, IsFileChooserButton o) => o -> T.Text -> m ()
setFileChooserButtonTitle :: o -> Text -> m ()
setFileChooserButtonTitle o
obj Text
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 -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"title" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@title@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFileChooserButtonTitle :: (IsFileChooserButton o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructFileChooserButtonTitle :: Text -> m (GValueConstruct o)
constructFileChooserButtonTitle Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"title" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data FileChooserButtonTitlePropertyInfo
instance AttrInfo FileChooserButtonTitlePropertyInfo where
    type AttrAllowedOps FileChooserButtonTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint FileChooserButtonTitlePropertyInfo = IsFileChooserButton
    type AttrSetTypeConstraint FileChooserButtonTitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint FileChooserButtonTitlePropertyInfo = (~) T.Text
    type AttrTransferType FileChooserButtonTitlePropertyInfo = T.Text
    type AttrGetType FileChooserButtonTitlePropertyInfo = T.Text
    type AttrLabel FileChooserButtonTitlePropertyInfo = "title"
    type AttrOrigin FileChooserButtonTitlePropertyInfo = FileChooserButton
    attrGet = getFileChooserButtonTitle
    attrSet = setFileChooserButtonTitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructFileChooserButtonTitle
    attrClear = undefined
#endif

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

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

-- | Set the value of the “@width-chars@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' fileChooserButton [ #widthChars 'Data.GI.Base.Attributes.:=' value ]
-- @
setFileChooserButtonWidthChars :: (MonadIO m, IsFileChooserButton o) => o -> Int32 -> m ()
setFileChooserButtonWidthChars :: o -> Int32 -> m ()
setFileChooserButtonWidthChars o
obj Int32
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"width-chars" Int32
val

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

#if defined(ENABLE_OVERLOADING)
data FileChooserButtonWidthCharsPropertyInfo
instance AttrInfo FileChooserButtonWidthCharsPropertyInfo where
    type AttrAllowedOps FileChooserButtonWidthCharsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint FileChooserButtonWidthCharsPropertyInfo = IsFileChooserButton
    type AttrSetTypeConstraint FileChooserButtonWidthCharsPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint FileChooserButtonWidthCharsPropertyInfo = (~) Int32
    type AttrTransferType FileChooserButtonWidthCharsPropertyInfo = Int32
    type AttrGetType FileChooserButtonWidthCharsPropertyInfo = Int32
    type AttrLabel FileChooserButtonWidthCharsPropertyInfo = "width-chars"
    type AttrOrigin FileChooserButtonWidthCharsPropertyInfo = FileChooserButton
    attrGet = getFileChooserButtonWidthChars
    attrSet = setFileChooserButtonWidthChars
    attrTransfer _ v = do
        return v
    attrConstruct = constructFileChooserButtonWidthChars
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FileChooserButton
type instance O.AttributeList FileChooserButton = FileChooserButtonAttributeList
type FileChooserButtonAttributeList = ('[ '("action", Gtk.FileChooser.FileChooserActionPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("createFolders", Gtk.FileChooser.FileChooserCreateFoldersPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("dialog", FileChooserButtonDialogPropertyInfo), '("filter", Gtk.FileChooser.FileChooserFilterPropertyInfo), '("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), '("modal", FileChooserButtonModalPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("selectMultiple", Gtk.FileChooser.FileChooserSelectMultiplePropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("title", FileChooserButtonTitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthChars", FileChooserButtonWidthCharsPropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
fileChooserButtonDialog :: AttrLabelProxy "dialog"
fileChooserButtonDialog = AttrLabelProxy

fileChooserButtonModal :: AttrLabelProxy "modal"
fileChooserButtonModal = AttrLabelProxy

fileChooserButtonTitle :: AttrLabelProxy "title"
fileChooserButtonTitle = AttrLabelProxy

fileChooserButtonWidthChars :: AttrLabelProxy "widthChars"
fileChooserButtonWidthChars = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FileChooserButton = FileChooserButtonSignalList
type FileChooserButtonSignalList = ('[ '("currentFolderChanged", Gtk.FileChooser.FileChooserCurrentFolderChangedSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("fileActivated", Gtk.FileChooser.FileChooserFileActivatedSignalInfo), '("fileSet", FileChooserButtonFileSetSignalInfo), '("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), '("selectionChanged", Gtk.FileChooser.FileChooserSelectionChangedSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

-- method FileChooserButton::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "title"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the title of the browse dialog."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileChooserAction" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the open mode for the widget."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gtk" , name = "FileChooserButton" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_chooser_button_new" gtk_file_chooser_button_new :: 
    CString ->                              -- title : TBasicType TUTF8
    CUInt ->                                -- action : TInterface (Name {namespace = "Gtk", name = "FileChooserAction"})
    IO (Ptr FileChooserButton)

-- | Creates a new file-selecting button widget.
fileChooserButtonNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@title@/: the title of the browse dialog.
    -> Gtk.Enums.FileChooserAction
    -- ^ /@action@/: the open mode for the widget.
    -> m FileChooserButton
    -- ^ __Returns:__ a new button widget.
fileChooserButtonNew :: Text -> FileChooserAction -> m FileChooserButton
fileChooserButtonNew Text
title FileChooserAction
action = IO FileChooserButton -> m FileChooserButton
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileChooserButton -> m FileChooserButton)
-> IO FileChooserButton -> m FileChooserButton
forall a b. (a -> b) -> a -> b
$ do
    CString
title' <- Text -> IO CString
textToCString Text
title
    let action' :: CUInt
action' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (FileChooserAction -> Int) -> FileChooserAction -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileChooserAction -> Int
forall a. Enum a => a -> Int
fromEnum) FileChooserAction
action
    Ptr FileChooserButton
result <- CString -> CUInt -> IO (Ptr FileChooserButton)
gtk_file_chooser_button_new CString
title' CUInt
action'
    Text -> Ptr FileChooserButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fileChooserButtonNew" Ptr FileChooserButton
result
    FileChooserButton
result' <- ((ManagedPtr FileChooserButton -> FileChooserButton)
-> Ptr FileChooserButton -> IO FileChooserButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FileChooserButton -> FileChooserButton
FileChooserButton) Ptr FileChooserButton
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
    FileChooserButton -> IO FileChooserButton
forall (m :: * -> *) a. Monad m => a -> m a
return FileChooserButton
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method FileChooserButton::new_with_dialog
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "dialog"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Dialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the widget to use as dialog"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gtk" , name = "FileChooserButton" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_chooser_button_new_with_dialog" gtk_file_chooser_button_new_with_dialog :: 
    Ptr Gtk.Dialog.Dialog ->                -- dialog : TInterface (Name {namespace = "Gtk", name = "Dialog"})
    IO (Ptr FileChooserButton)

-- | Creates a t'GI.Gtk.Objects.FileChooserButton.FileChooserButton' widget which uses /@dialog@/ as its
-- file-picking window.
-- 
-- Note that /@dialog@/ must be a t'GI.Gtk.Objects.Dialog.Dialog' (or subclass) which
-- implements the t'GI.Gtk.Interfaces.FileChooser.FileChooser' interface and must not have
-- 'GI.Gtk.Flags.DialogFlagsDestroyWithParent' set.
-- 
-- Also note that the dialog needs to have its confirmative button
-- added with response 'GI.Gtk.Enums.ResponseTypeAccept' or 'GI.Gtk.Enums.ResponseTypeOk' in
-- order for the button to take over the file selected in the dialog.
fileChooserButtonNewWithDialog ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Dialog.IsDialog a) =>
    a
    -- ^ /@dialog@/: the widget to use as dialog
    -> m FileChooserButton
    -- ^ __Returns:__ a new button widget.
fileChooserButtonNewWithDialog :: a -> m FileChooserButton
fileChooserButtonNewWithDialog a
dialog = IO FileChooserButton -> m FileChooserButton
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileChooserButton -> m FileChooserButton)
-> IO FileChooserButton -> m FileChooserButton
forall a b. (a -> b) -> a -> b
$ do
    Ptr Dialog
dialog' <- a -> IO (Ptr Dialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dialog
    Ptr FileChooserButton
result <- Ptr Dialog -> IO (Ptr FileChooserButton)
gtk_file_chooser_button_new_with_dialog Ptr Dialog
dialog'
    Text -> Ptr FileChooserButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fileChooserButtonNewWithDialog" Ptr FileChooserButton
result
    FileChooserButton
result' <- ((ManagedPtr FileChooserButton -> FileChooserButton)
-> Ptr FileChooserButton -> IO FileChooserButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FileChooserButton -> FileChooserButton
FileChooserButton) Ptr FileChooserButton
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dialog
    FileChooserButton -> IO FileChooserButton
forall (m :: * -> *) a. Monad m => a -> m a
return FileChooserButton
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method FileChooserButton::get_modal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileChooserButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkFileChooserButton"
--                 , 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_file_chooser_button_get_modal" gtk_file_chooser_button_get_modal :: 
    Ptr FileChooserButton ->                -- button : TInterface (Name {namespace = "Gtk", name = "FileChooserButton"})
    IO CInt

-- | Gets whether the dialog is modal.
fileChooserButtonGetModal ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
    a
    -- ^ /@button@/: a t'GI.Gtk.Objects.FileChooserButton.FileChooserButton'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the dialog is modal
fileChooserButtonGetModal :: a -> m Bool
fileChooserButtonGetModal a
button = 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 FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    CInt
result <- Ptr FileChooserButton -> IO CInt
gtk_file_chooser_button_get_modal Ptr FileChooserButton
button'
    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
button
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FileChooserButtonGetModalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonGetModalMethodInfo a signature where
    overloadedMethod = fileChooserButtonGetModal

#endif

-- method FileChooserButton::get_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileChooserButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the button widget to examine."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_chooser_button_get_title" gtk_file_chooser_button_get_title :: 
    Ptr FileChooserButton ->                -- button : TInterface (Name {namespace = "Gtk", name = "FileChooserButton"})
    IO CString

-- | Retrieves the title of the browse dialog used by /@button@/. The returned value
-- should not be modified or freed.
fileChooserButtonGetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
    a
    -- ^ /@button@/: the button widget to examine.
    -> m T.Text
    -- ^ __Returns:__ a pointer to the browse dialog’s title.
fileChooserButtonGetTitle :: a -> m Text
fileChooserButtonGetTitle a
button = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    CString
result <- Ptr FileChooserButton -> IO CString
gtk_file_chooser_button_get_title Ptr FileChooserButton
button'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fileChooserButtonGetTitle" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data FileChooserButtonGetTitleMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonGetTitleMethodInfo a signature where
    overloadedMethod = fileChooserButtonGetTitle

#endif

-- method FileChooserButton::get_width_chars
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileChooserButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the button widget to examine."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_chooser_button_get_width_chars" gtk_file_chooser_button_get_width_chars :: 
    Ptr FileChooserButton ->                -- button : TInterface (Name {namespace = "Gtk", name = "FileChooserButton"})
    IO Int32

-- | Retrieves the width in characters of the /@button@/ widget’s entry and\/or label.
fileChooserButtonGetWidthChars ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
    a
    -- ^ /@button@/: the button widget to examine.
    -> m Int32
    -- ^ __Returns:__ an integer width (in characters) that the button will use to size itself.
fileChooserButtonGetWidthChars :: a -> m Int32
fileChooserButtonGetWidthChars a
button = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Int32
result <- Ptr FileChooserButton -> IO Int32
gtk_file_chooser_button_get_width_chars Ptr FileChooserButton
button'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data FileChooserButtonGetWidthCharsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonGetWidthCharsMethodInfo a signature where
    overloadedMethod = fileChooserButtonGetWidthChars

#endif

-- method FileChooserButton::set_modal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileChooserButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkFileChooserButton"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "modal"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to make the dialog modal"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_chooser_button_set_modal" gtk_file_chooser_button_set_modal :: 
    Ptr FileChooserButton ->                -- button : TInterface (Name {namespace = "Gtk", name = "FileChooserButton"})
    CInt ->                                 -- modal : TBasicType TBoolean
    IO ()

-- | Sets whether the dialog should be modal.
fileChooserButtonSetModal ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
    a
    -- ^ /@button@/: a t'GI.Gtk.Objects.FileChooserButton.FileChooserButton'
    -> Bool
    -- ^ /@modal@/: 'P.True' to make the dialog modal
    -> m ()
fileChooserButtonSetModal :: a -> Bool -> m ()
fileChooserButtonSetModal a
button Bool
modal = 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 FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    let modal' :: CInt
modal' = (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
modal
    Ptr FileChooserButton -> CInt -> IO ()
gtk_file_chooser_button_set_modal Ptr FileChooserButton
button' CInt
modal'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileChooserButtonSetModalMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonSetModalMethodInfo a signature where
    overloadedMethod = fileChooserButtonSetModal

#endif

-- method FileChooserButton::set_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileChooserButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the button widget to modify."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "title"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new browse dialog title."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_chooser_button_set_title" gtk_file_chooser_button_set_title :: 
    Ptr FileChooserButton ->                -- button : TInterface (Name {namespace = "Gtk", name = "FileChooserButton"})
    CString ->                              -- title : TBasicType TUTF8
    IO ()

-- | Modifies the /@title@/ of the browse dialog used by /@button@/.
fileChooserButtonSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
    a
    -- ^ /@button@/: the button widget to modify.
    -> T.Text
    -- ^ /@title@/: the new browse dialog title.
    -> m ()
fileChooserButtonSetTitle :: a -> Text -> m ()
fileChooserButtonSetTitle a
button Text
title = 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 FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    CString
title' <- Text -> IO CString
textToCString Text
title
    Ptr FileChooserButton -> CString -> IO ()
gtk_file_chooser_button_set_title Ptr FileChooserButton
button' CString
title'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileChooserButtonSetTitleMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonSetTitleMethodInfo a signature where
    overloadedMethod = fileChooserButtonSetTitle

#endif

-- method FileChooserButton::set_width_chars
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileChooserButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the button widget to examine."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_chars"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new width, in characters."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_chooser_button_set_width_chars" gtk_file_chooser_button_set_width_chars :: 
    Ptr FileChooserButton ->                -- button : TInterface (Name {namespace = "Gtk", name = "FileChooserButton"})
    Int32 ->                                -- n_chars : TBasicType TInt
    IO ()

-- | Sets the width (in characters) that /@button@/ will use to /@nChars@/.
fileChooserButtonSetWidthChars ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
    a
    -- ^ /@button@/: the button widget to examine.
    -> Int32
    -- ^ /@nChars@/: the new width, in characters.
    -> m ()
fileChooserButtonSetWidthChars :: a -> Int32 -> m ()
fileChooserButtonSetWidthChars a
button Int32
nChars = 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 FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr FileChooserButton -> Int32 -> IO ()
gtk_file_chooser_button_set_width_chars Ptr FileChooserButton
button' Int32
nChars
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileChooserButtonSetWidthCharsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonSetWidthCharsMethodInfo a signature where
    overloadedMethod = fileChooserButtonSetWidthChars

#endif