{-# 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.AppChooserDialog.AppChooserDialog' shows a t'GI.Gtk.Objects.AppChooserWidget.AppChooserWidget' inside a t'GI.Gtk.Objects.Dialog.Dialog'.
-- 
-- Note that t'GI.Gtk.Objects.AppChooserDialog.AppChooserDialog' does not have any interesting methods
-- of its own. Instead, you should get the embedded t'GI.Gtk.Objects.AppChooserWidget.AppChooserWidget'
-- using 'GI.Gtk.Objects.AppChooserDialog.appChooserDialogGetWidget' and call its methods if
-- the generic t'GI.Gtk.Interfaces.AppChooser.AppChooser' interface is not sufficient for your needs.
-- 
-- To set the heading that is shown above the t'GI.Gtk.Objects.AppChooserWidget.AppChooserWidget',
-- use 'GI.Gtk.Objects.AppChooserDialog.appChooserDialogSetHeading'.

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

module GI.Gtk.Objects.AppChooserDialog
    ( 

-- * Exported types
    AppChooserDialog(..)                    ,
    IsAppChooserDialog                      ,
    toAppChooserDialog                      ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveAppChooserDialogMethod           ,
#endif


-- ** getHeading #method:getHeading#

#if defined(ENABLE_OVERLOADING)
    AppChooserDialogGetHeadingMethodInfo    ,
#endif
    appChooserDialogGetHeading              ,


-- ** getWidget #method:getWidget#

#if defined(ENABLE_OVERLOADING)
    AppChooserDialogGetWidgetMethodInfo     ,
#endif
    appChooserDialogGetWidget               ,


-- ** new #method:new#

    appChooserDialogNew                     ,


-- ** newForContentType #method:newForContentType#

    appChooserDialogNewForContentType       ,


-- ** setHeading #method:setHeading#

#if defined(ENABLE_OVERLOADING)
    AppChooserDialogSetHeadingMethodInfo    ,
#endif
    appChooserDialogSetHeading              ,




 -- * Properties
-- ** gfile #attr:gfile#
-- | The GFile used by the t'GI.Gtk.Objects.AppChooserDialog.AppChooserDialog'.
-- The dialog\'s t'GI.Gtk.Objects.AppChooserWidget.AppChooserWidget' content type will be guessed from the
-- file, if present.

#if defined(ENABLE_OVERLOADING)
    AppChooserDialogGfilePropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    appChooserDialogGfile                   ,
#endif
    constructAppChooserDialogGfile          ,
    getAppChooserDialogGfile                ,


-- ** heading #attr:heading#
-- | The text to show at the top of the dialog.
-- The string may contain Pango markup.

#if defined(ENABLE_OVERLOADING)
    AppChooserDialogHeadingPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    appChooserDialogHeading                 ,
#endif
    constructAppChooserDialogHeading        ,
    getAppChooserDialogHeading              ,
    setAppChooserDialogHeading              ,




    ) 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 qualified GI.Gio.Interfaces.File as Gio.File
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.AppChooser as Gtk.AppChooser
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.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 AppChooserDialog = AppChooserDialog (SP.ManagedPtr AppChooserDialog)
    deriving (AppChooserDialog -> AppChooserDialog -> Bool
(AppChooserDialog -> AppChooserDialog -> Bool)
-> (AppChooserDialog -> AppChooserDialog -> Bool)
-> Eq AppChooserDialog
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AppChooserDialog -> AppChooserDialog -> Bool
$c/= :: AppChooserDialog -> AppChooserDialog -> Bool
== :: AppChooserDialog -> AppChooserDialog -> Bool
$c== :: AppChooserDialog -> AppChooserDialog -> Bool
Eq)

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

foreign import ccall "gtk_app_chooser_dialog_get_type"
    c_gtk_app_chooser_dialog_get_type :: IO B.Types.GType

instance B.Types.TypedObject AppChooserDialog where
    glibType :: IO GType
glibType = IO GType
c_gtk_app_chooser_dialog_get_type

instance B.Types.GObject AppChooserDialog

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

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

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

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

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

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

#endif

-- VVV Prop "gfile"
   -- Type: TInterface (Name {namespace = "Gio", name = "File"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gfile@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' appChooserDialog #gfile
-- @
getAppChooserDialogGfile :: (MonadIO m, IsAppChooserDialog o) => o -> m (Maybe Gio.File.File)
getAppChooserDialogGfile :: o -> m (Maybe File)
getAppChooserDialogGfile o
obj = IO (Maybe File) -> m (Maybe File)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe File) -> m (Maybe File))
-> IO (Maybe File) -> m (Maybe File)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr File -> File) -> IO (Maybe File)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"gfile" ManagedPtr File -> File
Gio.File.File

-- | Construct a `GValueConstruct` with valid value for the “@gfile@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAppChooserDialogGfile :: (IsAppChooserDialog o, MIO.MonadIO m, Gio.File.IsFile a) => a -> m (GValueConstruct o)
constructAppChooserDialogGfile :: a -> m (GValueConstruct o)
constructAppChooserDialogGfile 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
"gfile" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data AppChooserDialogGfilePropertyInfo
instance AttrInfo AppChooserDialogGfilePropertyInfo where
    type AttrAllowedOps AppChooserDialogGfilePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint AppChooserDialogGfilePropertyInfo = IsAppChooserDialog
    type AttrSetTypeConstraint AppChooserDialogGfilePropertyInfo = Gio.File.IsFile
    type AttrTransferTypeConstraint AppChooserDialogGfilePropertyInfo = Gio.File.IsFile
    type AttrTransferType AppChooserDialogGfilePropertyInfo = Gio.File.File
    type AttrGetType AppChooserDialogGfilePropertyInfo = (Maybe Gio.File.File)
    type AttrLabel AppChooserDialogGfilePropertyInfo = "gfile"
    type AttrOrigin AppChooserDialogGfilePropertyInfo = AppChooserDialog
    attrGet = getAppChooserDialogGfile
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.File.File v
    attrConstruct = constructAppChooserDialogGfile
    attrClear = undefined
#endif

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

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

-- | Set the value of the “@heading@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' appChooserDialog [ #heading 'Data.GI.Base.Attributes.:=' value ]
-- @
setAppChooserDialogHeading :: (MonadIO m, IsAppChooserDialog o) => o -> T.Text -> m ()
setAppChooserDialogHeading :: o -> Text -> m ()
setAppChooserDialogHeading 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
"heading" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@heading@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructAppChooserDialogHeading :: (IsAppChooserDialog o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructAppChooserDialogHeading :: Text -> m (GValueConstruct o)
constructAppChooserDialogHeading 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
"heading" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data AppChooserDialogHeadingPropertyInfo
instance AttrInfo AppChooserDialogHeadingPropertyInfo where
    type AttrAllowedOps AppChooserDialogHeadingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AppChooserDialogHeadingPropertyInfo = IsAppChooserDialog
    type AttrSetTypeConstraint AppChooserDialogHeadingPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint AppChooserDialogHeadingPropertyInfo = (~) T.Text
    type AttrTransferType AppChooserDialogHeadingPropertyInfo = T.Text
    type AttrGetType AppChooserDialogHeadingPropertyInfo = (Maybe T.Text)
    type AttrLabel AppChooserDialogHeadingPropertyInfo = "heading"
    type AttrOrigin AppChooserDialogHeadingPropertyInfo = AppChooserDialog
    attrGet = getAppChooserDialogHeading
    attrSet = setAppChooserDialogHeading
    attrTransfer _ v = do
        return v
    attrConstruct = constructAppChooserDialogHeading
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AppChooserDialog
type instance O.AttributeList AppChooserDialog = AppChooserDialogAttributeList
type AppChooserDialogAttributeList = ('[ '("application", Gtk.Window.WindowApplicationPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("child", Gtk.Window.WindowChildPropertyInfo), '("contentType", Gtk.AppChooser.AppChooserContentTypePropertyInfo), '("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), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusVisible", Gtk.Window.WindowFocusVisiblePropertyInfo), '("focusWidget", Gtk.Window.WindowFocusWidgetPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("gfile", AppChooserDialogGfilePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heading", AppChooserDialogHeadingPropertyInfo), '("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), '("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)
appChooserDialogGfile :: AttrLabelProxy "gfile"
appChooserDialogGfile = AttrLabelProxy

appChooserDialogHeading :: AttrLabelProxy "heading"
appChooserDialogHeading = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AppChooserDialog = AppChooserDialogSignalList
type AppChooserDialogSignalList = ('[ '("activateDefault", Gtk.Window.WindowActivateDefaultSignalInfo), '("activateFocus", Gtk.Window.WindowActivateFocusSignalInfo), '("close", Gtk.Dialog.DialogCloseSignalInfo), '("closeRequest", Gtk.Window.WindowCloseRequestSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("enableDebugging", Gtk.Window.WindowEnableDebuggingSignalInfo), '("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), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

-- method AppChooserDialog::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWindow, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "DialogFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags for this dialog"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "AppChooserDialog" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_app_chooser_dialog_new" gtk_app_chooser_dialog_new :: 
    Ptr Gtk.Window.Window ->                -- parent : TInterface (Name {namespace = "Gtk", name = "Window"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "DialogFlags"})
    Ptr Gio.File.File ->                    -- file : TInterface (Name {namespace = "Gio", name = "File"})
    IO (Ptr AppChooserDialog)

-- | Creates a new t'GI.Gtk.Objects.AppChooserDialog.AppChooserDialog' for the provided t'GI.Gio.Interfaces.File.File',
-- to allow the user to select an application for it.
appChooserDialogNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Window.IsWindow a, Gio.File.IsFile b) =>
    Maybe (a)
    -- ^ /@parent@/: a t'GI.Gtk.Objects.Window.Window', or 'P.Nothing'
    -> [Gtk.Flags.DialogFlags]
    -- ^ /@flags@/: flags for this dialog
    -> b
    -- ^ /@file@/: a t'GI.Gio.Interfaces.File.File'
    -> m AppChooserDialog
    -- ^ __Returns:__ a newly created t'GI.Gtk.Objects.AppChooserDialog.AppChooserDialog'
appChooserDialogNew :: Maybe a -> [DialogFlags] -> b -> m AppChooserDialog
appChooserDialogNew Maybe a
parent [DialogFlags]
flags b
file = IO AppChooserDialog -> m AppChooserDialog
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AppChooserDialog -> m AppChooserDialog)
-> IO AppChooserDialog -> m AppChooserDialog
forall a b. (a -> b) -> a -> b
$ do
    Ptr Window
maybeParent <- case Maybe a
parent of
        Maybe a
Nothing -> Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
        Just a
jParent -> do
            Ptr Window
jParent' <- a -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jParent
            Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jParent'
    let flags' :: CUInt
flags' = [DialogFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DialogFlags]
flags
    Ptr File
file' <- b -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
file
    Ptr AppChooserDialog
result <- Ptr Window -> CUInt -> Ptr File -> IO (Ptr AppChooserDialog)
gtk_app_chooser_dialog_new Ptr Window
maybeParent CUInt
flags' Ptr File
file'
    Text -> Ptr AppChooserDialog -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"appChooserDialogNew" Ptr AppChooserDialog
result
    AppChooserDialog
result' <- ((ManagedPtr AppChooserDialog -> AppChooserDialog)
-> Ptr AppChooserDialog -> IO AppChooserDialog
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr AppChooserDialog -> AppChooserDialog
AppChooserDialog) Ptr AppChooserDialog
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
parent a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
file
    AppChooserDialog -> IO AppChooserDialog
forall (m :: * -> *) a. Monad m => a -> m a
return AppChooserDialog
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method AppChooserDialog::new_for_content_type
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWindow, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "DialogFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags for this dialog"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "content_type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a content type string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "AppChooserDialog" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_app_chooser_dialog_new_for_content_type" gtk_app_chooser_dialog_new_for_content_type :: 
    Ptr Gtk.Window.Window ->                -- parent : TInterface (Name {namespace = "Gtk", name = "Window"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "DialogFlags"})
    CString ->                              -- content_type : TBasicType TUTF8
    IO (Ptr AppChooserDialog)

-- | Creates a new t'GI.Gtk.Objects.AppChooserDialog.AppChooserDialog' for the provided content type,
-- to allow the user to select an application for it.
appChooserDialogNewForContentType ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Window.IsWindow a) =>
    Maybe (a)
    -- ^ /@parent@/: a t'GI.Gtk.Objects.Window.Window', or 'P.Nothing'
    -> [Gtk.Flags.DialogFlags]
    -- ^ /@flags@/: flags for this dialog
    -> T.Text
    -- ^ /@contentType@/: a content type string
    -> m AppChooserDialog
    -- ^ __Returns:__ a newly created t'GI.Gtk.Objects.AppChooserDialog.AppChooserDialog'
appChooserDialogNewForContentType :: Maybe a -> [DialogFlags] -> Text -> m AppChooserDialog
appChooserDialogNewForContentType Maybe a
parent [DialogFlags]
flags Text
contentType = IO AppChooserDialog -> m AppChooserDialog
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AppChooserDialog -> m AppChooserDialog)
-> IO AppChooserDialog -> m AppChooserDialog
forall a b. (a -> b) -> a -> b
$ do
    Ptr Window
maybeParent <- case Maybe a
parent of
        Maybe a
Nothing -> Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
        Just a
jParent -> do
            Ptr Window
jParent' <- a -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jParent
            Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jParent'
    let flags' :: CUInt
flags' = [DialogFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DialogFlags]
flags
    CString
contentType' <- Text -> IO CString
textToCString Text
contentType
    Ptr AppChooserDialog
result <- Ptr Window -> CUInt -> CString -> IO (Ptr AppChooserDialog)
gtk_app_chooser_dialog_new_for_content_type Ptr Window
maybeParent CUInt
flags' CString
contentType'
    Text -> Ptr AppChooserDialog -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"appChooserDialogNewForContentType" Ptr AppChooserDialog
result
    AppChooserDialog
result' <- ((ManagedPtr AppChooserDialog -> AppChooserDialog)
-> Ptr AppChooserDialog -> IO AppChooserDialog
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr AppChooserDialog -> AppChooserDialog
AppChooserDialog) Ptr AppChooserDialog
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
parent a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
contentType'
    AppChooserDialog -> IO AppChooserDialog
forall (m :: * -> *) a. Monad m => a -> m a
return AppChooserDialog
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method AppChooserDialog::get_heading
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "AppChooserDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkAppChooserDialog"
--                 , 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_app_chooser_dialog_get_heading" gtk_app_chooser_dialog_get_heading :: 
    Ptr AppChooserDialog ->                 -- self : TInterface (Name {namespace = "Gtk", name = "AppChooserDialog"})
    IO CString

-- | Returns the text to display at the top of the dialog.
appChooserDialogGetHeading ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppChooserDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.AppChooserDialog.AppChooserDialog'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the text to display at the top of the dialog, or 'P.Nothing', in which
    --     case a default text is displayed
appChooserDialogGetHeading :: a -> m (Maybe Text)
appChooserDialogGetHeading a
self = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppChooserDialog
self' <- a -> IO (Ptr AppChooserDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr AppChooserDialog -> IO CString
gtk_app_chooser_dialog_get_heading Ptr AppChooserDialog
self'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data AppChooserDialogGetHeadingMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsAppChooserDialog a) => O.MethodInfo AppChooserDialogGetHeadingMethodInfo a signature where
    overloadedMethod = appChooserDialogGetHeading

#endif

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

foreign import ccall "gtk_app_chooser_dialog_get_widget" gtk_app_chooser_dialog_get_widget :: 
    Ptr AppChooserDialog ->                 -- self : TInterface (Name {namespace = "Gtk", name = "AppChooserDialog"})
    IO (Ptr Gtk.Widget.Widget)

-- | Returns the t'GI.Gtk.Objects.AppChooserWidget.AppChooserWidget' of this dialog.
appChooserDialogGetWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppChooserDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.AppChooserDialog.AppChooserDialog'
    -> m Gtk.Widget.Widget
    -- ^ __Returns:__ the t'GI.Gtk.Objects.AppChooserWidget.AppChooserWidget' of /@self@/
appChooserDialogGetWidget :: a -> m Widget
appChooserDialogGetWidget a
self = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppChooserDialog
self' <- a -> IO (Ptr AppChooserDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr AppChooserDialog -> IO (Ptr Widget)
gtk_app_chooser_dialog_get_widget Ptr AppChooserDialog
self'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"appChooserDialogGetWidget" Ptr Widget
result
    Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'

#if defined(ENABLE_OVERLOADING)
data AppChooserDialogGetWidgetMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsAppChooserDialog a) => O.MethodInfo AppChooserDialogGetWidgetMethodInfo a signature where
    overloadedMethod = appChooserDialogGetWidget

#endif

-- method AppChooserDialog::set_heading
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "AppChooserDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkAppChooserDialog"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "heading"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string containing Pango markup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_app_chooser_dialog_set_heading" gtk_app_chooser_dialog_set_heading :: 
    Ptr AppChooserDialog ->                 -- self : TInterface (Name {namespace = "Gtk", name = "AppChooserDialog"})
    CString ->                              -- heading : TBasicType TUTF8
    IO ()

-- | Sets the text to display at the top of the dialog.
-- If the heading is not set, the dialog displays a default text.
appChooserDialogSetHeading ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppChooserDialog a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.AppChooserDialog.AppChooserDialog'
    -> T.Text
    -- ^ /@heading@/: a string containing Pango markup
    -> m ()
appChooserDialogSetHeading :: a -> Text -> m ()
appChooserDialogSetHeading a
self Text
heading = 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 AppChooserDialog
self' <- a -> IO (Ptr AppChooserDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
heading' <- Text -> IO CString
textToCString Text
heading
    Ptr AppChooserDialog -> CString -> IO ()
gtk_app_chooser_dialog_set_heading Ptr AppChooserDialog
self' CString
heading'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
heading'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif