{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.FileChooserWidget
(
FileChooserWidget(..) ,
IsFileChooserWidget ,
toFileChooserWidget ,
#if defined(ENABLE_OVERLOADING)
ResolveFileChooserWidgetMethod ,
#endif
fileChooserWidgetNew ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetSearchModePropertyInfo ,
#endif
constructFileChooserWidgetSearchMode ,
#if defined(ENABLE_OVERLOADING)
fileChooserWidgetSearchMode ,
#endif
getFileChooserWidgetSearchMode ,
setFileChooserWidgetSearchMode ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetSubtitlePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
fileChooserWidgetSubtitle ,
#endif
getFileChooserWidgetSubtitle ,
FileChooserWidgetDesktopFolderCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetDesktopFolderSignalInfo,
#endif
afterFileChooserWidgetDesktopFolder ,
onFileChooserWidgetDesktopFolder ,
FileChooserWidgetDownFolderCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetDownFolderSignalInfo ,
#endif
afterFileChooserWidgetDownFolder ,
onFileChooserWidgetDownFolder ,
FileChooserWidgetHomeFolderCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetHomeFolderSignalInfo ,
#endif
afterFileChooserWidgetHomeFolder ,
onFileChooserWidgetHomeFolder ,
FileChooserWidgetLocationPopupCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetLocationPopupSignalInfo,
#endif
afterFileChooserWidgetLocationPopup ,
onFileChooserWidgetLocationPopup ,
FileChooserWidgetLocationPopupOnPasteCallback,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetLocationPopupOnPasteSignalInfo,
#endif
afterFileChooserWidgetLocationPopupOnPaste,
onFileChooserWidgetLocationPopupOnPaste ,
FileChooserWidgetLocationTogglePopupCallback,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetLocationTogglePopupSignalInfo,
#endif
afterFileChooserWidgetLocationTogglePopup,
onFileChooserWidgetLocationTogglePopup ,
FileChooserWidgetPlacesShortcutCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetPlacesShortcutSignalInfo,
#endif
afterFileChooserWidgetPlacesShortcut ,
onFileChooserWidgetPlacesShortcut ,
FileChooserWidgetQuickBookmarkCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetQuickBookmarkSignalInfo,
#endif
afterFileChooserWidgetQuickBookmark ,
onFileChooserWidgetQuickBookmark ,
FileChooserWidgetRecentShortcutCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetRecentShortcutSignalInfo,
#endif
afterFileChooserWidgetRecentShortcut ,
onFileChooserWidgetRecentShortcut ,
FileChooserWidgetSearchShortcutCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetSearchShortcutSignalInfo,
#endif
afterFileChooserWidgetSearchShortcut ,
onFileChooserWidgetSearchShortcut ,
FileChooserWidgetShowHiddenCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetShowHiddenSignalInfo ,
#endif
afterFileChooserWidgetShowHidden ,
onFileChooserWidgetShowHidden ,
FileChooserWidgetUpFolderCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserWidgetUpFolderSignalInfo ,
#endif
afterFileChooserWidgetUpFolder ,
onFileChooserWidgetUpFolder ,
) 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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 GHC.Records as R
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.FileChooser as Gtk.FileChooser
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Box as Gtk.Box
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype FileChooserWidget = FileChooserWidget (SP.ManagedPtr FileChooserWidget)
deriving (FileChooserWidget -> FileChooserWidget -> Bool
(FileChooserWidget -> FileChooserWidget -> Bool)
-> (FileChooserWidget -> FileChooserWidget -> Bool)
-> Eq FileChooserWidget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileChooserWidget -> FileChooserWidget -> Bool
== :: FileChooserWidget -> FileChooserWidget -> Bool
$c/= :: FileChooserWidget -> FileChooserWidget -> Bool
/= :: FileChooserWidget -> FileChooserWidget -> Bool
Eq)
instance SP.ManagedPtrNewtype FileChooserWidget where
toManagedPtr :: FileChooserWidget -> ManagedPtr FileChooserWidget
toManagedPtr (FileChooserWidget ManagedPtr FileChooserWidget
p) = ManagedPtr FileChooserWidget
p
foreign import ccall "gtk_file_chooser_widget_get_type"
c_gtk_file_chooser_widget_get_type :: IO B.Types.GType
instance B.Types.TypedObject FileChooserWidget where
glibType :: IO GType
glibType = IO GType
c_gtk_file_chooser_widget_get_type
instance B.Types.GObject FileChooserWidget
class (SP.GObject o, O.IsDescendantOf FileChooserWidget o) => IsFileChooserWidget o
instance (SP.GObject o, O.IsDescendantOf FileChooserWidget o) => IsFileChooserWidget o
instance O.HasParentTypes FileChooserWidget
type instance O.ParentTypes FileChooserWidget = '[Gtk.Box.Box, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, Gtk.FileChooser.FileChooser, Gtk.Orientable.Orientable]
toFileChooserWidget :: (MIO.MonadIO m, IsFileChooserWidget o) => o -> m FileChooserWidget
toFileChooserWidget :: forall (m :: * -> *) o.
(MonadIO m, IsFileChooserWidget o) =>
o -> m FileChooserWidget
toFileChooserWidget = IO FileChooserWidget -> m FileChooserWidget
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO FileChooserWidget -> m FileChooserWidget)
-> (o -> IO FileChooserWidget) -> o -> m FileChooserWidget
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr FileChooserWidget -> FileChooserWidget)
-> o -> IO FileChooserWidget
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr FileChooserWidget -> FileChooserWidget
FileChooserWidget
instance B.GValue.IsGValue (Maybe FileChooserWidget) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_file_chooser_widget_get_type
gvalueSet_ :: Ptr GValue -> Maybe FileChooserWidget -> IO ()
gvalueSet_ Ptr GValue
gv Maybe FileChooserWidget
P.Nothing = Ptr GValue -> Ptr FileChooserWidget -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr FileChooserWidget
forall a. Ptr a
FP.nullPtr :: FP.Ptr FileChooserWidget)
gvalueSet_ Ptr GValue
gv (P.Just FileChooserWidget
obj) = FileChooserWidget -> (Ptr FileChooserWidget -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FileChooserWidget
obj (Ptr GValue -> Ptr FileChooserWidget -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe FileChooserWidget)
gvalueGet_ Ptr GValue
gv = do
Ptr FileChooserWidget
ptr <- Ptr GValue -> IO (Ptr FileChooserWidget)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr FileChooserWidget)
if Ptr FileChooserWidget
ptr Ptr FileChooserWidget -> Ptr FileChooserWidget -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr FileChooserWidget
forall a. Ptr a
FP.nullPtr
then FileChooserWidget -> Maybe FileChooserWidget
forall a. a -> Maybe a
P.Just (FileChooserWidget -> Maybe FileChooserWidget)
-> IO FileChooserWidget -> IO (Maybe FileChooserWidget)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr FileChooserWidget -> FileChooserWidget)
-> Ptr FileChooserWidget -> IO FileChooserWidget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr FileChooserWidget -> FileChooserWidget
FileChooserWidget Ptr FileChooserWidget
ptr
else Maybe FileChooserWidget -> IO (Maybe FileChooserWidget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FileChooserWidget
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveFileChooserWidgetMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveFileChooserWidgetMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveFileChooserWidgetMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolveFileChooserWidgetMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveFileChooserWidgetMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveFileChooserWidgetMethod "addChoice" o = Gtk.FileChooser.FileChooserAddChoiceMethodInfo
ResolveFileChooserWidgetMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveFileChooserWidgetMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveFileChooserWidgetMethod "addFilter" o = Gtk.FileChooser.FileChooserAddFilterMethodInfo
ResolveFileChooserWidgetMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveFileChooserWidgetMethod "addShortcutFolder" o = Gtk.FileChooser.FileChooserAddShortcutFolderMethodInfo
ResolveFileChooserWidgetMethod "addShortcutFolderUri" o = Gtk.FileChooser.FileChooserAddShortcutFolderUriMethodInfo
ResolveFileChooserWidgetMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveFileChooserWidgetMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveFileChooserWidgetMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveFileChooserWidgetMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveFileChooserWidgetMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolveFileChooserWidgetMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveFileChooserWidgetMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolveFileChooserWidgetMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolveFileChooserWidgetMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolveFileChooserWidgetMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolveFileChooserWidgetMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolveFileChooserWidgetMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveFileChooserWidgetMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveFileChooserWidgetMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveFileChooserWidgetMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveFileChooserWidgetMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveFileChooserWidgetMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveFileChooserWidgetMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveFileChooserWidgetMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveFileChooserWidgetMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveFileChooserWidgetMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveFileChooserWidgetMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveFileChooserWidgetMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveFileChooserWidgetMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveFileChooserWidgetMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveFileChooserWidgetMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveFileChooserWidgetMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveFileChooserWidgetMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveFileChooserWidgetMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveFileChooserWidgetMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveFileChooserWidgetMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveFileChooserWidgetMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveFileChooserWidgetMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveFileChooserWidgetMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveFileChooserWidgetMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveFileChooserWidgetMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveFileChooserWidgetMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveFileChooserWidgetMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveFileChooserWidgetMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveFileChooserWidgetMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveFileChooserWidgetMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveFileChooserWidgetMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveFileChooserWidgetMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveFileChooserWidgetMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveFileChooserWidgetMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveFileChooserWidgetMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveFileChooserWidgetMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveFileChooserWidgetMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveFileChooserWidgetMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveFileChooserWidgetMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveFileChooserWidgetMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveFileChooserWidgetMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveFileChooserWidgetMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveFileChooserWidgetMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveFileChooserWidgetMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolveFileChooserWidgetMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveFileChooserWidgetMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolveFileChooserWidgetMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveFileChooserWidgetMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveFileChooserWidgetMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveFileChooserWidgetMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveFileChooserWidgetMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveFileChooserWidgetMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveFileChooserWidgetMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveFileChooserWidgetMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveFileChooserWidgetMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveFileChooserWidgetMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveFileChooserWidgetMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveFileChooserWidgetMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveFileChooserWidgetMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveFileChooserWidgetMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveFileChooserWidgetMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveFileChooserWidgetMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveFileChooserWidgetMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveFileChooserWidgetMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveFileChooserWidgetMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveFileChooserWidgetMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveFileChooserWidgetMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveFileChooserWidgetMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveFileChooserWidgetMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveFileChooserWidgetMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveFileChooserWidgetMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveFileChooserWidgetMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveFileChooserWidgetMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveFileChooserWidgetMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveFileChooserWidgetMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveFileChooserWidgetMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveFileChooserWidgetMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveFileChooserWidgetMethod "listFilters" o = Gtk.FileChooser.FileChooserListFiltersMethodInfo
ResolveFileChooserWidgetMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveFileChooserWidgetMethod "listShortcutFolderUris" o = Gtk.FileChooser.FileChooserListShortcutFolderUrisMethodInfo
ResolveFileChooserWidgetMethod "listShortcutFolders" o = Gtk.FileChooser.FileChooserListShortcutFoldersMethodInfo
ResolveFileChooserWidgetMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveFileChooserWidgetMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveFileChooserWidgetMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveFileChooserWidgetMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveFileChooserWidgetMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveFileChooserWidgetMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveFileChooserWidgetMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveFileChooserWidgetMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveFileChooserWidgetMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveFileChooserWidgetMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveFileChooserWidgetMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveFileChooserWidgetMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveFileChooserWidgetMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveFileChooserWidgetMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveFileChooserWidgetMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveFileChooserWidgetMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveFileChooserWidgetMethod "packEnd" o = Gtk.Box.BoxPackEndMethodInfo
ResolveFileChooserWidgetMethod "packStart" o = Gtk.Box.BoxPackStartMethodInfo
ResolveFileChooserWidgetMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveFileChooserWidgetMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveFileChooserWidgetMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolveFileChooserWidgetMethod "queryChildPacking" o = Gtk.Box.BoxQueryChildPackingMethodInfo
ResolveFileChooserWidgetMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveFileChooserWidgetMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveFileChooserWidgetMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveFileChooserWidgetMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveFileChooserWidgetMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveFileChooserWidgetMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveFileChooserWidgetMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveFileChooserWidgetMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveFileChooserWidgetMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveFileChooserWidgetMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveFileChooserWidgetMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveFileChooserWidgetMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveFileChooserWidgetMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolveFileChooserWidgetMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveFileChooserWidgetMethod "removeChoice" o = Gtk.FileChooser.FileChooserRemoveChoiceMethodInfo
ResolveFileChooserWidgetMethod "removeFilter" o = Gtk.FileChooser.FileChooserRemoveFilterMethodInfo
ResolveFileChooserWidgetMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveFileChooserWidgetMethod "removeShortcutFolder" o = Gtk.FileChooser.FileChooserRemoveShortcutFolderMethodInfo
ResolveFileChooserWidgetMethod "removeShortcutFolderUri" o = Gtk.FileChooser.FileChooserRemoveShortcutFolderUriMethodInfo
ResolveFileChooserWidgetMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveFileChooserWidgetMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveFileChooserWidgetMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveFileChooserWidgetMethod "reorderChild" o = Gtk.Box.BoxReorderChildMethodInfo
ResolveFileChooserWidgetMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveFileChooserWidgetMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveFileChooserWidgetMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveFileChooserWidgetMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolveFileChooserWidgetMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveFileChooserWidgetMethod "selectAll" o = Gtk.FileChooser.FileChooserSelectAllMethodInfo
ResolveFileChooserWidgetMethod "selectFile" o = Gtk.FileChooser.FileChooserSelectFileMethodInfo
ResolveFileChooserWidgetMethod "selectFilename" o = Gtk.FileChooser.FileChooserSelectFilenameMethodInfo
ResolveFileChooserWidgetMethod "selectUri" o = Gtk.FileChooser.FileChooserSelectUriMethodInfo
ResolveFileChooserWidgetMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveFileChooserWidgetMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveFileChooserWidgetMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveFileChooserWidgetMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveFileChooserWidgetMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveFileChooserWidgetMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveFileChooserWidgetMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveFileChooserWidgetMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveFileChooserWidgetMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveFileChooserWidgetMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveFileChooserWidgetMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveFileChooserWidgetMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveFileChooserWidgetMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveFileChooserWidgetMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveFileChooserWidgetMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveFileChooserWidgetMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveFileChooserWidgetMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveFileChooserWidgetMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveFileChooserWidgetMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveFileChooserWidgetMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveFileChooserWidgetMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveFileChooserWidgetMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveFileChooserWidgetMethod "unselectAll" o = Gtk.FileChooser.FileChooserUnselectAllMethodInfo
ResolveFileChooserWidgetMethod "unselectFile" o = Gtk.FileChooser.FileChooserUnselectFileMethodInfo
ResolveFileChooserWidgetMethod "unselectFilename" o = Gtk.FileChooser.FileChooserUnselectFilenameMethodInfo
ResolveFileChooserWidgetMethod "unselectUri" o = Gtk.FileChooser.FileChooserUnselectUriMethodInfo
ResolveFileChooserWidgetMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolveFileChooserWidgetMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveFileChooserWidgetMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveFileChooserWidgetMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveFileChooserWidgetMethod "getAction" o = Gtk.FileChooser.FileChooserGetActionMethodInfo
ResolveFileChooserWidgetMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveFileChooserWidgetMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveFileChooserWidgetMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveFileChooserWidgetMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveFileChooserWidgetMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveFileChooserWidgetMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveFileChooserWidgetMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveFileChooserWidgetMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveFileChooserWidgetMethod "getBaselinePosition" o = Gtk.Box.BoxGetBaselinePositionMethodInfo
ResolveFileChooserWidgetMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolveFileChooserWidgetMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveFileChooserWidgetMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveFileChooserWidgetMethod "getCenterWidget" o = Gtk.Box.BoxGetCenterWidgetMethodInfo
ResolveFileChooserWidgetMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveFileChooserWidgetMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveFileChooserWidgetMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolveFileChooserWidgetMethod "getChoice" o = Gtk.FileChooser.FileChooserGetChoiceMethodInfo
ResolveFileChooserWidgetMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveFileChooserWidgetMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveFileChooserWidgetMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveFileChooserWidgetMethod "getCreateFolders" o = Gtk.FileChooser.FileChooserGetCreateFoldersMethodInfo
ResolveFileChooserWidgetMethod "getCurrentFolder" o = Gtk.FileChooser.FileChooserGetCurrentFolderMethodInfo
ResolveFileChooserWidgetMethod "getCurrentFolderFile" o = Gtk.FileChooser.FileChooserGetCurrentFolderFileMethodInfo
ResolveFileChooserWidgetMethod "getCurrentFolderUri" o = Gtk.FileChooser.FileChooserGetCurrentFolderUriMethodInfo
ResolveFileChooserWidgetMethod "getCurrentName" o = Gtk.FileChooser.FileChooserGetCurrentNameMethodInfo
ResolveFileChooserWidgetMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveFileChooserWidgetMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveFileChooserWidgetMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveFileChooserWidgetMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveFileChooserWidgetMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveFileChooserWidgetMethod "getDoOverwriteConfirmation" o = Gtk.FileChooser.FileChooserGetDoOverwriteConfirmationMethodInfo
ResolveFileChooserWidgetMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveFileChooserWidgetMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveFileChooserWidgetMethod "getExtraWidget" o = Gtk.FileChooser.FileChooserGetExtraWidgetMethodInfo
ResolveFileChooserWidgetMethod "getFile" o = Gtk.FileChooser.FileChooserGetFileMethodInfo
ResolveFileChooserWidgetMethod "getFilename" o = Gtk.FileChooser.FileChooserGetFilenameMethodInfo
ResolveFileChooserWidgetMethod "getFilenames" o = Gtk.FileChooser.FileChooserGetFilenamesMethodInfo
ResolveFileChooserWidgetMethod "getFiles" o = Gtk.FileChooser.FileChooserGetFilesMethodInfo
ResolveFileChooserWidgetMethod "getFilter" o = Gtk.FileChooser.FileChooserGetFilterMethodInfo
ResolveFileChooserWidgetMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolveFileChooserWidgetMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolveFileChooserWidgetMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolveFileChooserWidgetMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveFileChooserWidgetMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolveFileChooserWidgetMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveFileChooserWidgetMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveFileChooserWidgetMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveFileChooserWidgetMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveFileChooserWidgetMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveFileChooserWidgetMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveFileChooserWidgetMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveFileChooserWidgetMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveFileChooserWidgetMethod "getHomogeneous" o = Gtk.Box.BoxGetHomogeneousMethodInfo
ResolveFileChooserWidgetMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveFileChooserWidgetMethod "getLocalOnly" o = Gtk.FileChooser.FileChooserGetLocalOnlyMethodInfo
ResolveFileChooserWidgetMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveFileChooserWidgetMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveFileChooserWidgetMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveFileChooserWidgetMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveFileChooserWidgetMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveFileChooserWidgetMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveFileChooserWidgetMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveFileChooserWidgetMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveFileChooserWidgetMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveFileChooserWidgetMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveFileChooserWidgetMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveFileChooserWidgetMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveFileChooserWidgetMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
ResolveFileChooserWidgetMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveFileChooserWidgetMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveFileChooserWidgetMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveFileChooserWidgetMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveFileChooserWidgetMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolveFileChooserWidgetMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveFileChooserWidgetMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveFileChooserWidgetMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveFileChooserWidgetMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveFileChooserWidgetMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveFileChooserWidgetMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveFileChooserWidgetMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveFileChooserWidgetMethod "getPreviewFile" o = Gtk.FileChooser.FileChooserGetPreviewFileMethodInfo
ResolveFileChooserWidgetMethod "getPreviewFilename" o = Gtk.FileChooser.FileChooserGetPreviewFilenameMethodInfo
ResolveFileChooserWidgetMethod "getPreviewUri" o = Gtk.FileChooser.FileChooserGetPreviewUriMethodInfo
ResolveFileChooserWidgetMethod "getPreviewWidget" o = Gtk.FileChooser.FileChooserGetPreviewWidgetMethodInfo
ResolveFileChooserWidgetMethod "getPreviewWidgetActive" o = Gtk.FileChooser.FileChooserGetPreviewWidgetActiveMethodInfo
ResolveFileChooserWidgetMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveFileChooserWidgetMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveFileChooserWidgetMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveFileChooserWidgetMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveFileChooserWidgetMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveFileChooserWidgetMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveFileChooserWidgetMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolveFileChooserWidgetMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveFileChooserWidgetMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveFileChooserWidgetMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveFileChooserWidgetMethod "getSelectMultiple" o = Gtk.FileChooser.FileChooserGetSelectMultipleMethodInfo
ResolveFileChooserWidgetMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveFileChooserWidgetMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveFileChooserWidgetMethod "getShowHidden" o = Gtk.FileChooser.FileChooserGetShowHiddenMethodInfo
ResolveFileChooserWidgetMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveFileChooserWidgetMethod "getSpacing" o = Gtk.Box.BoxGetSpacingMethodInfo
ResolveFileChooserWidgetMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveFileChooserWidgetMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveFileChooserWidgetMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveFileChooserWidgetMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveFileChooserWidgetMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveFileChooserWidgetMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveFileChooserWidgetMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveFileChooserWidgetMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveFileChooserWidgetMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveFileChooserWidgetMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveFileChooserWidgetMethod "getUri" o = Gtk.FileChooser.FileChooserGetUriMethodInfo
ResolveFileChooserWidgetMethod "getUris" o = Gtk.FileChooser.FileChooserGetUrisMethodInfo
ResolveFileChooserWidgetMethod "getUsePreviewLabel" o = Gtk.FileChooser.FileChooserGetUsePreviewLabelMethodInfo
ResolveFileChooserWidgetMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveFileChooserWidgetMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveFileChooserWidgetMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveFileChooserWidgetMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveFileChooserWidgetMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveFileChooserWidgetMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveFileChooserWidgetMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveFileChooserWidgetMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveFileChooserWidgetMethod "setAction" o = Gtk.FileChooser.FileChooserSetActionMethodInfo
ResolveFileChooserWidgetMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveFileChooserWidgetMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveFileChooserWidgetMethod "setBaselinePosition" o = Gtk.Box.BoxSetBaselinePositionMethodInfo
ResolveFileChooserWidgetMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolveFileChooserWidgetMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveFileChooserWidgetMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveFileChooserWidgetMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveFileChooserWidgetMethod "setCenterWidget" o = Gtk.Box.BoxSetCenterWidgetMethodInfo
ResolveFileChooserWidgetMethod "setChildPacking" o = Gtk.Box.BoxSetChildPackingMethodInfo
ResolveFileChooserWidgetMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveFileChooserWidgetMethod "setChoice" o = Gtk.FileChooser.FileChooserSetChoiceMethodInfo
ResolveFileChooserWidgetMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveFileChooserWidgetMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveFileChooserWidgetMethod "setCreateFolders" o = Gtk.FileChooser.FileChooserSetCreateFoldersMethodInfo
ResolveFileChooserWidgetMethod "setCurrentFolder" o = Gtk.FileChooser.FileChooserSetCurrentFolderMethodInfo
ResolveFileChooserWidgetMethod "setCurrentFolderFile" o = Gtk.FileChooser.FileChooserSetCurrentFolderFileMethodInfo
ResolveFileChooserWidgetMethod "setCurrentFolderUri" o = Gtk.FileChooser.FileChooserSetCurrentFolderUriMethodInfo
ResolveFileChooserWidgetMethod "setCurrentName" o = Gtk.FileChooser.FileChooserSetCurrentNameMethodInfo
ResolveFileChooserWidgetMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveFileChooserWidgetMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveFileChooserWidgetMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveFileChooserWidgetMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveFileChooserWidgetMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveFileChooserWidgetMethod "setDoOverwriteConfirmation" o = Gtk.FileChooser.FileChooserSetDoOverwriteConfirmationMethodInfo
ResolveFileChooserWidgetMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveFileChooserWidgetMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveFileChooserWidgetMethod "setExtraWidget" o = Gtk.FileChooser.FileChooserSetExtraWidgetMethodInfo
ResolveFileChooserWidgetMethod "setFile" o = Gtk.FileChooser.FileChooserSetFileMethodInfo
ResolveFileChooserWidgetMethod "setFilename" o = Gtk.FileChooser.FileChooserSetFilenameMethodInfo
ResolveFileChooserWidgetMethod "setFilter" o = Gtk.FileChooser.FileChooserSetFilterMethodInfo
ResolveFileChooserWidgetMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolveFileChooserWidgetMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolveFileChooserWidgetMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolveFileChooserWidgetMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveFileChooserWidgetMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolveFileChooserWidgetMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveFileChooserWidgetMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveFileChooserWidgetMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveFileChooserWidgetMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveFileChooserWidgetMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveFileChooserWidgetMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveFileChooserWidgetMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveFileChooserWidgetMethod "setHomogeneous" o = Gtk.Box.BoxSetHomogeneousMethodInfo
ResolveFileChooserWidgetMethod "setLocalOnly" o = Gtk.FileChooser.FileChooserSetLocalOnlyMethodInfo
ResolveFileChooserWidgetMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveFileChooserWidgetMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveFileChooserWidgetMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveFileChooserWidgetMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveFileChooserWidgetMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveFileChooserWidgetMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveFileChooserWidgetMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveFileChooserWidgetMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveFileChooserWidgetMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveFileChooserWidgetMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveFileChooserWidgetMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
ResolveFileChooserWidgetMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveFileChooserWidgetMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveFileChooserWidgetMethod "setPreviewWidget" o = Gtk.FileChooser.FileChooserSetPreviewWidgetMethodInfo
ResolveFileChooserWidgetMethod "setPreviewWidgetActive" o = Gtk.FileChooser.FileChooserSetPreviewWidgetActiveMethodInfo
ResolveFileChooserWidgetMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveFileChooserWidgetMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveFileChooserWidgetMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolveFileChooserWidgetMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveFileChooserWidgetMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveFileChooserWidgetMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolveFileChooserWidgetMethod "setSelectMultiple" o = Gtk.FileChooser.FileChooserSetSelectMultipleMethodInfo
ResolveFileChooserWidgetMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveFileChooserWidgetMethod "setShowHidden" o = Gtk.FileChooser.FileChooserSetShowHiddenMethodInfo
ResolveFileChooserWidgetMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveFileChooserWidgetMethod "setSpacing" o = Gtk.Box.BoxSetSpacingMethodInfo
ResolveFileChooserWidgetMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveFileChooserWidgetMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveFileChooserWidgetMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveFileChooserWidgetMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveFileChooserWidgetMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveFileChooserWidgetMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveFileChooserWidgetMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveFileChooserWidgetMethod "setUri" o = Gtk.FileChooser.FileChooserSetUriMethodInfo
ResolveFileChooserWidgetMethod "setUsePreviewLabel" o = Gtk.FileChooser.FileChooserSetUsePreviewLabelMethodInfo
ResolveFileChooserWidgetMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveFileChooserWidgetMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveFileChooserWidgetMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveFileChooserWidgetMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveFileChooserWidgetMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveFileChooserWidgetMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveFileChooserWidgetMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveFileChooserWidgetMethod t FileChooserWidget, O.OverloadedMethod info FileChooserWidget p) => OL.IsLabel t (FileChooserWidget -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveFileChooserWidgetMethod t FileChooserWidget, O.OverloadedMethod info FileChooserWidget p, R.HasField t FileChooserWidget p) => R.HasField t FileChooserWidget p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveFileChooserWidgetMethod t FileChooserWidget, O.OverloadedMethodInfo info FileChooserWidget) => OL.IsLabel t (O.MethodProxy info FileChooserWidget) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type FileChooserWidgetDesktopFolderCallback =
IO ()
type C_FileChooserWidgetDesktopFolderCallback =
Ptr FileChooserWidget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileChooserWidgetDesktopFolderCallback :: C_FileChooserWidgetDesktopFolderCallback -> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
wrap_FileChooserWidgetDesktopFolderCallback ::
GObject a => (a -> FileChooserWidgetDesktopFolderCallback) ->
C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetDesktopFolderCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetDesktopFolderCallback a -> IO ()
gi'cb Ptr FileChooserWidget
gi'selfPtr Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> IO ()
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self)
onFileChooserWidgetDesktopFolder :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetDesktopFolderCallback) -> m SignalHandlerId
onFileChooserWidgetDesktopFolder :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onFileChooserWidgetDesktopFolder a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetDesktopFolderCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetDesktopFolderCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"desktop-folder" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetDesktopFolder :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetDesktopFolderCallback) -> m SignalHandlerId
afterFileChooserWidgetDesktopFolder :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterFileChooserWidgetDesktopFolder a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetDesktopFolderCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetDesktopFolderCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"desktop-folder" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetDesktopFolderSignalInfo
instance SignalInfo FileChooserWidgetDesktopFolderSignalInfo where
type HaskellCallbackType FileChooserWidgetDesktopFolderSignalInfo = FileChooserWidgetDesktopFolderCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetDesktopFolderCallback cb
cb'' <- mk_FileChooserWidgetDesktopFolderCallback cb'
connectSignalFunPtr obj "desktop-folder" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::desktop-folder"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:desktopFolder"})
#endif
type FileChooserWidgetDownFolderCallback =
IO ()
type C_FileChooserWidgetDownFolderCallback =
Ptr FileChooserWidget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileChooserWidgetDownFolderCallback :: C_FileChooserWidgetDownFolderCallback -> IO (FunPtr C_FileChooserWidgetDownFolderCallback)
wrap_FileChooserWidgetDownFolderCallback ::
GObject a => (a -> FileChooserWidgetDownFolderCallback) ->
C_FileChooserWidgetDownFolderCallback
wrap_FileChooserWidgetDownFolderCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetDownFolderCallback a -> IO ()
gi'cb Ptr FileChooserWidget
gi'selfPtr Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> IO ()
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self)
onFileChooserWidgetDownFolder :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetDownFolderCallback) -> m SignalHandlerId
onFileChooserWidgetDownFolder :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onFileChooserWidgetDownFolder a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetDownFolderCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetDownFolderCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"down-folder" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetDownFolder :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetDownFolderCallback) -> m SignalHandlerId
afterFileChooserWidgetDownFolder :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterFileChooserWidgetDownFolder a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetDownFolderCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetDownFolderCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"down-folder" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetDownFolderSignalInfo
instance SignalInfo FileChooserWidgetDownFolderSignalInfo where
type HaskellCallbackType FileChooserWidgetDownFolderSignalInfo = FileChooserWidgetDownFolderCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetDownFolderCallback cb
cb'' <- mk_FileChooserWidgetDownFolderCallback cb'
connectSignalFunPtr obj "down-folder" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::down-folder"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:downFolder"})
#endif
type FileChooserWidgetHomeFolderCallback =
IO ()
type C_FileChooserWidgetHomeFolderCallback =
Ptr FileChooserWidget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileChooserWidgetHomeFolderCallback :: C_FileChooserWidgetHomeFolderCallback -> IO (FunPtr C_FileChooserWidgetHomeFolderCallback)
wrap_FileChooserWidgetHomeFolderCallback ::
GObject a => (a -> FileChooserWidgetHomeFolderCallback) ->
C_FileChooserWidgetHomeFolderCallback
wrap_FileChooserWidgetHomeFolderCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetHomeFolderCallback a -> IO ()
gi'cb Ptr FileChooserWidget
gi'selfPtr Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> IO ()
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self)
onFileChooserWidgetHomeFolder :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetHomeFolderCallback) -> m SignalHandlerId
onFileChooserWidgetHomeFolder :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onFileChooserWidgetHomeFolder a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetHomeFolderCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetHomeFolderCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"home-folder" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetHomeFolder :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetHomeFolderCallback) -> m SignalHandlerId
afterFileChooserWidgetHomeFolder :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterFileChooserWidgetHomeFolder a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetHomeFolderCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetHomeFolderCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"home-folder" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetHomeFolderSignalInfo
instance SignalInfo FileChooserWidgetHomeFolderSignalInfo where
type HaskellCallbackType FileChooserWidgetHomeFolderSignalInfo = FileChooserWidgetHomeFolderCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetHomeFolderCallback cb
cb'' <- mk_FileChooserWidgetHomeFolderCallback cb'
connectSignalFunPtr obj "home-folder" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::home-folder"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:homeFolder"})
#endif
type =
T.Text
-> IO ()
type =
Ptr FileChooserWidget ->
CString ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
:: C_FileChooserWidgetLocationPopupCallback -> IO (FunPtr C_FileChooserWidgetLocationPopupCallback)
wrap_FileChooserWidgetLocationPopupCallback ::
GObject a => (a -> FileChooserWidgetLocationPopupCallback) ->
C_FileChooserWidgetLocationPopupCallback
a -> FileChooserWidgetLocationPopupCallback
gi'cb Ptr FileChooserWidget
gi'selfPtr CString
path Ptr ()
_ = do
Text
path' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
path
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> FileChooserWidgetLocationPopupCallback
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self) Text
path'
onFileChooserWidgetLocationPopup :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetLocationPopupCallback) -> m SignalHandlerId
a
obj (?self::a) => FileChooserWidgetLocationPopupCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> FileChooserWidgetLocationPopupCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => FileChooserWidgetLocationPopupCallback
FileChooserWidgetLocationPopupCallback
cb
let wrapped' :: C_FileChooserWidgetLocationPopupCallback
wrapped' = (a -> FileChooserWidgetLocationPopupCallback)
-> C_FileChooserWidgetLocationPopupCallback
forall a.
GObject a =>
(a -> FileChooserWidgetLocationPopupCallback)
-> C_FileChooserWidgetLocationPopupCallback
wrap_FileChooserWidgetLocationPopupCallback a -> FileChooserWidgetLocationPopupCallback
wrapped
FunPtr C_FileChooserWidgetLocationPopupCallback
wrapped'' <- C_FileChooserWidgetLocationPopupCallback
-> IO (FunPtr C_FileChooserWidgetLocationPopupCallback)
mk_FileChooserWidgetLocationPopupCallback C_FileChooserWidgetLocationPopupCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetLocationPopupCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"location-popup" FunPtr C_FileChooserWidgetLocationPopupCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetLocationPopup :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetLocationPopupCallback) -> m SignalHandlerId
a
obj (?self::a) => FileChooserWidgetLocationPopupCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> FileChooserWidgetLocationPopupCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => FileChooserWidgetLocationPopupCallback
FileChooserWidgetLocationPopupCallback
cb
let wrapped' :: C_FileChooserWidgetLocationPopupCallback
wrapped' = (a -> FileChooserWidgetLocationPopupCallback)
-> C_FileChooserWidgetLocationPopupCallback
forall a.
GObject a =>
(a -> FileChooserWidgetLocationPopupCallback)
-> C_FileChooserWidgetLocationPopupCallback
wrap_FileChooserWidgetLocationPopupCallback a -> FileChooserWidgetLocationPopupCallback
wrapped
FunPtr C_FileChooserWidgetLocationPopupCallback
wrapped'' <- C_FileChooserWidgetLocationPopupCallback
-> IO (FunPtr C_FileChooserWidgetLocationPopupCallback)
mk_FileChooserWidgetLocationPopupCallback C_FileChooserWidgetLocationPopupCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetLocationPopupCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"location-popup" FunPtr C_FileChooserWidgetLocationPopupCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetLocationPopupSignalInfo
instance SignalInfo FileChooserWidgetLocationPopupSignalInfo where
type HaskellCallbackType FileChooserWidgetLocationPopupSignalInfo = FileChooserWidgetLocationPopupCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetLocationPopupCallback cb
cb'' <- mk_FileChooserWidgetLocationPopupCallback cb'
connectSignalFunPtr obj "location-popup" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::location-popup"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:locationPopup"})
#endif
type =
IO ()
type =
Ptr FileChooserWidget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
:: C_FileChooserWidgetLocationPopupOnPasteCallback -> IO (FunPtr C_FileChooserWidgetLocationPopupOnPasteCallback)
wrap_FileChooserWidgetLocationPopupOnPasteCallback ::
GObject a => (a -> FileChooserWidgetLocationPopupOnPasteCallback) ->
C_FileChooserWidgetLocationPopupOnPasteCallback
a -> IO ()
gi'cb Ptr FileChooserWidget
gi'selfPtr Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> IO ()
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self)
onFileChooserWidgetLocationPopupOnPaste :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetLocationPopupOnPasteCallback) -> m SignalHandlerId
a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetLocationPopupOnPasteCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetLocationPopupOnPasteCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"location-popup-on-paste" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetLocationPopupOnPaste :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetLocationPopupOnPasteCallback) -> m SignalHandlerId
a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetLocationPopupOnPasteCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetLocationPopupOnPasteCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"location-popup-on-paste" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetLocationPopupOnPasteSignalInfo
instance SignalInfo FileChooserWidgetLocationPopupOnPasteSignalInfo where
type HaskellCallbackType FileChooserWidgetLocationPopupOnPasteSignalInfo = FileChooserWidgetLocationPopupOnPasteCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetLocationPopupOnPasteCallback cb
cb'' <- mk_FileChooserWidgetLocationPopupOnPasteCallback cb'
connectSignalFunPtr obj "location-popup-on-paste" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::location-popup-on-paste"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:locationPopupOnPaste"})
#endif
type =
IO ()
type =
Ptr FileChooserWidget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
:: C_FileChooserWidgetLocationTogglePopupCallback -> IO (FunPtr C_FileChooserWidgetLocationTogglePopupCallback)
wrap_FileChooserWidgetLocationTogglePopupCallback ::
GObject a => (a -> FileChooserWidgetLocationTogglePopupCallback) ->
C_FileChooserWidgetLocationTogglePopupCallback
a -> IO ()
gi'cb Ptr FileChooserWidget
gi'selfPtr Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> IO ()
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self)
onFileChooserWidgetLocationTogglePopup :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetLocationTogglePopupCallback) -> m SignalHandlerId
a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetLocationTogglePopupCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetLocationTogglePopupCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"location-toggle-popup" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetLocationTogglePopup :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetLocationTogglePopupCallback) -> m SignalHandlerId
a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetLocationTogglePopupCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetLocationTogglePopupCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"location-toggle-popup" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetLocationTogglePopupSignalInfo
instance SignalInfo FileChooserWidgetLocationTogglePopupSignalInfo where
type HaskellCallbackType FileChooserWidgetLocationTogglePopupSignalInfo = FileChooserWidgetLocationTogglePopupCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetLocationTogglePopupCallback cb
cb'' <- mk_FileChooserWidgetLocationTogglePopupCallback cb'
connectSignalFunPtr obj "location-toggle-popup" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::location-toggle-popup"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:locationTogglePopup"})
#endif
type FileChooserWidgetPlacesShortcutCallback =
IO ()
type C_FileChooserWidgetPlacesShortcutCallback =
Ptr FileChooserWidget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileChooserWidgetPlacesShortcutCallback :: C_FileChooserWidgetPlacesShortcutCallback -> IO (FunPtr C_FileChooserWidgetPlacesShortcutCallback)
wrap_FileChooserWidgetPlacesShortcutCallback ::
GObject a => (a -> FileChooserWidgetPlacesShortcutCallback) ->
C_FileChooserWidgetPlacesShortcutCallback
wrap_FileChooserWidgetPlacesShortcutCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetPlacesShortcutCallback a -> IO ()
gi'cb Ptr FileChooserWidget
gi'selfPtr Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> IO ()
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self)
onFileChooserWidgetPlacesShortcut :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetPlacesShortcutCallback) -> m SignalHandlerId
onFileChooserWidgetPlacesShortcut :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onFileChooserWidgetPlacesShortcut a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetPlacesShortcutCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetPlacesShortcutCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"places-shortcut" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetPlacesShortcut :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetPlacesShortcutCallback) -> m SignalHandlerId
afterFileChooserWidgetPlacesShortcut :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterFileChooserWidgetPlacesShortcut a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetPlacesShortcutCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetPlacesShortcutCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"places-shortcut" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetPlacesShortcutSignalInfo
instance SignalInfo FileChooserWidgetPlacesShortcutSignalInfo where
type HaskellCallbackType FileChooserWidgetPlacesShortcutSignalInfo = FileChooserWidgetPlacesShortcutCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetPlacesShortcutCallback cb
cb'' <- mk_FileChooserWidgetPlacesShortcutCallback cb'
connectSignalFunPtr obj "places-shortcut" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::places-shortcut"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:placesShortcut"})
#endif
type FileChooserWidgetQuickBookmarkCallback =
Int32
-> IO ()
type C_FileChooserWidgetQuickBookmarkCallback =
Ptr FileChooserWidget ->
Int32 ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileChooserWidgetQuickBookmarkCallback :: C_FileChooserWidgetQuickBookmarkCallback -> IO (FunPtr C_FileChooserWidgetQuickBookmarkCallback)
wrap_FileChooserWidgetQuickBookmarkCallback ::
GObject a => (a -> FileChooserWidgetQuickBookmarkCallback) ->
C_FileChooserWidgetQuickBookmarkCallback
wrap_FileChooserWidgetQuickBookmarkCallback :: forall a.
GObject a =>
(a -> FileChooserWidgetQuickBookmarkCallback)
-> C_FileChooserWidgetQuickBookmarkCallback
wrap_FileChooserWidgetQuickBookmarkCallback a -> FileChooserWidgetQuickBookmarkCallback
gi'cb Ptr FileChooserWidget
gi'selfPtr Int32
bookmarkIndex Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> FileChooserWidgetQuickBookmarkCallback
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self) Int32
bookmarkIndex
onFileChooserWidgetQuickBookmark :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetQuickBookmarkCallback) -> m SignalHandlerId
onFileChooserWidgetQuickBookmark :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a
-> ((?self::a) => FileChooserWidgetQuickBookmarkCallback)
-> m SignalHandlerId
onFileChooserWidgetQuickBookmark a
obj (?self::a) => FileChooserWidgetQuickBookmarkCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> FileChooserWidgetQuickBookmarkCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => FileChooserWidgetQuickBookmarkCallback
FileChooserWidgetQuickBookmarkCallback
cb
let wrapped' :: C_FileChooserWidgetQuickBookmarkCallback
wrapped' = (a -> FileChooserWidgetQuickBookmarkCallback)
-> C_FileChooserWidgetQuickBookmarkCallback
forall a.
GObject a =>
(a -> FileChooserWidgetQuickBookmarkCallback)
-> C_FileChooserWidgetQuickBookmarkCallback
wrap_FileChooserWidgetQuickBookmarkCallback a -> FileChooserWidgetQuickBookmarkCallback
wrapped
FunPtr C_FileChooserWidgetQuickBookmarkCallback
wrapped'' <- C_FileChooserWidgetQuickBookmarkCallback
-> IO (FunPtr C_FileChooserWidgetQuickBookmarkCallback)
mk_FileChooserWidgetQuickBookmarkCallback C_FileChooserWidgetQuickBookmarkCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetQuickBookmarkCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"quick-bookmark" FunPtr C_FileChooserWidgetQuickBookmarkCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetQuickBookmark :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetQuickBookmarkCallback) -> m SignalHandlerId
afterFileChooserWidgetQuickBookmark :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a
-> ((?self::a) => FileChooserWidgetQuickBookmarkCallback)
-> m SignalHandlerId
afterFileChooserWidgetQuickBookmark a
obj (?self::a) => FileChooserWidgetQuickBookmarkCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> FileChooserWidgetQuickBookmarkCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => FileChooserWidgetQuickBookmarkCallback
FileChooserWidgetQuickBookmarkCallback
cb
let wrapped' :: C_FileChooserWidgetQuickBookmarkCallback
wrapped' = (a -> FileChooserWidgetQuickBookmarkCallback)
-> C_FileChooserWidgetQuickBookmarkCallback
forall a.
GObject a =>
(a -> FileChooserWidgetQuickBookmarkCallback)
-> C_FileChooserWidgetQuickBookmarkCallback
wrap_FileChooserWidgetQuickBookmarkCallback a -> FileChooserWidgetQuickBookmarkCallback
wrapped
FunPtr C_FileChooserWidgetQuickBookmarkCallback
wrapped'' <- C_FileChooserWidgetQuickBookmarkCallback
-> IO (FunPtr C_FileChooserWidgetQuickBookmarkCallback)
mk_FileChooserWidgetQuickBookmarkCallback C_FileChooserWidgetQuickBookmarkCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetQuickBookmarkCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"quick-bookmark" FunPtr C_FileChooserWidgetQuickBookmarkCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetQuickBookmarkSignalInfo
instance SignalInfo FileChooserWidgetQuickBookmarkSignalInfo where
type HaskellCallbackType FileChooserWidgetQuickBookmarkSignalInfo = FileChooserWidgetQuickBookmarkCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetQuickBookmarkCallback cb
cb'' <- mk_FileChooserWidgetQuickBookmarkCallback cb'
connectSignalFunPtr obj "quick-bookmark" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::quick-bookmark"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:quickBookmark"})
#endif
type FileChooserWidgetRecentShortcutCallback =
IO ()
type C_FileChooserWidgetRecentShortcutCallback =
Ptr FileChooserWidget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileChooserWidgetRecentShortcutCallback :: C_FileChooserWidgetRecentShortcutCallback -> IO (FunPtr C_FileChooserWidgetRecentShortcutCallback)
wrap_FileChooserWidgetRecentShortcutCallback ::
GObject a => (a -> FileChooserWidgetRecentShortcutCallback) ->
C_FileChooserWidgetRecentShortcutCallback
wrap_FileChooserWidgetRecentShortcutCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetRecentShortcutCallback a -> IO ()
gi'cb Ptr FileChooserWidget
gi'selfPtr Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> IO ()
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self)
onFileChooserWidgetRecentShortcut :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetRecentShortcutCallback) -> m SignalHandlerId
onFileChooserWidgetRecentShortcut :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onFileChooserWidgetRecentShortcut a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetRecentShortcutCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetRecentShortcutCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"recent-shortcut" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetRecentShortcut :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetRecentShortcutCallback) -> m SignalHandlerId
afterFileChooserWidgetRecentShortcut :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterFileChooserWidgetRecentShortcut a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetRecentShortcutCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetRecentShortcutCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"recent-shortcut" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetRecentShortcutSignalInfo
instance SignalInfo FileChooserWidgetRecentShortcutSignalInfo where
type HaskellCallbackType FileChooserWidgetRecentShortcutSignalInfo = FileChooserWidgetRecentShortcutCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetRecentShortcutCallback cb
cb'' <- mk_FileChooserWidgetRecentShortcutCallback cb'
connectSignalFunPtr obj "recent-shortcut" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::recent-shortcut"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:recentShortcut"})
#endif
type FileChooserWidgetSearchShortcutCallback =
IO ()
type C_FileChooserWidgetSearchShortcutCallback =
Ptr FileChooserWidget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileChooserWidgetSearchShortcutCallback :: C_FileChooserWidgetSearchShortcutCallback -> IO (FunPtr C_FileChooserWidgetSearchShortcutCallback)
wrap_FileChooserWidgetSearchShortcutCallback ::
GObject a => (a -> FileChooserWidgetSearchShortcutCallback) ->
C_FileChooserWidgetSearchShortcutCallback
wrap_FileChooserWidgetSearchShortcutCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetSearchShortcutCallback a -> IO ()
gi'cb Ptr FileChooserWidget
gi'selfPtr Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> IO ()
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self)
onFileChooserWidgetSearchShortcut :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetSearchShortcutCallback) -> m SignalHandlerId
onFileChooserWidgetSearchShortcut :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onFileChooserWidgetSearchShortcut a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetSearchShortcutCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetSearchShortcutCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"search-shortcut" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetSearchShortcut :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetSearchShortcutCallback) -> m SignalHandlerId
afterFileChooserWidgetSearchShortcut :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterFileChooserWidgetSearchShortcut a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetSearchShortcutCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetSearchShortcutCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"search-shortcut" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetSearchShortcutSignalInfo
instance SignalInfo FileChooserWidgetSearchShortcutSignalInfo where
type HaskellCallbackType FileChooserWidgetSearchShortcutSignalInfo = FileChooserWidgetSearchShortcutCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetSearchShortcutCallback cb
cb'' <- mk_FileChooserWidgetSearchShortcutCallback cb'
connectSignalFunPtr obj "search-shortcut" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::search-shortcut"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:searchShortcut"})
#endif
type FileChooserWidgetShowHiddenCallback =
IO ()
type C_FileChooserWidgetShowHiddenCallback =
Ptr FileChooserWidget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileChooserWidgetShowHiddenCallback :: C_FileChooserWidgetShowHiddenCallback -> IO (FunPtr C_FileChooserWidgetShowHiddenCallback)
wrap_FileChooserWidgetShowHiddenCallback ::
GObject a => (a -> FileChooserWidgetShowHiddenCallback) ->
C_FileChooserWidgetShowHiddenCallback
wrap_FileChooserWidgetShowHiddenCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetShowHiddenCallback a -> IO ()
gi'cb Ptr FileChooserWidget
gi'selfPtr Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> IO ()
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self)
onFileChooserWidgetShowHidden :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetShowHiddenCallback) -> m SignalHandlerId
onFileChooserWidgetShowHidden :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onFileChooserWidgetShowHidden a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetShowHiddenCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetShowHiddenCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"show-hidden" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetShowHidden :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetShowHiddenCallback) -> m SignalHandlerId
afterFileChooserWidgetShowHidden :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterFileChooserWidgetShowHidden a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetShowHiddenCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetShowHiddenCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"show-hidden" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetShowHiddenSignalInfo
instance SignalInfo FileChooserWidgetShowHiddenSignalInfo where
type HaskellCallbackType FileChooserWidgetShowHiddenSignalInfo = FileChooserWidgetShowHiddenCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetShowHiddenCallback cb
cb'' <- mk_FileChooserWidgetShowHiddenCallback cb'
connectSignalFunPtr obj "show-hidden" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::show-hidden"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:showHidden"})
#endif
type FileChooserWidgetUpFolderCallback =
IO ()
type C_FileChooserWidgetUpFolderCallback =
Ptr FileChooserWidget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileChooserWidgetUpFolderCallback :: C_FileChooserWidgetUpFolderCallback -> IO (FunPtr C_FileChooserWidgetUpFolderCallback)
wrap_FileChooserWidgetUpFolderCallback ::
GObject a => (a -> FileChooserWidgetUpFolderCallback) ->
C_FileChooserWidgetUpFolderCallback
wrap_FileChooserWidgetUpFolderCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetUpFolderCallback a -> IO ()
gi'cb Ptr FileChooserWidget
gi'selfPtr Ptr ()
_ = do
Ptr FileChooserWidget -> (FileChooserWidget -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr FileChooserWidget
gi'selfPtr ((FileChooserWidget -> IO ()) -> IO ())
-> (FileChooserWidget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FileChooserWidget
gi'self -> a -> IO ()
gi'cb (FileChooserWidget -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FileChooserWidget
gi'self)
onFileChooserWidgetUpFolder :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetUpFolderCallback) -> m SignalHandlerId
onFileChooserWidgetUpFolder :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onFileChooserWidgetUpFolder a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetUpFolderCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetUpFolderCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"up-folder" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserWidgetUpFolder :: (IsFileChooserWidget a, MonadIO m) => a -> ((?self :: a) => FileChooserWidgetUpFolderCallback) -> m SignalHandlerId
afterFileChooserWidgetUpFolder :: forall a (m :: * -> *).
(IsFileChooserWidget a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterFileChooserWidgetUpFolder a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_FileChooserWidgetDesktopFolderCallback
wrapped' = (a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
forall a.
GObject a =>
(a -> IO ()) -> C_FileChooserWidgetDesktopFolderCallback
wrap_FileChooserWidgetUpFolderCallback a -> IO ()
wrapped
FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' <- C_FileChooserWidgetDesktopFolderCallback
-> IO (FunPtr C_FileChooserWidgetDesktopFolderCallback)
mk_FileChooserWidgetUpFolderCallback C_FileChooserWidgetDesktopFolderCallback
wrapped'
a
-> Text
-> FunPtr C_FileChooserWidgetDesktopFolderCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"up-folder" FunPtr C_FileChooserWidgetDesktopFolderCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetUpFolderSignalInfo
instance SignalInfo FileChooserWidgetUpFolderSignalInfo where
type HaskellCallbackType FileChooserWidgetUpFolderSignalInfo = FileChooserWidgetUpFolderCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserWidgetUpFolderCallback cb
cb'' <- mk_FileChooserWidgetUpFolderCallback cb'
connectSignalFunPtr obj "up-folder" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget::up-folder"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:signal:upFolder"})
#endif
getFileChooserWidgetSearchMode :: (MonadIO m, IsFileChooserWidget o) => o -> m Bool
getFileChooserWidgetSearchMode :: forall (m :: * -> *) o.
(MonadIO m, IsFileChooserWidget o) =>
o -> m Bool
getFileChooserWidgetSearchMode o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"search-mode"
setFileChooserWidgetSearchMode :: (MonadIO m, IsFileChooserWidget o) => o -> Bool -> m ()
setFileChooserWidgetSearchMode :: forall (m :: * -> *) o.
(MonadIO m, IsFileChooserWidget o) =>
o -> Bool -> m ()
setFileChooserWidgetSearchMode o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"search-mode" Bool
val
constructFileChooserWidgetSearchMode :: (IsFileChooserWidget o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructFileChooserWidgetSearchMode :: forall o (m :: * -> *).
(IsFileChooserWidget o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructFileChooserWidgetSearchMode Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"search-mode" Bool
val
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetSearchModePropertyInfo
instance AttrInfo FileChooserWidgetSearchModePropertyInfo where
type AttrAllowedOps FileChooserWidgetSearchModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint FileChooserWidgetSearchModePropertyInfo = IsFileChooserWidget
type AttrSetTypeConstraint FileChooserWidgetSearchModePropertyInfo = (~) Bool
type AttrTransferTypeConstraint FileChooserWidgetSearchModePropertyInfo = (~) Bool
type AttrTransferType FileChooserWidgetSearchModePropertyInfo = Bool
type AttrGetType FileChooserWidgetSearchModePropertyInfo = Bool
type AttrLabel FileChooserWidgetSearchModePropertyInfo = "search-mode"
type AttrOrigin FileChooserWidgetSearchModePropertyInfo = FileChooserWidget
attrGet = getFileChooserWidgetSearchMode
attrSet = setFileChooserWidgetSearchMode
attrTransfer _ v = do
return v
attrConstruct = constructFileChooserWidgetSearchMode
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget.searchMode"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:attr:searchMode"
})
#endif
getFileChooserWidgetSubtitle :: (MonadIO m, IsFileChooserWidget o) => o -> m (Maybe T.Text)
getFileChooserWidgetSubtitle :: forall (m :: * -> *) o.
(MonadIO m, IsFileChooserWidget o) =>
o -> m (Maybe Text)
getFileChooserWidgetSubtitle o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"subtitle"
#if defined(ENABLE_OVERLOADING)
data FileChooserWidgetSubtitlePropertyInfo
instance AttrInfo FileChooserWidgetSubtitlePropertyInfo where
type AttrAllowedOps FileChooserWidgetSubtitlePropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint FileChooserWidgetSubtitlePropertyInfo = IsFileChooserWidget
type AttrSetTypeConstraint FileChooserWidgetSubtitlePropertyInfo = (~) ()
type AttrTransferTypeConstraint FileChooserWidgetSubtitlePropertyInfo = (~) ()
type AttrTransferType FileChooserWidgetSubtitlePropertyInfo = ()
type AttrGetType FileChooserWidgetSubtitlePropertyInfo = (Maybe T.Text)
type AttrLabel FileChooserWidgetSubtitlePropertyInfo = "subtitle"
type AttrOrigin FileChooserWidgetSubtitlePropertyInfo = FileChooserWidget
attrGet = getFileChooserWidgetSubtitle
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.FileChooserWidget.subtitle"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-FileChooserWidget.html#g:attr:subtitle"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FileChooserWidget
type instance O.AttributeList FileChooserWidget = FileChooserWidgetAttributeList
type FileChooserWidgetAttributeList = ('[ '("action", Gtk.FileChooser.FileChooserActionPropertyInfo), '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("baselinePosition", Gtk.Box.BoxBaselinePositionPropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("createFolders", Gtk.FileChooser.FileChooserCreateFoldersPropertyInfo), '("doOverwriteConfirmation", Gtk.FileChooser.FileChooserDoOverwriteConfirmationPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("extraWidget", Gtk.FileChooser.FileChooserExtraWidgetPropertyInfo), '("filter", Gtk.FileChooser.FileChooserFilterPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("homogeneous", Gtk.Box.BoxHomogeneousPropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("localOnly", Gtk.FileChooser.FileChooserLocalOnlyPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("orientation", Gtk.Orientable.OrientableOrientationPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("previewWidget", Gtk.FileChooser.FileChooserPreviewWidgetPropertyInfo), '("previewWidgetActive", Gtk.FileChooser.FileChooserPreviewWidgetActivePropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("searchMode", FileChooserWidgetSearchModePropertyInfo), '("selectMultiple", Gtk.FileChooser.FileChooserSelectMultiplePropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("showHidden", Gtk.FileChooser.FileChooserShowHiddenPropertyInfo), '("spacing", Gtk.Box.BoxSpacingPropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("subtitle", FileChooserWidgetSubtitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("usePreviewLabel", Gtk.FileChooser.FileChooserUsePreviewLabelPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
fileChooserWidgetSearchMode :: AttrLabelProxy "searchMode"
fileChooserWidgetSearchMode = AttrLabelProxy
fileChooserWidgetSubtitle :: AttrLabelProxy "subtitle"
fileChooserWidgetSubtitle = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FileChooserWidget = FileChooserWidgetSignalList
type FileChooserWidgetSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("confirmOverwrite", Gtk.FileChooser.FileChooserConfirmOverwriteSignalInfo), '("currentFolderChanged", Gtk.FileChooser.FileChooserCurrentFolderChangedSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("desktopFolder", FileChooserWidgetDesktopFolderSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("downFolder", FileChooserWidgetDownFolderSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("fileActivated", Gtk.FileChooser.FileChooserFileActivatedSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("homeFolder", FileChooserWidgetHomeFolderSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("locationPopup", FileChooserWidgetLocationPopupSignalInfo), '("locationPopupOnPaste", FileChooserWidgetLocationPopupOnPasteSignalInfo), '("locationTogglePopup", FileChooserWidgetLocationTogglePopupSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("placesShortcut", FileChooserWidgetPlacesShortcutSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("quickBookmark", FileChooserWidgetQuickBookmarkSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("recentShortcut", FileChooserWidgetRecentShortcutSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("searchShortcut", FileChooserWidgetSearchShortcutSignalInfo), '("selectionChanged", Gtk.FileChooser.FileChooserSelectionChangedSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("setFocusChild", Gtk.Container.ContainerSetFocusChildSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("showHidden", FileChooserWidgetShowHiddenSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("upFolder", FileChooserWidgetUpFolderSignalInfo), '("updatePreview", Gtk.FileChooser.FileChooserUpdatePreviewSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_file_chooser_widget_new" gtk_file_chooser_widget_new ::
CUInt ->
IO (Ptr FileChooserWidget)
fileChooserWidgetNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Gtk.Enums.FileChooserAction
-> m FileChooserWidget
fileChooserWidgetNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FileChooserAction -> m FileChooserWidget
fileChooserWidgetNew FileChooserAction
action = IO FileChooserWidget -> m FileChooserWidget
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileChooserWidget -> m FileChooserWidget)
-> IO FileChooserWidget -> m FileChooserWidget
forall a b. (a -> b) -> a -> b
$ do
let action' :: CUInt
action' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (FileChooserAction -> Int) -> FileChooserAction -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileChooserAction -> Int
forall a. Enum a => a -> Int
fromEnum) FileChooserAction
action
Ptr FileChooserWidget
result <- CUInt -> IO (Ptr FileChooserWidget)
gtk_file_chooser_widget_new CUInt
action'
Text -> Ptr FileChooserWidget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fileChooserWidgetNew" Ptr FileChooserWidget
result
FileChooserWidget
result' <- ((ManagedPtr FileChooserWidget -> FileChooserWidget)
-> Ptr FileChooserWidget -> IO FileChooserWidget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FileChooserWidget -> FileChooserWidget
FileChooserWidget) Ptr FileChooserWidget
result
FileChooserWidget -> IO FileChooserWidget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FileChooserWidget
result'
#if defined(ENABLE_OVERLOADING)
#endif