{-# 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.FileChooserDialog.FileChooserDialog' is a dialog box suitable for use with
-- “File Open” or “File Save” commands.  This widget works by
-- putting a t'GI.Gtk.Objects.FileChooserWidget.FileChooserWidget' inside a t'GI.Gtk.Objects.Dialog.Dialog'.  It exposes
-- the t'GI.Gtk.Interfaces.FileChooser.FileChooser' interface, so you can use all of the
-- t'GI.Gtk.Interfaces.FileChooser.FileChooser' functions on the file chooser dialog as well as
-- those for t'GI.Gtk.Objects.Dialog.Dialog'.
-- 
-- Note that t'GI.Gtk.Objects.FileChooserDialog.FileChooserDialog' does not have any methods of its
-- own.  Instead, you should use the functions that work on a
-- t'GI.Gtk.Interfaces.FileChooser.FileChooser'.
-- 
-- If you want to integrate well with the platform you should use the
-- t'GI.Gtk.Objects.FileChooserNative.FileChooserNative' API, which will use a platform-specific
-- dialog if available and fall back to GtkFileChooserDialog
-- otherwise.
-- 
-- ## Typical usage ## {@/gtkfilechooser/@-typical-usage}
-- 
-- In the simplest of cases, you can the following code to use
-- t'GI.Gtk.Objects.FileChooserDialog.FileChooserDialog' to select a file for opening:
-- 
-- >
-- >static void
-- >on_open_response (GtkDialog *dialog,
-- >                  int        response)
-- >{
-- >  if (response == GTK_RESPONSE_ACCEPT)
-- >    {
-- >      GtkFileChooser *chooser = GTK_FILE_CHOOSER (dialog);
-- >
-- >      g_autoptr(GFile) file = gtk_file_chooser_get_file (chooser);
-- >
-- >      open_file (file);
-- >    }
-- >
-- >  gtk_window_destroy (GTK_WINDOW (dialog));
-- >}
-- >
-- >  // ...
-- >  GtkWidget *dialog;
-- >  GtkFileChooserAction action = GTK_FILE_CHOOSER_ACTION_OPEN;
-- >
-- >  dialog = gtk_file_chooser_dialog_new ("Open File",
-- >                                        parent_window,
-- >                                        action,
-- >                                        _("_Cancel"),
-- >                                        GTK_RESPONSE_CANCEL,
-- >                                        _("_Open"),
-- >                                        GTK_RESPONSE_ACCEPT,
-- >                                        NULL);
-- >
-- >  gtk_widget_show (dialog);
-- >
-- >  g_signal_connect (dialog, "response",
-- >                    G_CALLBACK (on_open_response),
-- >                    NULL);
-- 
-- 
-- To use a dialog for saving, you can use this:
-- 
-- >
-- >static void
-- >on_save_response (GtkDialog *dialog,
-- >                  int        response)
-- >{
-- >  if (response == GTK_RESPONSE_ACCEPT)
-- >    {
-- >      GtkFileChooser *chooser = GTK_FILE_CHOOSER (dialog);
-- >
-- >      g_autoptr(GFile) file = gtk_file_chooser_get_file (chooser);
-- >
-- >      save_to_file (file);
-- >    }
-- >
-- >  gtk_window_destroy (GTK_WINDOW (dialog));
-- >}
-- >
-- >  // ...
-- >  GtkWidget *dialog;
-- >  GtkFileChooser *chooser;
-- >  GtkFileChooserAction action = GTK_FILE_CHOOSER_ACTION_SAVE;
-- >
-- >  dialog = gtk_file_chooser_dialog_new ("Save File",
-- >                                        parent_window,
-- >                                        action,
-- >                                        _("_Cancel"),
-- >                                        GTK_RESPONSE_CANCEL,
-- >                                        _("_Save"),
-- >                                        GTK_RESPONSE_ACCEPT,
-- >                                        NULL);
-- >  chooser = GTK_FILE_CHOOSER (dialog);
-- >
-- >  if (user_edited_a_new_document)
-- >    gtk_file_chooser_set_current_name (chooser, _("Untitled document"));
-- >  else
-- >    gtk_file_chooser_set_file (chooser, existing_filename);
-- >
-- >  gtk_widget_show (dialog);
-- >
-- >  g_signal_connect (dialog, "response",
-- >                    G_CALLBACK (on_save_response),
-- >                    NULL);
-- 
-- 
-- ## Setting up a file chooser dialog ## {@/gtkfilechooserdialog/@-setting-up}
-- 
-- There are various cases in which you may need to use a t'GI.Gtk.Objects.FileChooserDialog.FileChooserDialog':
-- 
-- * To select a file for opening. Use @/GTK_FILE_CHOOSER_ACTION_OPEN/@.
-- * To save a file for the first time. Use @/GTK_FILE_CHOOSER_ACTION_SAVE/@,
-- and suggest a name such as “Untitled” with 'GI.Gtk.Interfaces.FileChooser.fileChooserSetCurrentName'.
-- * To save a file under a different name. Use @/GTK_FILE_CHOOSER_ACTION_SAVE/@,
-- and set the existing file with 'GI.Gtk.Interfaces.FileChooser.fileChooserSetFile'.
-- * To choose a folder instead of a file. Use @/GTK_FILE_CHOOSER_ACTION_SELECT_FOLDER/@.
-- 
-- 
-- Note that old versions of the file chooser’s documentation suggested
-- using 'GI.Gtk.Interfaces.FileChooser.fileChooserSetCurrentFolder' in various
-- situations, with the intention of letting the application
-- suggest a reasonable default folder.  This is no longer
-- considered to be a good policy, as now the file chooser is
-- able to make good suggestions on its own.  In general, you
-- should only cause the file chooser to show a specific folder
-- when it is appropriate to use 'GI.Gtk.Interfaces.FileChooser.fileChooserSetFile',
-- i.e. when you are doing a Save As command and you already
-- have a file saved somewhere.
-- 
-- ## Response Codes ## {@/gtkfilechooserdialog/@-responses}
-- 
-- t'GI.Gtk.Objects.FileChooserDialog.FileChooserDialog' inherits from t'GI.Gtk.Objects.Dialog.Dialog', so buttons that
-- go in its action area have response codes such as
-- @/GTK_RESPONSE_ACCEPT/@ and @/GTK_RESPONSE_CANCEL/@.  For example, you
-- could call @/gtk_file_chooser_dialog_new()/@ as follows:
-- 
-- >
-- >GtkWidget *dialog;
-- >GtkFileChooserAction action = GTK_FILE_CHOOSER_ACTION_OPEN;
-- >
-- >dialog = gtk_file_chooser_dialog_new ("Open File",
-- >                                      parent_window,
-- >                                      action,
-- >                                      _("_Cancel"),
-- >                                      GTK_RESPONSE_CANCEL,
-- >                                      _("_Open"),
-- >                                      GTK_RESPONSE_ACCEPT,
-- >                                      NULL);
-- 
-- 
-- This will create buttons for “Cancel” and “Open” that use predefined
-- response identifiers from t'GI.Gtk.Enums.ResponseType'.  For most dialog
-- boxes you can use your own custom response codes rather than the
-- ones in t'GI.Gtk.Enums.ResponseType', but t'GI.Gtk.Objects.FileChooserDialog.FileChooserDialog' assumes that
-- its “accept”-type action, e.g. an “Open” or “Save” button,
-- will have one of the following response codes:
-- 
-- * @/GTK_RESPONSE_ACCEPT/@
-- * @/GTK_RESPONSE_OK/@
-- * @/GTK_RESPONSE_YES/@
-- * @/GTK_RESPONSE_APPLY/@
-- 
-- 
-- This is because t'GI.Gtk.Objects.FileChooserDialog.FileChooserDialog' must intercept responses
-- and switch to folders if appropriate, rather than letting the
-- dialog terminate — the implementation uses these known
-- response codes to know which responses can be blocked if
-- appropriate.
-- 
-- To summarize, make sure you use a
-- [predefined response code][gtkfilechooserdialog-responses]
-- when you use t'GI.Gtk.Objects.FileChooserDialog.FileChooserDialog' to ensure proper operation.

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

module GI.Gtk.Objects.FileChooserDialog
    ( 

-- * Exported types
    FileChooserDialog(..)                   ,
    IsFileChooserDialog                     ,
    toFileChooserDialog                     ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveFileChooserDialogMethod          ,
#endif




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

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

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

foreign import ccall "gtk_file_chooser_dialog_get_type"
    c_gtk_file_chooser_dialog_get_type :: IO B.Types.GType

instance B.Types.TypedObject FileChooserDialog where
    glibType :: IO GType
glibType = IO GType
c_gtk_file_chooser_dialog_get_type

instance B.Types.GObject FileChooserDialog

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

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

instance O.HasParentTypes FileChooserDialog
type instance O.ParentTypes FileChooserDialog = '[Gtk.Dialog.Dialog, Gtk.Window.Window, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget, Gtk.FileChooser.FileChooser, Gtk.Native.Native, Gtk.Root.Root, Gtk.ShortcutManager.ShortcutManager]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveFileChooserDialogMethod (t :: Symbol) (o :: *) :: * where
    ResolveFileChooserDialogMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveFileChooserDialogMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveFileChooserDialogMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveFileChooserDialogMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveFileChooserDialogMethod "addActionWidget" o = Gtk.Dialog.DialogAddActionWidgetMethodInfo
    ResolveFileChooserDialogMethod "addButton" o = Gtk.Dialog.DialogAddButtonMethodInfo
    ResolveFileChooserDialogMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveFileChooserDialogMethod "addChoice" o = Gtk.FileChooser.FileChooserAddChoiceMethodInfo
    ResolveFileChooserDialogMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveFileChooserDialogMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveFileChooserDialogMethod "addFilter" o = Gtk.FileChooser.FileChooserAddFilterMethodInfo
    ResolveFileChooserDialogMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveFileChooserDialogMethod "addShortcutFolder" o = Gtk.FileChooser.FileChooserAddShortcutFolderMethodInfo
    ResolveFileChooserDialogMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveFileChooserDialogMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveFileChooserDialogMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveFileChooserDialogMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveFileChooserDialogMethod "checkResize" o = Gtk.Native.NativeCheckResizeMethodInfo
    ResolveFileChooserDialogMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveFileChooserDialogMethod "close" o = Gtk.Window.WindowCloseMethodInfo
    ResolveFileChooserDialogMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveFileChooserDialogMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveFileChooserDialogMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveFileChooserDialogMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveFileChooserDialogMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveFileChooserDialogMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveFileChooserDialogMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveFileChooserDialogMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveFileChooserDialogMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveFileChooserDialogMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveFileChooserDialogMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveFileChooserDialogMethod "destroy" o = Gtk.Window.WindowDestroyMethodInfo
    ResolveFileChooserDialogMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveFileChooserDialogMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveFileChooserDialogMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveFileChooserDialogMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveFileChooserDialogMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveFileChooserDialogMethod "fullscreen" o = Gtk.Window.WindowFullscreenMethodInfo
    ResolveFileChooserDialogMethod "fullscreenOnMonitor" o = Gtk.Window.WindowFullscreenOnMonitorMethodInfo
    ResolveFileChooserDialogMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveFileChooserDialogMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveFileChooserDialogMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveFileChooserDialogMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveFileChooserDialogMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveFileChooserDialogMethod "hasGroup" o = Gtk.Window.WindowHasGroupMethodInfo
    ResolveFileChooserDialogMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveFileChooserDialogMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveFileChooserDialogMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveFileChooserDialogMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveFileChooserDialogMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveFileChooserDialogMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveFileChooserDialogMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveFileChooserDialogMethod "isActive" o = Gtk.Window.WindowIsActiveMethodInfo
    ResolveFileChooserDialogMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveFileChooserDialogMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveFileChooserDialogMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveFileChooserDialogMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveFileChooserDialogMethod "isMaximized" o = Gtk.Window.WindowIsMaximizedMethodInfo
    ResolveFileChooserDialogMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveFileChooserDialogMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveFileChooserDialogMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveFileChooserDialogMethod "listFilters" o = Gtk.FileChooser.FileChooserListFiltersMethodInfo
    ResolveFileChooserDialogMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveFileChooserDialogMethod "listShortcutFolders" o = Gtk.FileChooser.FileChooserListShortcutFoldersMethodInfo
    ResolveFileChooserDialogMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveFileChooserDialogMethod "maximize" o = Gtk.Window.WindowMaximizeMethodInfo
    ResolveFileChooserDialogMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveFileChooserDialogMethod "minimize" o = Gtk.Window.WindowMinimizeMethodInfo
    ResolveFileChooserDialogMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveFileChooserDialogMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveFileChooserDialogMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveFileChooserDialogMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveFileChooserDialogMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveFileChooserDialogMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveFileChooserDialogMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveFileChooserDialogMethod "present" o = Gtk.Window.WindowPresentMethodInfo
    ResolveFileChooserDialogMethod "presentWithTime" o = Gtk.Window.WindowPresentWithTimeMethodInfo
    ResolveFileChooserDialogMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveFileChooserDialogMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveFileChooserDialogMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveFileChooserDialogMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveFileChooserDialogMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveFileChooserDialogMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveFileChooserDialogMethod "removeChoice" o = Gtk.FileChooser.FileChooserRemoveChoiceMethodInfo
    ResolveFileChooserDialogMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveFileChooserDialogMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveFileChooserDialogMethod "removeFilter" o = Gtk.FileChooser.FileChooserRemoveFilterMethodInfo
    ResolveFileChooserDialogMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveFileChooserDialogMethod "removeShortcutFolder" o = Gtk.FileChooser.FileChooserRemoveShortcutFolderMethodInfo
    ResolveFileChooserDialogMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveFileChooserDialogMethod "resize" o = Gtk.Window.WindowResizeMethodInfo
    ResolveFileChooserDialogMethod "response" o = Gtk.Dialog.DialogResponseMethodInfo
    ResolveFileChooserDialogMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveFileChooserDialogMethod "selectAll" o = Gtk.FileChooser.FileChooserSelectAllMethodInfo
    ResolveFileChooserDialogMethod "selectFile" o = Gtk.FileChooser.FileChooserSelectFileMethodInfo
    ResolveFileChooserDialogMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveFileChooserDialogMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveFileChooserDialogMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveFileChooserDialogMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveFileChooserDialogMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveFileChooserDialogMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveFileChooserDialogMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveFileChooserDialogMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveFileChooserDialogMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveFileChooserDialogMethod "unfullscreen" o = Gtk.Window.WindowUnfullscreenMethodInfo
    ResolveFileChooserDialogMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveFileChooserDialogMethod "unmaximize" o = Gtk.Window.WindowUnmaximizeMethodInfo
    ResolveFileChooserDialogMethod "unminimize" o = Gtk.Window.WindowUnminimizeMethodInfo
    ResolveFileChooserDialogMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveFileChooserDialogMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveFileChooserDialogMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveFileChooserDialogMethod "unselectAll" o = Gtk.FileChooser.FileChooserUnselectAllMethodInfo
    ResolveFileChooserDialogMethod "unselectFile" o = Gtk.FileChooser.FileChooserUnselectFileMethodInfo
    ResolveFileChooserDialogMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveFileChooserDialogMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveFileChooserDialogMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveFileChooserDialogMethod "getAction" o = Gtk.FileChooser.FileChooserGetActionMethodInfo
    ResolveFileChooserDialogMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveFileChooserDialogMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveFileChooserDialogMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveFileChooserDialogMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveFileChooserDialogMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveFileChooserDialogMethod "getApplication" o = Gtk.Window.WindowGetApplicationMethodInfo
    ResolveFileChooserDialogMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveFileChooserDialogMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveFileChooserDialogMethod "getChild" o = Gtk.Window.WindowGetChildMethodInfo
    ResolveFileChooserDialogMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveFileChooserDialogMethod "getChoice" o = Gtk.FileChooser.FileChooserGetChoiceMethodInfo
    ResolveFileChooserDialogMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveFileChooserDialogMethod "getContentArea" o = Gtk.Dialog.DialogGetContentAreaMethodInfo
    ResolveFileChooserDialogMethod "getCreateFolders" o = Gtk.FileChooser.FileChooserGetCreateFoldersMethodInfo
    ResolveFileChooserDialogMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveFileChooserDialogMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveFileChooserDialogMethod "getCurrentFolder" o = Gtk.FileChooser.FileChooserGetCurrentFolderMethodInfo
    ResolveFileChooserDialogMethod "getCurrentName" o = Gtk.FileChooser.FileChooserGetCurrentNameMethodInfo
    ResolveFileChooserDialogMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveFileChooserDialogMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveFileChooserDialogMethod "getDecorated" o = Gtk.Window.WindowGetDecoratedMethodInfo
    ResolveFileChooserDialogMethod "getDefaultSize" o = Gtk.Window.WindowGetDefaultSizeMethodInfo
    ResolveFileChooserDialogMethod "getDefaultWidget" o = Gtk.Window.WindowGetDefaultWidgetMethodInfo
    ResolveFileChooserDialogMethod "getDeletable" o = Gtk.Window.WindowGetDeletableMethodInfo
    ResolveFileChooserDialogMethod "getDestroyWithParent" o = Gtk.Window.WindowGetDestroyWithParentMethodInfo
    ResolveFileChooserDialogMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveFileChooserDialogMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveFileChooserDialogMethod "getFile" o = Gtk.FileChooser.FileChooserGetFileMethodInfo
    ResolveFileChooserDialogMethod "getFiles" o = Gtk.FileChooser.FileChooserGetFilesMethodInfo
    ResolveFileChooserDialogMethod "getFilter" o = Gtk.FileChooser.FileChooserGetFilterMethodInfo
    ResolveFileChooserDialogMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveFileChooserDialogMethod "getFocus" o = Gtk.Window.WindowGetFocusMethodInfo
    ResolveFileChooserDialogMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveFileChooserDialogMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveFileChooserDialogMethod "getFocusVisible" o = Gtk.Window.WindowGetFocusVisibleMethodInfo
    ResolveFileChooserDialogMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveFileChooserDialogMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveFileChooserDialogMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveFileChooserDialogMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveFileChooserDialogMethod "getGroup" o = Gtk.Window.WindowGetGroupMethodInfo
    ResolveFileChooserDialogMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveFileChooserDialogMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveFileChooserDialogMethod "getHeaderBar" o = Gtk.Dialog.DialogGetHeaderBarMethodInfo
    ResolveFileChooserDialogMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveFileChooserDialogMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveFileChooserDialogMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveFileChooserDialogMethod "getHideOnClose" o = Gtk.Window.WindowGetHideOnCloseMethodInfo
    ResolveFileChooserDialogMethod "getIconName" o = Gtk.Window.WindowGetIconNameMethodInfo
    ResolveFileChooserDialogMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveFileChooserDialogMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveFileChooserDialogMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveFileChooserDialogMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveFileChooserDialogMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveFileChooserDialogMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveFileChooserDialogMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveFileChooserDialogMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveFileChooserDialogMethod "getMnemonicsVisible" o = Gtk.Window.WindowGetMnemonicsVisibleMethodInfo
    ResolveFileChooserDialogMethod "getModal" o = Gtk.Window.WindowGetModalMethodInfo
    ResolveFileChooserDialogMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveFileChooserDialogMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveFileChooserDialogMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveFileChooserDialogMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveFileChooserDialogMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveFileChooserDialogMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveFileChooserDialogMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveFileChooserDialogMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveFileChooserDialogMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveFileChooserDialogMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveFileChooserDialogMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveFileChooserDialogMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveFileChooserDialogMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveFileChooserDialogMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveFileChooserDialogMethod "getRenderer" o = Gtk.Native.NativeGetRendererMethodInfo
    ResolveFileChooserDialogMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveFileChooserDialogMethod "getResizable" o = Gtk.Window.WindowGetResizableMethodInfo
    ResolveFileChooserDialogMethod "getResponseForWidget" o = Gtk.Dialog.DialogGetResponseForWidgetMethodInfo
    ResolveFileChooserDialogMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveFileChooserDialogMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveFileChooserDialogMethod "getSelectMultiple" o = Gtk.FileChooser.FileChooserGetSelectMultipleMethodInfo
    ResolveFileChooserDialogMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveFileChooserDialogMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveFileChooserDialogMethod "getSize" o = Gtk.Window.WindowGetSizeMethodInfo
    ResolveFileChooserDialogMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveFileChooserDialogMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveFileChooserDialogMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveFileChooserDialogMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveFileChooserDialogMethod "getSurface" o = Gtk.Native.NativeGetSurfaceMethodInfo
    ResolveFileChooserDialogMethod "getSurfaceTransform" o = Gtk.Native.NativeGetSurfaceTransformMethodInfo
    ResolveFileChooserDialogMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveFileChooserDialogMethod "getTitle" o = Gtk.Window.WindowGetTitleMethodInfo
    ResolveFileChooserDialogMethod "getTitlebar" o = Gtk.Window.WindowGetTitlebarMethodInfo
    ResolveFileChooserDialogMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveFileChooserDialogMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveFileChooserDialogMethod "getTransientFor" o = Gtk.Window.WindowGetTransientForMethodInfo
    ResolveFileChooserDialogMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveFileChooserDialogMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveFileChooserDialogMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveFileChooserDialogMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveFileChooserDialogMethod "getWidgetForResponse" o = Gtk.Dialog.DialogGetWidgetForResponseMethodInfo
    ResolveFileChooserDialogMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveFileChooserDialogMethod "setAction" o = Gtk.FileChooser.FileChooserSetActionMethodInfo
    ResolveFileChooserDialogMethod "setApplication" o = Gtk.Window.WindowSetApplicationMethodInfo
    ResolveFileChooserDialogMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveFileChooserDialogMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveFileChooserDialogMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveFileChooserDialogMethod "setChild" o = Gtk.Window.WindowSetChildMethodInfo
    ResolveFileChooserDialogMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveFileChooserDialogMethod "setChoice" o = Gtk.FileChooser.FileChooserSetChoiceMethodInfo
    ResolveFileChooserDialogMethod "setCreateFolders" o = Gtk.FileChooser.FileChooserSetCreateFoldersMethodInfo
    ResolveFileChooserDialogMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveFileChooserDialogMethod "setCurrentFolder" o = Gtk.FileChooser.FileChooserSetCurrentFolderMethodInfo
    ResolveFileChooserDialogMethod "setCurrentName" o = Gtk.FileChooser.FileChooserSetCurrentNameMethodInfo
    ResolveFileChooserDialogMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveFileChooserDialogMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveFileChooserDialogMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveFileChooserDialogMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveFileChooserDialogMethod "setDecorated" o = Gtk.Window.WindowSetDecoratedMethodInfo
    ResolveFileChooserDialogMethod "setDefaultResponse" o = Gtk.Dialog.DialogSetDefaultResponseMethodInfo
    ResolveFileChooserDialogMethod "setDefaultSize" o = Gtk.Window.WindowSetDefaultSizeMethodInfo
    ResolveFileChooserDialogMethod "setDefaultWidget" o = Gtk.Window.WindowSetDefaultWidgetMethodInfo
    ResolveFileChooserDialogMethod "setDeletable" o = Gtk.Window.WindowSetDeletableMethodInfo
    ResolveFileChooserDialogMethod "setDestroyWithParent" o = Gtk.Window.WindowSetDestroyWithParentMethodInfo
    ResolveFileChooserDialogMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveFileChooserDialogMethod "setDisplay" o = Gtk.Window.WindowSetDisplayMethodInfo
    ResolveFileChooserDialogMethod "setFile" o = Gtk.FileChooser.FileChooserSetFileMethodInfo
    ResolveFileChooserDialogMethod "setFilter" o = Gtk.FileChooser.FileChooserSetFilterMethodInfo
    ResolveFileChooserDialogMethod "setFocus" o = Gtk.Window.WindowSetFocusMethodInfo
    ResolveFileChooserDialogMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveFileChooserDialogMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveFileChooserDialogMethod "setFocusVisible" o = Gtk.Window.WindowSetFocusVisibleMethodInfo
    ResolveFileChooserDialogMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveFileChooserDialogMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveFileChooserDialogMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveFileChooserDialogMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveFileChooserDialogMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveFileChooserDialogMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveFileChooserDialogMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveFileChooserDialogMethod "setHideOnClose" o = Gtk.Window.WindowSetHideOnCloseMethodInfo
    ResolveFileChooserDialogMethod "setIconName" o = Gtk.Window.WindowSetIconNameMethodInfo
    ResolveFileChooserDialogMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveFileChooserDialogMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveFileChooserDialogMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveFileChooserDialogMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveFileChooserDialogMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveFileChooserDialogMethod "setMnemonicsVisible" o = Gtk.Window.WindowSetMnemonicsVisibleMethodInfo
    ResolveFileChooserDialogMethod "setModal" o = Gtk.Window.WindowSetModalMethodInfo
    ResolveFileChooserDialogMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveFileChooserDialogMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveFileChooserDialogMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveFileChooserDialogMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveFileChooserDialogMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveFileChooserDialogMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveFileChooserDialogMethod "setResizable" o = Gtk.Window.WindowSetResizableMethodInfo
    ResolveFileChooserDialogMethod "setResponseSensitive" o = Gtk.Dialog.DialogSetResponseSensitiveMethodInfo
    ResolveFileChooserDialogMethod "setSelectMultiple" o = Gtk.FileChooser.FileChooserSetSelectMultipleMethodInfo
    ResolveFileChooserDialogMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveFileChooserDialogMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveFileChooserDialogMethod "setStartupId" o = Gtk.Window.WindowSetStartupIdMethodInfo
    ResolveFileChooserDialogMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveFileChooserDialogMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveFileChooserDialogMethod "setTitle" o = Gtk.Window.WindowSetTitleMethodInfo
    ResolveFileChooserDialogMethod "setTitlebar" o = Gtk.Window.WindowSetTitlebarMethodInfo
    ResolveFileChooserDialogMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveFileChooserDialogMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveFileChooserDialogMethod "setTransientFor" o = Gtk.Window.WindowSetTransientForMethodInfo
    ResolveFileChooserDialogMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveFileChooserDialogMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveFileChooserDialogMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveFileChooserDialogMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveFileChooserDialogMethod l o = O.MethodResolutionFailed l o

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FileChooserDialog
type instance O.AttributeList FileChooserDialog = FileChooserDialogAttributeList
type FileChooserDialogAttributeList = ('[ '("action", Gtk.FileChooser.FileChooserActionPropertyInfo), '("application", Gtk.Window.WindowApplicationPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("child", Gtk.Window.WindowChildPropertyInfo), '("createFolders", Gtk.FileChooser.FileChooserCreateFoldersPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("decorated", Gtk.Window.WindowDecoratedPropertyInfo), '("defaultHeight", Gtk.Window.WindowDefaultHeightPropertyInfo), '("defaultWidget", Gtk.Window.WindowDefaultWidgetPropertyInfo), '("defaultWidth", Gtk.Window.WindowDefaultWidthPropertyInfo), '("deletable", Gtk.Window.WindowDeletablePropertyInfo), '("destroyWithParent", Gtk.Window.WindowDestroyWithParentPropertyInfo), '("display", Gtk.Window.WindowDisplayPropertyInfo), '("filter", Gtk.FileChooser.FileChooserFilterPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusVisible", Gtk.Window.WindowFocusVisiblePropertyInfo), '("focusWidget", Gtk.Window.WindowFocusWidgetPropertyInfo), '("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), '("hideOnClose", Gtk.Window.WindowHideOnClosePropertyInfo), '("iconName", Gtk.Window.WindowIconNamePropertyInfo), '("isActive", Gtk.Window.WindowIsActivePropertyInfo), '("isMaximized", Gtk.Window.WindowIsMaximizedPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("mnemonicsVisible", Gtk.Window.WindowMnemonicsVisiblePropertyInfo), '("modal", Gtk.Window.WindowModalPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resizable", Gtk.Window.WindowResizablePropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("selectMultiple", Gtk.FileChooser.FileChooserSelectMultiplePropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("startupId", Gtk.Window.WindowStartupIdPropertyInfo), '("title", Gtk.Window.WindowTitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("transientFor", Gtk.Window.WindowTransientForPropertyInfo), '("useHeaderBar", Gtk.Dialog.DialogUseHeaderBarPropertyInfo), '("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)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FileChooserDialog = FileChooserDialogSignalList
type FileChooserDialogSignalList = ('[ '("activateDefault", Gtk.Window.WindowActivateDefaultSignalInfo), '("activateFocus", Gtk.Window.WindowActivateFocusSignalInfo), '("close", Gtk.Dialog.DialogCloseSignalInfo), '("closeRequest", Gtk.Window.WindowCloseRequestSignalInfo), '("currentFolderChanged", Gtk.FileChooser.FileChooserCurrentFolderChangedSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("enableDebugging", Gtk.Window.WindowEnableDebuggingSignalInfo), '("fileActivated", Gtk.FileChooser.FileChooserFileActivatedSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("keysChanged", Gtk.Window.WindowKeysChangedSignalInfo), '("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", Gtk.Dialog.DialogResponseSignalInfo), '("selectionChanged", Gtk.FileChooser.FileChooserSelectionChangedSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif