{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.FileChooserButton
(
FileChooserButton(..) ,
IsFileChooserButton ,
toFileChooserButton ,
#if defined(ENABLE_OVERLOADING)
ResolveFileChooserButtonMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
FileChooserButtonGetFocusOnClickMethodInfo,
#endif
fileChooserButtonGetFocusOnClick ,
#if defined(ENABLE_OVERLOADING)
FileChooserButtonGetTitleMethodInfo ,
#endif
fileChooserButtonGetTitle ,
#if defined(ENABLE_OVERLOADING)
FileChooserButtonGetWidthCharsMethodInfo,
#endif
fileChooserButtonGetWidthChars ,
fileChooserButtonNew ,
fileChooserButtonNewWithDialog ,
#if defined(ENABLE_OVERLOADING)
FileChooserButtonSetFocusOnClickMethodInfo,
#endif
fileChooserButtonSetFocusOnClick ,
#if defined(ENABLE_OVERLOADING)
FileChooserButtonSetTitleMethodInfo ,
#endif
fileChooserButtonSetTitle ,
#if defined(ENABLE_OVERLOADING)
FileChooserButtonSetWidthCharsMethodInfo,
#endif
fileChooserButtonSetWidthChars ,
#if defined(ENABLE_OVERLOADING)
FileChooserButtonDialogPropertyInfo ,
#endif
constructFileChooserButtonDialog ,
#if defined(ENABLE_OVERLOADING)
fileChooserButtonDialog ,
#endif
#if defined(ENABLE_OVERLOADING)
FileChooserButtonTitlePropertyInfo ,
#endif
constructFileChooserButtonTitle ,
#if defined(ENABLE_OVERLOADING)
fileChooserButtonTitle ,
#endif
getFileChooserButtonTitle ,
setFileChooserButtonTitle ,
#if defined(ENABLE_OVERLOADING)
FileChooserButtonWidthCharsPropertyInfo ,
#endif
constructFileChooserButtonWidthChars ,
#if defined(ENABLE_OVERLOADING)
fileChooserButtonWidthChars ,
#endif
getFileChooserButtonWidthChars ,
setFileChooserButtonWidthChars ,
C_FileChooserButtonFileSetCallback ,
FileChooserButtonFileSetCallback ,
#if defined(ENABLE_OVERLOADING)
FileChooserButtonFileSetSignalInfo ,
#endif
afterFileChooserButtonFileSet ,
genClosure_FileChooserButtonFileSet ,
mk_FileChooserButtonFileSetCallback ,
noFileChooserButtonFileSetCallback ,
onFileChooserButtonFileSet ,
wrap_FileChooserButtonFileSetCallback ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.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.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.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.Dialog as Gtk.Dialog
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype FileChooserButton = FileChooserButton (SP.ManagedPtr FileChooserButton)
deriving (FileChooserButton -> FileChooserButton -> Bool
(FileChooserButton -> FileChooserButton -> Bool)
-> (FileChooserButton -> FileChooserButton -> Bool)
-> Eq FileChooserButton
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileChooserButton -> FileChooserButton -> Bool
$c/= :: FileChooserButton -> FileChooserButton -> Bool
== :: FileChooserButton -> FileChooserButton -> Bool
$c== :: FileChooserButton -> FileChooserButton -> Bool
Eq)
instance SP.ManagedPtrNewtype FileChooserButton where
toManagedPtr :: FileChooserButton -> ManagedPtr FileChooserButton
toManagedPtr (FileChooserButton ManagedPtr FileChooserButton
p) = ManagedPtr FileChooserButton
p
foreign import ccall "gtk_file_chooser_button_get_type"
c_gtk_file_chooser_button_get_type :: IO B.Types.GType
instance B.Types.TypedObject FileChooserButton where
glibType :: IO GType
glibType = IO GType
c_gtk_file_chooser_button_get_type
instance B.Types.GObject FileChooserButton
instance B.GValue.IsGValue FileChooserButton where
toGValue :: FileChooserButton -> IO GValue
toGValue FileChooserButton
o = do
GType
gtype <- IO GType
c_gtk_file_chooser_button_get_type
FileChooserButton
-> (Ptr FileChooserButton -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FileChooserButton
o (GType
-> (GValue -> Ptr FileChooserButton -> IO ())
-> Ptr FileChooserButton
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr FileChooserButton -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO FileChooserButton
fromGValue GValue
gv = do
Ptr FileChooserButton
ptr <- GValue -> IO (Ptr FileChooserButton)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr FileChooserButton)
(ManagedPtr FileChooserButton -> FileChooserButton)
-> Ptr FileChooserButton -> IO FileChooserButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr FileChooserButton -> FileChooserButton
FileChooserButton Ptr FileChooserButton
ptr
class (SP.GObject o, O.IsDescendantOf FileChooserButton o) => IsFileChooserButton o
instance (SP.GObject o, O.IsDescendantOf FileChooserButton o) => IsFileChooserButton o
instance O.HasParentTypes FileChooserButton
type instance O.ParentTypes FileChooserButton = '[Gtk.Box.Box, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, Gtk.FileChooser.FileChooser, Gtk.Orientable.Orientable]
toFileChooserButton :: (MonadIO m, IsFileChooserButton o) => o -> m FileChooserButton
toFileChooserButton :: o -> m FileChooserButton
toFileChooserButton = IO FileChooserButton -> m FileChooserButton
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileChooserButton -> m FileChooserButton)
-> (o -> IO FileChooserButton) -> o -> m FileChooserButton
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr FileChooserButton -> FileChooserButton)
-> o -> IO FileChooserButton
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr FileChooserButton -> FileChooserButton
FileChooserButton
#if defined(ENABLE_OVERLOADING)
type family ResolveFileChooserButtonMethod (t :: Symbol) (o :: *) :: * where
ResolveFileChooserButtonMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveFileChooserButtonMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolveFileChooserButtonMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveFileChooserButtonMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveFileChooserButtonMethod "addChoice" o = Gtk.FileChooser.FileChooserAddChoiceMethodInfo
ResolveFileChooserButtonMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveFileChooserButtonMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveFileChooserButtonMethod "addFilter" o = Gtk.FileChooser.FileChooserAddFilterMethodInfo
ResolveFileChooserButtonMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveFileChooserButtonMethod "addShortcutFolder" o = Gtk.FileChooser.FileChooserAddShortcutFolderMethodInfo
ResolveFileChooserButtonMethod "addShortcutFolderUri" o = Gtk.FileChooser.FileChooserAddShortcutFolderUriMethodInfo
ResolveFileChooserButtonMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveFileChooserButtonMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveFileChooserButtonMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveFileChooserButtonMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveFileChooserButtonMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolveFileChooserButtonMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveFileChooserButtonMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolveFileChooserButtonMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolveFileChooserButtonMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolveFileChooserButtonMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolveFileChooserButtonMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolveFileChooserButtonMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveFileChooserButtonMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveFileChooserButtonMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveFileChooserButtonMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveFileChooserButtonMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveFileChooserButtonMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveFileChooserButtonMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveFileChooserButtonMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveFileChooserButtonMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveFileChooserButtonMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveFileChooserButtonMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveFileChooserButtonMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveFileChooserButtonMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveFileChooserButtonMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveFileChooserButtonMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveFileChooserButtonMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveFileChooserButtonMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveFileChooserButtonMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveFileChooserButtonMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveFileChooserButtonMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveFileChooserButtonMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveFileChooserButtonMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveFileChooserButtonMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveFileChooserButtonMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveFileChooserButtonMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveFileChooserButtonMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveFileChooserButtonMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveFileChooserButtonMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveFileChooserButtonMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveFileChooserButtonMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveFileChooserButtonMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveFileChooserButtonMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveFileChooserButtonMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveFileChooserButtonMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveFileChooserButtonMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveFileChooserButtonMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveFileChooserButtonMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveFileChooserButtonMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveFileChooserButtonMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveFileChooserButtonMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveFileChooserButtonMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveFileChooserButtonMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveFileChooserButtonMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveFileChooserButtonMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolveFileChooserButtonMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveFileChooserButtonMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolveFileChooserButtonMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveFileChooserButtonMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveFileChooserButtonMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveFileChooserButtonMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveFileChooserButtonMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveFileChooserButtonMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveFileChooserButtonMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveFileChooserButtonMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveFileChooserButtonMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveFileChooserButtonMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveFileChooserButtonMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveFileChooserButtonMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveFileChooserButtonMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveFileChooserButtonMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveFileChooserButtonMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveFileChooserButtonMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveFileChooserButtonMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveFileChooserButtonMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveFileChooserButtonMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveFileChooserButtonMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveFileChooserButtonMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveFileChooserButtonMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveFileChooserButtonMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveFileChooserButtonMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveFileChooserButtonMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveFileChooserButtonMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveFileChooserButtonMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveFileChooserButtonMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveFileChooserButtonMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveFileChooserButtonMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveFileChooserButtonMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveFileChooserButtonMethod "listFilters" o = Gtk.FileChooser.FileChooserListFiltersMethodInfo
ResolveFileChooserButtonMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveFileChooserButtonMethod "listShortcutFolderUris" o = Gtk.FileChooser.FileChooserListShortcutFolderUrisMethodInfo
ResolveFileChooserButtonMethod "listShortcutFolders" o = Gtk.FileChooser.FileChooserListShortcutFoldersMethodInfo
ResolveFileChooserButtonMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveFileChooserButtonMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveFileChooserButtonMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveFileChooserButtonMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveFileChooserButtonMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveFileChooserButtonMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveFileChooserButtonMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveFileChooserButtonMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveFileChooserButtonMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveFileChooserButtonMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveFileChooserButtonMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveFileChooserButtonMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveFileChooserButtonMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveFileChooserButtonMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveFileChooserButtonMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveFileChooserButtonMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveFileChooserButtonMethod "packEnd" o = Gtk.Box.BoxPackEndMethodInfo
ResolveFileChooserButtonMethod "packStart" o = Gtk.Box.BoxPackStartMethodInfo
ResolveFileChooserButtonMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveFileChooserButtonMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveFileChooserButtonMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolveFileChooserButtonMethod "queryChildPacking" o = Gtk.Box.BoxQueryChildPackingMethodInfo
ResolveFileChooserButtonMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveFileChooserButtonMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveFileChooserButtonMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveFileChooserButtonMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveFileChooserButtonMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveFileChooserButtonMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveFileChooserButtonMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveFileChooserButtonMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveFileChooserButtonMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveFileChooserButtonMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveFileChooserButtonMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveFileChooserButtonMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveFileChooserButtonMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolveFileChooserButtonMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveFileChooserButtonMethod "removeChoice" o = Gtk.FileChooser.FileChooserRemoveChoiceMethodInfo
ResolveFileChooserButtonMethod "removeFilter" o = Gtk.FileChooser.FileChooserRemoveFilterMethodInfo
ResolveFileChooserButtonMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveFileChooserButtonMethod "removeShortcutFolder" o = Gtk.FileChooser.FileChooserRemoveShortcutFolderMethodInfo
ResolveFileChooserButtonMethod "removeShortcutFolderUri" o = Gtk.FileChooser.FileChooserRemoveShortcutFolderUriMethodInfo
ResolveFileChooserButtonMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveFileChooserButtonMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveFileChooserButtonMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveFileChooserButtonMethod "reorderChild" o = Gtk.Box.BoxReorderChildMethodInfo
ResolveFileChooserButtonMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveFileChooserButtonMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveFileChooserButtonMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveFileChooserButtonMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolveFileChooserButtonMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveFileChooserButtonMethod "selectAll" o = Gtk.FileChooser.FileChooserSelectAllMethodInfo
ResolveFileChooserButtonMethod "selectFile" o = Gtk.FileChooser.FileChooserSelectFileMethodInfo
ResolveFileChooserButtonMethod "selectFilename" o = Gtk.FileChooser.FileChooserSelectFilenameMethodInfo
ResolveFileChooserButtonMethod "selectUri" o = Gtk.FileChooser.FileChooserSelectUriMethodInfo
ResolveFileChooserButtonMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveFileChooserButtonMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveFileChooserButtonMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveFileChooserButtonMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveFileChooserButtonMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveFileChooserButtonMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveFileChooserButtonMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveFileChooserButtonMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveFileChooserButtonMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveFileChooserButtonMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveFileChooserButtonMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveFileChooserButtonMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveFileChooserButtonMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveFileChooserButtonMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveFileChooserButtonMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveFileChooserButtonMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveFileChooserButtonMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveFileChooserButtonMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveFileChooserButtonMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveFileChooserButtonMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveFileChooserButtonMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveFileChooserButtonMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveFileChooserButtonMethod "unselectAll" o = Gtk.FileChooser.FileChooserUnselectAllMethodInfo
ResolveFileChooserButtonMethod "unselectFile" o = Gtk.FileChooser.FileChooserUnselectFileMethodInfo
ResolveFileChooserButtonMethod "unselectFilename" o = Gtk.FileChooser.FileChooserUnselectFilenameMethodInfo
ResolveFileChooserButtonMethod "unselectUri" o = Gtk.FileChooser.FileChooserUnselectUriMethodInfo
ResolveFileChooserButtonMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolveFileChooserButtonMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveFileChooserButtonMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveFileChooserButtonMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveFileChooserButtonMethod "getAction" o = Gtk.FileChooser.FileChooserGetActionMethodInfo
ResolveFileChooserButtonMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveFileChooserButtonMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveFileChooserButtonMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveFileChooserButtonMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveFileChooserButtonMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveFileChooserButtonMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveFileChooserButtonMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveFileChooserButtonMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveFileChooserButtonMethod "getBaselinePosition" o = Gtk.Box.BoxGetBaselinePositionMethodInfo
ResolveFileChooserButtonMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolveFileChooserButtonMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveFileChooserButtonMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveFileChooserButtonMethod "getCenterWidget" o = Gtk.Box.BoxGetCenterWidgetMethodInfo
ResolveFileChooserButtonMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveFileChooserButtonMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveFileChooserButtonMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolveFileChooserButtonMethod "getChoice" o = Gtk.FileChooser.FileChooserGetChoiceMethodInfo
ResolveFileChooserButtonMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveFileChooserButtonMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveFileChooserButtonMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveFileChooserButtonMethod "getCreateFolders" o = Gtk.FileChooser.FileChooserGetCreateFoldersMethodInfo
ResolveFileChooserButtonMethod "getCurrentFolder" o = Gtk.FileChooser.FileChooserGetCurrentFolderMethodInfo
ResolveFileChooserButtonMethod "getCurrentFolderFile" o = Gtk.FileChooser.FileChooserGetCurrentFolderFileMethodInfo
ResolveFileChooserButtonMethod "getCurrentFolderUri" o = Gtk.FileChooser.FileChooserGetCurrentFolderUriMethodInfo
ResolveFileChooserButtonMethod "getCurrentName" o = Gtk.FileChooser.FileChooserGetCurrentNameMethodInfo
ResolveFileChooserButtonMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveFileChooserButtonMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveFileChooserButtonMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveFileChooserButtonMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveFileChooserButtonMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveFileChooserButtonMethod "getDoOverwriteConfirmation" o = Gtk.FileChooser.FileChooserGetDoOverwriteConfirmationMethodInfo
ResolveFileChooserButtonMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveFileChooserButtonMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveFileChooserButtonMethod "getExtraWidget" o = Gtk.FileChooser.FileChooserGetExtraWidgetMethodInfo
ResolveFileChooserButtonMethod "getFile" o = Gtk.FileChooser.FileChooserGetFileMethodInfo
ResolveFileChooserButtonMethod "getFilename" o = Gtk.FileChooser.FileChooserGetFilenameMethodInfo
ResolveFileChooserButtonMethod "getFilenames" o = Gtk.FileChooser.FileChooserGetFilenamesMethodInfo
ResolveFileChooserButtonMethod "getFiles" o = Gtk.FileChooser.FileChooserGetFilesMethodInfo
ResolveFileChooserButtonMethod "getFilter" o = Gtk.FileChooser.FileChooserGetFilterMethodInfo
ResolveFileChooserButtonMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolveFileChooserButtonMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolveFileChooserButtonMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolveFileChooserButtonMethod "getFocusOnClick" o = FileChooserButtonGetFocusOnClickMethodInfo
ResolveFileChooserButtonMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolveFileChooserButtonMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveFileChooserButtonMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveFileChooserButtonMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveFileChooserButtonMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveFileChooserButtonMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveFileChooserButtonMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveFileChooserButtonMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveFileChooserButtonMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveFileChooserButtonMethod "getHomogeneous" o = Gtk.Box.BoxGetHomogeneousMethodInfo
ResolveFileChooserButtonMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveFileChooserButtonMethod "getLocalOnly" o = Gtk.FileChooser.FileChooserGetLocalOnlyMethodInfo
ResolveFileChooserButtonMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveFileChooserButtonMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveFileChooserButtonMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveFileChooserButtonMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveFileChooserButtonMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveFileChooserButtonMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveFileChooserButtonMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveFileChooserButtonMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveFileChooserButtonMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveFileChooserButtonMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveFileChooserButtonMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveFileChooserButtonMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveFileChooserButtonMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
ResolveFileChooserButtonMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveFileChooserButtonMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveFileChooserButtonMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveFileChooserButtonMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveFileChooserButtonMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolveFileChooserButtonMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveFileChooserButtonMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveFileChooserButtonMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveFileChooserButtonMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveFileChooserButtonMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveFileChooserButtonMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveFileChooserButtonMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveFileChooserButtonMethod "getPreviewFile" o = Gtk.FileChooser.FileChooserGetPreviewFileMethodInfo
ResolveFileChooserButtonMethod "getPreviewFilename" o = Gtk.FileChooser.FileChooserGetPreviewFilenameMethodInfo
ResolveFileChooserButtonMethod "getPreviewUri" o = Gtk.FileChooser.FileChooserGetPreviewUriMethodInfo
ResolveFileChooserButtonMethod "getPreviewWidget" o = Gtk.FileChooser.FileChooserGetPreviewWidgetMethodInfo
ResolveFileChooserButtonMethod "getPreviewWidgetActive" o = Gtk.FileChooser.FileChooserGetPreviewWidgetActiveMethodInfo
ResolveFileChooserButtonMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveFileChooserButtonMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveFileChooserButtonMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveFileChooserButtonMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveFileChooserButtonMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveFileChooserButtonMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveFileChooserButtonMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolveFileChooserButtonMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveFileChooserButtonMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveFileChooserButtonMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveFileChooserButtonMethod "getSelectMultiple" o = Gtk.FileChooser.FileChooserGetSelectMultipleMethodInfo
ResolveFileChooserButtonMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveFileChooserButtonMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveFileChooserButtonMethod "getShowHidden" o = Gtk.FileChooser.FileChooserGetShowHiddenMethodInfo
ResolveFileChooserButtonMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveFileChooserButtonMethod "getSpacing" o = Gtk.Box.BoxGetSpacingMethodInfo
ResolveFileChooserButtonMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveFileChooserButtonMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveFileChooserButtonMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveFileChooserButtonMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveFileChooserButtonMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveFileChooserButtonMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveFileChooserButtonMethod "getTitle" o = FileChooserButtonGetTitleMethodInfo
ResolveFileChooserButtonMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveFileChooserButtonMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveFileChooserButtonMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveFileChooserButtonMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveFileChooserButtonMethod "getUri" o = Gtk.FileChooser.FileChooserGetUriMethodInfo
ResolveFileChooserButtonMethod "getUris" o = Gtk.FileChooser.FileChooserGetUrisMethodInfo
ResolveFileChooserButtonMethod "getUsePreviewLabel" o = Gtk.FileChooser.FileChooserGetUsePreviewLabelMethodInfo
ResolveFileChooserButtonMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveFileChooserButtonMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveFileChooserButtonMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveFileChooserButtonMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveFileChooserButtonMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveFileChooserButtonMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveFileChooserButtonMethod "getWidthChars" o = FileChooserButtonGetWidthCharsMethodInfo
ResolveFileChooserButtonMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveFileChooserButtonMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveFileChooserButtonMethod "setAction" o = Gtk.FileChooser.FileChooserSetActionMethodInfo
ResolveFileChooserButtonMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveFileChooserButtonMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveFileChooserButtonMethod "setBaselinePosition" o = Gtk.Box.BoxSetBaselinePositionMethodInfo
ResolveFileChooserButtonMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolveFileChooserButtonMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveFileChooserButtonMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveFileChooserButtonMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveFileChooserButtonMethod "setCenterWidget" o = Gtk.Box.BoxSetCenterWidgetMethodInfo
ResolveFileChooserButtonMethod "setChildPacking" o = Gtk.Box.BoxSetChildPackingMethodInfo
ResolveFileChooserButtonMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveFileChooserButtonMethod "setChoice" o = Gtk.FileChooser.FileChooserSetChoiceMethodInfo
ResolveFileChooserButtonMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveFileChooserButtonMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveFileChooserButtonMethod "setCreateFolders" o = Gtk.FileChooser.FileChooserSetCreateFoldersMethodInfo
ResolveFileChooserButtonMethod "setCurrentFolder" o = Gtk.FileChooser.FileChooserSetCurrentFolderMethodInfo
ResolveFileChooserButtonMethod "setCurrentFolderFile" o = Gtk.FileChooser.FileChooserSetCurrentFolderFileMethodInfo
ResolveFileChooserButtonMethod "setCurrentFolderUri" o = Gtk.FileChooser.FileChooserSetCurrentFolderUriMethodInfo
ResolveFileChooserButtonMethod "setCurrentName" o = Gtk.FileChooser.FileChooserSetCurrentNameMethodInfo
ResolveFileChooserButtonMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveFileChooserButtonMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveFileChooserButtonMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveFileChooserButtonMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveFileChooserButtonMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveFileChooserButtonMethod "setDoOverwriteConfirmation" o = Gtk.FileChooser.FileChooserSetDoOverwriteConfirmationMethodInfo
ResolveFileChooserButtonMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveFileChooserButtonMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveFileChooserButtonMethod "setExtraWidget" o = Gtk.FileChooser.FileChooserSetExtraWidgetMethodInfo
ResolveFileChooserButtonMethod "setFile" o = Gtk.FileChooser.FileChooserSetFileMethodInfo
ResolveFileChooserButtonMethod "setFilename" o = Gtk.FileChooser.FileChooserSetFilenameMethodInfo
ResolveFileChooserButtonMethod "setFilter" o = Gtk.FileChooser.FileChooserSetFilterMethodInfo
ResolveFileChooserButtonMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolveFileChooserButtonMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolveFileChooserButtonMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolveFileChooserButtonMethod "setFocusOnClick" o = FileChooserButtonSetFocusOnClickMethodInfo
ResolveFileChooserButtonMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolveFileChooserButtonMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveFileChooserButtonMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveFileChooserButtonMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveFileChooserButtonMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveFileChooserButtonMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveFileChooserButtonMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveFileChooserButtonMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveFileChooserButtonMethod "setHomogeneous" o = Gtk.Box.BoxSetHomogeneousMethodInfo
ResolveFileChooserButtonMethod "setLocalOnly" o = Gtk.FileChooser.FileChooserSetLocalOnlyMethodInfo
ResolveFileChooserButtonMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveFileChooserButtonMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveFileChooserButtonMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveFileChooserButtonMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveFileChooserButtonMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveFileChooserButtonMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveFileChooserButtonMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveFileChooserButtonMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveFileChooserButtonMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveFileChooserButtonMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveFileChooserButtonMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
ResolveFileChooserButtonMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveFileChooserButtonMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveFileChooserButtonMethod "setPreviewWidget" o = Gtk.FileChooser.FileChooserSetPreviewWidgetMethodInfo
ResolveFileChooserButtonMethod "setPreviewWidgetActive" o = Gtk.FileChooser.FileChooserSetPreviewWidgetActiveMethodInfo
ResolveFileChooserButtonMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveFileChooserButtonMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveFileChooserButtonMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolveFileChooserButtonMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveFileChooserButtonMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveFileChooserButtonMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolveFileChooserButtonMethod "setSelectMultiple" o = Gtk.FileChooser.FileChooserSetSelectMultipleMethodInfo
ResolveFileChooserButtonMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveFileChooserButtonMethod "setShowHidden" o = Gtk.FileChooser.FileChooserSetShowHiddenMethodInfo
ResolveFileChooserButtonMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveFileChooserButtonMethod "setSpacing" o = Gtk.Box.BoxSetSpacingMethodInfo
ResolveFileChooserButtonMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveFileChooserButtonMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveFileChooserButtonMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveFileChooserButtonMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveFileChooserButtonMethod "setTitle" o = FileChooserButtonSetTitleMethodInfo
ResolveFileChooserButtonMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveFileChooserButtonMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveFileChooserButtonMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveFileChooserButtonMethod "setUri" o = Gtk.FileChooser.FileChooserSetUriMethodInfo
ResolveFileChooserButtonMethod "setUsePreviewLabel" o = Gtk.FileChooser.FileChooserSetUsePreviewLabelMethodInfo
ResolveFileChooserButtonMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveFileChooserButtonMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveFileChooserButtonMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveFileChooserButtonMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveFileChooserButtonMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveFileChooserButtonMethod "setWidthChars" o = FileChooserButtonSetWidthCharsMethodInfo
ResolveFileChooserButtonMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveFileChooserButtonMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveFileChooserButtonMethod t FileChooserButton, O.MethodInfo info FileChooserButton p) => OL.IsLabel t (FileChooserButton -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
type FileChooserButtonFileSetCallback =
IO ()
noFileChooserButtonFileSetCallback :: Maybe FileChooserButtonFileSetCallback
noFileChooserButtonFileSetCallback :: Maybe (IO ())
noFileChooserButtonFileSetCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_FileChooserButtonFileSetCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FileChooserButtonFileSetCallback :: C_FileChooserButtonFileSetCallback -> IO (FunPtr C_FileChooserButtonFileSetCallback)
genClosure_FileChooserButtonFileSet :: MonadIO m => FileChooserButtonFileSetCallback -> m (GClosure C_FileChooserButtonFileSetCallback)
genClosure_FileChooserButtonFileSet :: IO () -> m (GClosure C_FileChooserButtonFileSetCallback)
genClosure_FileChooserButtonFileSet IO ()
cb = IO (GClosure C_FileChooserButtonFileSetCallback)
-> m (GClosure C_FileChooserButtonFileSetCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FileChooserButtonFileSetCallback)
-> m (GClosure C_FileChooserButtonFileSetCallback))
-> IO (GClosure C_FileChooserButtonFileSetCallback)
-> m (GClosure C_FileChooserButtonFileSetCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FileChooserButtonFileSetCallback
cb' = IO () -> C_FileChooserButtonFileSetCallback
wrap_FileChooserButtonFileSetCallback IO ()
cb
C_FileChooserButtonFileSetCallback
-> IO (FunPtr C_FileChooserButtonFileSetCallback)
mk_FileChooserButtonFileSetCallback C_FileChooserButtonFileSetCallback
cb' IO (FunPtr C_FileChooserButtonFileSetCallback)
-> (FunPtr C_FileChooserButtonFileSetCallback
-> IO (GClosure C_FileChooserButtonFileSetCallback))
-> IO (GClosure C_FileChooserButtonFileSetCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FileChooserButtonFileSetCallback
-> IO (GClosure C_FileChooserButtonFileSetCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_FileChooserButtonFileSetCallback ::
FileChooserButtonFileSetCallback ->
C_FileChooserButtonFileSetCallback
wrap_FileChooserButtonFileSetCallback :: IO () -> C_FileChooserButtonFileSetCallback
wrap_FileChooserButtonFileSetCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onFileChooserButtonFileSet :: (IsFileChooserButton a, MonadIO m) => a -> FileChooserButtonFileSetCallback -> m SignalHandlerId
onFileChooserButtonFileSet :: a -> IO () -> m SignalHandlerId
onFileChooserButtonFileSet a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FileChooserButtonFileSetCallback
cb' = IO () -> C_FileChooserButtonFileSetCallback
wrap_FileChooserButtonFileSetCallback IO ()
cb
FunPtr C_FileChooserButtonFileSetCallback
cb'' <- C_FileChooserButtonFileSetCallback
-> IO (FunPtr C_FileChooserButtonFileSetCallback)
mk_FileChooserButtonFileSetCallback C_FileChooserButtonFileSetCallback
cb'
a
-> Text
-> FunPtr C_FileChooserButtonFileSetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"file-set" FunPtr C_FileChooserButtonFileSetCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFileChooserButtonFileSet :: (IsFileChooserButton a, MonadIO m) => a -> FileChooserButtonFileSetCallback -> m SignalHandlerId
afterFileChooserButtonFileSet :: a -> IO () -> m SignalHandlerId
afterFileChooserButtonFileSet a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FileChooserButtonFileSetCallback
cb' = IO () -> C_FileChooserButtonFileSetCallback
wrap_FileChooserButtonFileSetCallback IO ()
cb
FunPtr C_FileChooserButtonFileSetCallback
cb'' <- C_FileChooserButtonFileSetCallback
-> IO (FunPtr C_FileChooserButtonFileSetCallback)
mk_FileChooserButtonFileSetCallback C_FileChooserButtonFileSetCallback
cb'
a
-> Text
-> FunPtr C_FileChooserButtonFileSetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"file-set" FunPtr C_FileChooserButtonFileSetCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FileChooserButtonFileSetSignalInfo
instance SignalInfo FileChooserButtonFileSetSignalInfo where
type HaskellCallbackType FileChooserButtonFileSetSignalInfo = FileChooserButtonFileSetCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FileChooserButtonFileSetCallback cb
cb'' <- mk_FileChooserButtonFileSetCallback cb'
connectSignalFunPtr obj "file-set" cb'' connectMode detail
#endif
constructFileChooserButtonDialog :: (IsFileChooserButton o, MIO.MonadIO m, Gtk.FileChooser.IsFileChooser a) => a -> m (GValueConstruct o)
constructFileChooserButtonDialog :: a -> m (GValueConstruct o)
constructFileChooserButtonDialog a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"dialog" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data FileChooserButtonDialogPropertyInfo
instance AttrInfo FileChooserButtonDialogPropertyInfo where
type AttrAllowedOps FileChooserButtonDialogPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint FileChooserButtonDialogPropertyInfo = IsFileChooserButton
type AttrSetTypeConstraint FileChooserButtonDialogPropertyInfo = Gtk.FileChooser.IsFileChooser
type AttrTransferTypeConstraint FileChooserButtonDialogPropertyInfo = Gtk.FileChooser.IsFileChooser
type AttrTransferType FileChooserButtonDialogPropertyInfo = Gtk.FileChooser.FileChooser
type AttrGetType FileChooserButtonDialogPropertyInfo = ()
type AttrLabel FileChooserButtonDialogPropertyInfo = "dialog"
type AttrOrigin FileChooserButtonDialogPropertyInfo = FileChooserButton
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gtk.FileChooser.FileChooser v
attrConstruct = constructFileChooserButtonDialog
attrClear = undefined
#endif
getFileChooserButtonTitle :: (MonadIO m, IsFileChooserButton o) => o -> m T.Text
getFileChooserButtonTitle :: o -> m Text
getFileChooserButtonTitle o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getFileChooserButtonTitle" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"title"
setFileChooserButtonTitle :: (MonadIO m, IsFileChooserButton o) => o -> T.Text -> m ()
setFileChooserButtonTitle :: o -> Text -> m ()
setFileChooserButtonTitle o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"title" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructFileChooserButtonTitle :: (IsFileChooserButton o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructFileChooserButtonTitle :: Text -> m (GValueConstruct o)
constructFileChooserButtonTitle Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"title" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data FileChooserButtonTitlePropertyInfo
instance AttrInfo FileChooserButtonTitlePropertyInfo where
type AttrAllowedOps FileChooserButtonTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint FileChooserButtonTitlePropertyInfo = IsFileChooserButton
type AttrSetTypeConstraint FileChooserButtonTitlePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint FileChooserButtonTitlePropertyInfo = (~) T.Text
type AttrTransferType FileChooserButtonTitlePropertyInfo = T.Text
type AttrGetType FileChooserButtonTitlePropertyInfo = T.Text
type AttrLabel FileChooserButtonTitlePropertyInfo = "title"
type AttrOrigin FileChooserButtonTitlePropertyInfo = FileChooserButton
attrGet = getFileChooserButtonTitle
attrSet = setFileChooserButtonTitle
attrTransfer _ v = do
return v
attrConstruct = constructFileChooserButtonTitle
attrClear = undefined
#endif
getFileChooserButtonWidthChars :: (MonadIO m, IsFileChooserButton o) => o -> m Int32
getFileChooserButtonWidthChars :: o -> m Int32
getFileChooserButtonWidthChars o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"width-chars"
setFileChooserButtonWidthChars :: (MonadIO m, IsFileChooserButton o) => o -> Int32 -> m ()
setFileChooserButtonWidthChars :: o -> Int32 -> m ()
setFileChooserButtonWidthChars o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"width-chars" Int32
val
constructFileChooserButtonWidthChars :: (IsFileChooserButton o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructFileChooserButtonWidthChars :: Int32 -> m (GValueConstruct o)
constructFileChooserButtonWidthChars Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"width-chars" Int32
val
#if defined(ENABLE_OVERLOADING)
data FileChooserButtonWidthCharsPropertyInfo
instance AttrInfo FileChooserButtonWidthCharsPropertyInfo where
type AttrAllowedOps FileChooserButtonWidthCharsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint FileChooserButtonWidthCharsPropertyInfo = IsFileChooserButton
type AttrSetTypeConstraint FileChooserButtonWidthCharsPropertyInfo = (~) Int32
type AttrTransferTypeConstraint FileChooserButtonWidthCharsPropertyInfo = (~) Int32
type AttrTransferType FileChooserButtonWidthCharsPropertyInfo = Int32
type AttrGetType FileChooserButtonWidthCharsPropertyInfo = Int32
type AttrLabel FileChooserButtonWidthCharsPropertyInfo = "width-chars"
type AttrOrigin FileChooserButtonWidthCharsPropertyInfo = FileChooserButton
attrGet = getFileChooserButtonWidthChars
attrSet = setFileChooserButtonWidthChars
attrTransfer _ v = do
return v
attrConstruct = constructFileChooserButtonWidthChars
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FileChooserButton
type instance O.AttributeList FileChooserButton = FileChooserButtonAttributeList
type FileChooserButtonAttributeList = ('[ '("action", Gtk.FileChooser.FileChooserActionPropertyInfo), '("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), '("dialog", FileChooserButtonDialogPropertyInfo), '("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), '("selectMultiple", Gtk.FileChooser.FileChooserSelectMultiplePropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("showHidden", Gtk.FileChooser.FileChooserShowHiddenPropertyInfo), '("spacing", Gtk.Box.BoxSpacingPropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("title", FileChooserButtonTitlePropertyInfo), '("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), '("widthChars", FileChooserButtonWidthCharsPropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
fileChooserButtonDialog :: AttrLabelProxy "dialog"
fileChooserButtonDialog = AttrLabelProxy
fileChooserButtonTitle :: AttrLabelProxy "title"
fileChooserButtonTitle = AttrLabelProxy
fileChooserButtonWidthChars :: AttrLabelProxy "widthChars"
fileChooserButtonWidthChars = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FileChooserButton = FileChooserButtonSignalList
type FileChooserButtonSignalList = ('[ '("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), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("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), '("fileSet", FileChooserButtonFileSetSignalInfo), '("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), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("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), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("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), '("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), '("updatePreview", Gtk.FileChooser.FileChooserUpdatePreviewSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_file_chooser_button_new" gtk_file_chooser_button_new ::
CString ->
CUInt ->
IO (Ptr FileChooserButton)
fileChooserButtonNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Gtk.Enums.FileChooserAction
-> m FileChooserButton
fileChooserButtonNew :: Text -> FileChooserAction -> m FileChooserButton
fileChooserButtonNew Text
title FileChooserAction
action = IO FileChooserButton -> m FileChooserButton
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileChooserButton -> m FileChooserButton)
-> IO FileChooserButton -> m FileChooserButton
forall a b. (a -> b) -> a -> b
$ do
CString
title' <- Text -> IO CString
textToCString Text
title
let action' :: CUInt
action' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (FileChooserAction -> Int) -> FileChooserAction -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileChooserAction -> Int
forall a. Enum a => a -> Int
fromEnum) FileChooserAction
action
Ptr FileChooserButton
result <- CString -> CUInt -> IO (Ptr FileChooserButton)
gtk_file_chooser_button_new CString
title' CUInt
action'
Text -> Ptr FileChooserButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fileChooserButtonNew" Ptr FileChooserButton
result
FileChooserButton
result' <- ((ManagedPtr FileChooserButton -> FileChooserButton)
-> Ptr FileChooserButton -> IO FileChooserButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FileChooserButton -> FileChooserButton
FileChooserButton) Ptr FileChooserButton
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
FileChooserButton -> IO FileChooserButton
forall (m :: * -> *) a. Monad m => a -> m a
return FileChooserButton
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_file_chooser_button_new_with_dialog" gtk_file_chooser_button_new_with_dialog ::
Ptr Gtk.Dialog.Dialog ->
IO (Ptr FileChooserButton)
fileChooserButtonNewWithDialog ::
(B.CallStack.HasCallStack, MonadIO m, Gtk.Dialog.IsDialog a) =>
a
-> m FileChooserButton
fileChooserButtonNewWithDialog :: a -> m FileChooserButton
fileChooserButtonNewWithDialog a
dialog = IO FileChooserButton -> m FileChooserButton
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileChooserButton -> m FileChooserButton)
-> IO FileChooserButton -> m FileChooserButton
forall a b. (a -> b) -> a -> b
$ do
Ptr Dialog
dialog' <- a -> IO (Ptr Dialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dialog
Ptr FileChooserButton
result <- Ptr Dialog -> IO (Ptr FileChooserButton)
gtk_file_chooser_button_new_with_dialog Ptr Dialog
dialog'
Text -> Ptr FileChooserButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fileChooserButtonNewWithDialog" Ptr FileChooserButton
result
FileChooserButton
result' <- ((ManagedPtr FileChooserButton -> FileChooserButton)
-> Ptr FileChooserButton -> IO FileChooserButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FileChooserButton -> FileChooserButton
FileChooserButton) Ptr FileChooserButton
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dialog
FileChooserButton -> IO FileChooserButton
forall (m :: * -> *) a. Monad m => a -> m a
return FileChooserButton
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_file_chooser_button_get_focus_on_click" gtk_file_chooser_button_get_focus_on_click ::
Ptr FileChooserButton ->
IO CInt
{-# DEPRECATED fileChooserButtonGetFocusOnClick ["(Since version 3.20)","Use 'GI.Gtk.Objects.Widget.widgetGetFocusOnClick' instead"] #-}
fileChooserButtonGetFocusOnClick ::
(B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
a
-> m Bool
fileChooserButtonGetFocusOnClick :: a -> m Bool
fileChooserButtonGetFocusOnClick a
button = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
CInt
result <- Ptr FileChooserButton -> IO CInt
gtk_file_chooser_button_get_focus_on_click Ptr FileChooserButton
button'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data FileChooserButtonGetFocusOnClickMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonGetFocusOnClickMethodInfo a signature where
overloadedMethod = fileChooserButtonGetFocusOnClick
#endif
foreign import ccall "gtk_file_chooser_button_get_title" gtk_file_chooser_button_get_title ::
Ptr FileChooserButton ->
IO CString
fileChooserButtonGetTitle ::
(B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
a
-> m T.Text
fileChooserButtonGetTitle :: a -> m Text
fileChooserButtonGetTitle a
button = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
CString
result <- Ptr FileChooserButton -> IO CString
gtk_file_chooser_button_get_title Ptr FileChooserButton
button'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fileChooserButtonGetTitle" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data FileChooserButtonGetTitleMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonGetTitleMethodInfo a signature where
overloadedMethod = fileChooserButtonGetTitle
#endif
foreign import ccall "gtk_file_chooser_button_get_width_chars" gtk_file_chooser_button_get_width_chars ::
Ptr FileChooserButton ->
IO Int32
fileChooserButtonGetWidthChars ::
(B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
a
-> m Int32
fileChooserButtonGetWidthChars :: a -> m Int32
fileChooserButtonGetWidthChars a
button = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
Int32
result <- Ptr FileChooserButton -> IO Int32
gtk_file_chooser_button_get_width_chars Ptr FileChooserButton
button'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FileChooserButtonGetWidthCharsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonGetWidthCharsMethodInfo a signature where
overloadedMethod = fileChooserButtonGetWidthChars
#endif
foreign import ccall "gtk_file_chooser_button_set_focus_on_click" gtk_file_chooser_button_set_focus_on_click ::
Ptr FileChooserButton ->
CInt ->
IO ()
{-# DEPRECATED fileChooserButtonSetFocusOnClick ["(Since version 3.20)","Use 'GI.Gtk.Objects.Widget.widgetSetFocusOnClick' instead"] #-}
fileChooserButtonSetFocusOnClick ::
(B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
a
-> Bool
-> m ()
fileChooserButtonSetFocusOnClick :: a -> Bool -> m ()
fileChooserButtonSetFocusOnClick a
button Bool
focusOnClick = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
let focusOnClick' :: CInt
focusOnClick' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
focusOnClick
Ptr FileChooserButton -> CInt -> IO ()
gtk_file_chooser_button_set_focus_on_click Ptr FileChooserButton
button' CInt
focusOnClick'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FileChooserButtonSetFocusOnClickMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonSetFocusOnClickMethodInfo a signature where
overloadedMethod = fileChooserButtonSetFocusOnClick
#endif
foreign import ccall "gtk_file_chooser_button_set_title" gtk_file_chooser_button_set_title ::
Ptr FileChooserButton ->
CString ->
IO ()
fileChooserButtonSetTitle ::
(B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
a
-> T.Text
-> m ()
fileChooserButtonSetTitle :: a -> Text -> m ()
fileChooserButtonSetTitle a
button Text
title = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
CString
title' <- Text -> IO CString
textToCString Text
title
Ptr FileChooserButton -> CString -> IO ()
gtk_file_chooser_button_set_title Ptr FileChooserButton
button' CString
title'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FileChooserButtonSetTitleMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonSetTitleMethodInfo a signature where
overloadedMethod = fileChooserButtonSetTitle
#endif
foreign import ccall "gtk_file_chooser_button_set_width_chars" gtk_file_chooser_button_set_width_chars ::
Ptr FileChooserButton ->
Int32 ->
IO ()
fileChooserButtonSetWidthChars ::
(B.CallStack.HasCallStack, MonadIO m, IsFileChooserButton a) =>
a
-> Int32
-> m ()
fileChooserButtonSetWidthChars :: a -> Int32 -> m ()
fileChooserButtonSetWidthChars a
button Int32
nChars = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr FileChooserButton
button' <- a -> IO (Ptr FileChooserButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
Ptr FileChooserButton -> Int32 -> IO ()
gtk_file_chooser_button_set_width_chars Ptr FileChooserButton
button' Int32
nChars
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FileChooserButtonSetWidthCharsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsFileChooserButton a) => O.MethodInfo FileChooserButtonSetWidthCharsMethodInfo a signature where
overloadedMethod = fileChooserButtonSetWidthChars
#endif