{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Interfaces.AppChooser
(
AppChooser(..) ,
IsAppChooser ,
toAppChooser ,
#if defined(ENABLE_OVERLOADING)
ResolveAppChooserMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
AppChooserGetAppInfoMethodInfo ,
#endif
appChooserGetAppInfo ,
#if defined(ENABLE_OVERLOADING)
AppChooserGetContentTypeMethodInfo ,
#endif
appChooserGetContentType ,
#if defined(ENABLE_OVERLOADING)
AppChooserRefreshMethodInfo ,
#endif
appChooserRefresh ,
#if defined(ENABLE_OVERLOADING)
AppChooserContentTypePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
appChooserContentType ,
#endif
constructAppChooserContentType ,
getAppChooserContentType ,
) 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.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.AppInfo as Gio.AppInfo
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype AppChooser = AppChooser (SP.ManagedPtr AppChooser)
deriving (AppChooser -> AppChooser -> Bool
(AppChooser -> AppChooser -> Bool)
-> (AppChooser -> AppChooser -> Bool) -> Eq AppChooser
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AppChooser -> AppChooser -> Bool
== :: AppChooser -> AppChooser -> Bool
$c/= :: AppChooser -> AppChooser -> Bool
/= :: AppChooser -> AppChooser -> Bool
Eq)
instance SP.ManagedPtrNewtype AppChooser where
toManagedPtr :: AppChooser -> ManagedPtr AppChooser
toManagedPtr (AppChooser ManagedPtr AppChooser
p) = ManagedPtr AppChooser
p
foreign import ccall "gtk_app_chooser_get_type"
c_gtk_app_chooser_get_type :: IO B.Types.GType
instance B.Types.TypedObject AppChooser where
glibType :: IO GType
glibType = IO GType
c_gtk_app_chooser_get_type
instance B.Types.GObject AppChooser
class (SP.GObject o, O.IsDescendantOf AppChooser o) => IsAppChooser o
instance (SP.GObject o, O.IsDescendantOf AppChooser o) => IsAppChooser o
instance O.HasParentTypes AppChooser
type instance O.ParentTypes AppChooser = '[GObject.Object.Object, Gtk.Widget.Widget]
toAppChooser :: (MIO.MonadIO m, IsAppChooser o) => o -> m AppChooser
toAppChooser :: forall (m :: * -> *) o.
(MonadIO m, IsAppChooser o) =>
o -> m AppChooser
toAppChooser = IO AppChooser -> m AppChooser
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO AppChooser -> m AppChooser)
-> (o -> IO AppChooser) -> o -> m AppChooser
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr AppChooser -> AppChooser) -> o -> IO AppChooser
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr AppChooser -> AppChooser
AppChooser
instance B.GValue.IsGValue (Maybe AppChooser) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_app_chooser_get_type
gvalueSet_ :: Ptr GValue -> Maybe AppChooser -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AppChooser
P.Nothing = Ptr GValue -> Ptr AppChooser -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr AppChooser
forall a. Ptr a
FP.nullPtr :: FP.Ptr AppChooser)
gvalueSet_ Ptr GValue
gv (P.Just AppChooser
obj) = AppChooser -> (Ptr AppChooser -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AppChooser
obj (Ptr GValue -> Ptr AppChooser -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe AppChooser)
gvalueGet_ Ptr GValue
gv = do
Ptr AppChooser
ptr <- Ptr GValue -> IO (Ptr AppChooser)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr AppChooser)
if Ptr AppChooser
ptr Ptr AppChooser -> Ptr AppChooser -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AppChooser
forall a. Ptr a
FP.nullPtr
then AppChooser -> Maybe AppChooser
forall a. a -> Maybe a
P.Just (AppChooser -> Maybe AppChooser)
-> IO AppChooser -> IO (Maybe AppChooser)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr AppChooser -> AppChooser)
-> Ptr AppChooser -> IO AppChooser
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AppChooser -> AppChooser
AppChooser Ptr AppChooser
ptr
else Maybe AppChooser -> IO (Maybe AppChooser)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AppChooser
forall a. Maybe a
P.Nothing
getAppChooserContentType :: (MonadIO m, IsAppChooser o) => o -> m (Maybe T.Text)
getAppChooserContentType :: forall (m :: * -> *) o.
(MonadIO m, IsAppChooser o) =>
o -> m (Maybe Text)
getAppChooserContentType 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
"content-type"
constructAppChooserContentType :: (IsAppChooser o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructAppChooserContentType :: forall o (m :: * -> *).
(IsAppChooser o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructAppChooserContentType Text
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 -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"content-type" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data AppChooserContentTypePropertyInfo
instance AttrInfo AppChooserContentTypePropertyInfo where
type AttrAllowedOps AppChooserContentTypePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint AppChooserContentTypePropertyInfo = IsAppChooser
type AttrSetTypeConstraint AppChooserContentTypePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint AppChooserContentTypePropertyInfo = (~) T.Text
type AttrTransferType AppChooserContentTypePropertyInfo = T.Text
type AttrGetType AppChooserContentTypePropertyInfo = (Maybe T.Text)
type AttrLabel AppChooserContentTypePropertyInfo = "content-type"
type AttrOrigin AppChooserContentTypePropertyInfo = AppChooser
attrGet = getAppChooserContentType
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructAppChooserContentType
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.AppChooser.contentType"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Interfaces-AppChooser.html#g:attr:contentType"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AppChooser
type instance O.AttributeList AppChooser = AppChooserAttributeList
type AppChooserAttributeList = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("contentType", AppChooserContentTypePropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("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), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("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), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("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)
appChooserContentType :: AttrLabelProxy "contentType"
appChooserContentType = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveAppChooserMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveAppChooserMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveAppChooserMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveAppChooserMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveAppChooserMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveAppChooserMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveAppChooserMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveAppChooserMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveAppChooserMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveAppChooserMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveAppChooserMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveAppChooserMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveAppChooserMethod "childNotify" o = Gtk.Widget.WidgetChildNotifyMethodInfo
ResolveAppChooserMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveAppChooserMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveAppChooserMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveAppChooserMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveAppChooserMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveAppChooserMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveAppChooserMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveAppChooserMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveAppChooserMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveAppChooserMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveAppChooserMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveAppChooserMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveAppChooserMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveAppChooserMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveAppChooserMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveAppChooserMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveAppChooserMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveAppChooserMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveAppChooserMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveAppChooserMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveAppChooserMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveAppChooserMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveAppChooserMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveAppChooserMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveAppChooserMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveAppChooserMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveAppChooserMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveAppChooserMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveAppChooserMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveAppChooserMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveAppChooserMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveAppChooserMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveAppChooserMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveAppChooserMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveAppChooserMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveAppChooserMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveAppChooserMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveAppChooserMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveAppChooserMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveAppChooserMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveAppChooserMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveAppChooserMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveAppChooserMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveAppChooserMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveAppChooserMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveAppChooserMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveAppChooserMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveAppChooserMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveAppChooserMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveAppChooserMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveAppChooserMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveAppChooserMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveAppChooserMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveAppChooserMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveAppChooserMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveAppChooserMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveAppChooserMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveAppChooserMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveAppChooserMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveAppChooserMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveAppChooserMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveAppChooserMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveAppChooserMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveAppChooserMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveAppChooserMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveAppChooserMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveAppChooserMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveAppChooserMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveAppChooserMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveAppChooserMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveAppChooserMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveAppChooserMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveAppChooserMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveAppChooserMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveAppChooserMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveAppChooserMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveAppChooserMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveAppChooserMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveAppChooserMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveAppChooserMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveAppChooserMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveAppChooserMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveAppChooserMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveAppChooserMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveAppChooserMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveAppChooserMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveAppChooserMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveAppChooserMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveAppChooserMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveAppChooserMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveAppChooserMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveAppChooserMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveAppChooserMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveAppChooserMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveAppChooserMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveAppChooserMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveAppChooserMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveAppChooserMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveAppChooserMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveAppChooserMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveAppChooserMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveAppChooserMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveAppChooserMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveAppChooserMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveAppChooserMethod "refresh" o = AppChooserRefreshMethodInfo
ResolveAppChooserMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveAppChooserMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveAppChooserMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveAppChooserMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveAppChooserMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveAppChooserMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveAppChooserMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveAppChooserMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveAppChooserMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveAppChooserMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveAppChooserMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveAppChooserMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveAppChooserMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveAppChooserMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveAppChooserMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveAppChooserMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveAppChooserMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveAppChooserMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveAppChooserMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveAppChooserMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveAppChooserMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveAppChooserMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveAppChooserMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveAppChooserMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveAppChooserMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveAppChooserMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveAppChooserMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveAppChooserMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveAppChooserMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveAppChooserMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveAppChooserMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveAppChooserMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveAppChooserMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveAppChooserMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveAppChooserMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveAppChooserMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveAppChooserMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveAppChooserMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveAppChooserMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveAppChooserMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveAppChooserMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveAppChooserMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveAppChooserMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveAppChooserMethod "getAppInfo" o = AppChooserGetAppInfoMethodInfo
ResolveAppChooserMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveAppChooserMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveAppChooserMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveAppChooserMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveAppChooserMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveAppChooserMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveAppChooserMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveAppChooserMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveAppChooserMethod "getContentType" o = AppChooserGetContentTypeMethodInfo
ResolveAppChooserMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveAppChooserMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveAppChooserMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveAppChooserMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveAppChooserMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveAppChooserMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveAppChooserMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveAppChooserMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveAppChooserMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveAppChooserMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveAppChooserMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveAppChooserMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveAppChooserMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveAppChooserMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveAppChooserMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveAppChooserMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveAppChooserMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveAppChooserMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveAppChooserMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveAppChooserMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveAppChooserMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveAppChooserMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveAppChooserMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveAppChooserMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveAppChooserMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveAppChooserMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveAppChooserMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveAppChooserMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveAppChooserMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveAppChooserMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveAppChooserMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveAppChooserMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveAppChooserMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveAppChooserMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveAppChooserMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveAppChooserMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveAppChooserMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveAppChooserMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveAppChooserMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveAppChooserMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveAppChooserMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveAppChooserMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveAppChooserMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveAppChooserMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveAppChooserMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveAppChooserMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveAppChooserMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveAppChooserMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveAppChooserMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveAppChooserMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveAppChooserMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveAppChooserMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveAppChooserMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveAppChooserMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveAppChooserMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveAppChooserMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveAppChooserMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveAppChooserMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveAppChooserMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveAppChooserMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveAppChooserMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveAppChooserMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveAppChooserMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveAppChooserMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveAppChooserMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveAppChooserMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveAppChooserMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveAppChooserMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveAppChooserMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveAppChooserMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveAppChooserMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveAppChooserMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveAppChooserMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveAppChooserMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveAppChooserMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveAppChooserMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveAppChooserMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveAppChooserMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveAppChooserMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveAppChooserMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveAppChooserMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveAppChooserMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveAppChooserMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveAppChooserMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveAppChooserMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveAppChooserMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveAppChooserMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveAppChooserMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveAppChooserMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveAppChooserMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveAppChooserMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveAppChooserMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveAppChooserMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveAppChooserMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveAppChooserMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveAppChooserMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveAppChooserMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveAppChooserMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveAppChooserMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveAppChooserMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveAppChooserMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveAppChooserMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveAppChooserMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveAppChooserMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveAppChooserMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveAppChooserMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveAppChooserMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveAppChooserMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveAppChooserMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveAppChooserMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveAppChooserMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveAppChooserMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveAppChooserMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveAppChooserMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveAppChooserMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveAppChooserMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveAppChooserMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveAppChooserMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveAppChooserMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveAppChooserMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveAppChooserMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveAppChooserMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveAppChooserMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveAppChooserMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveAppChooserMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAppChooserMethod t AppChooser, O.OverloadedMethod info AppChooser p) => OL.IsLabel t (AppChooser -> 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 ~ ResolveAppChooserMethod t AppChooser, O.OverloadedMethod info AppChooser p, R.HasField t AppChooser p) => R.HasField t AppChooser p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveAppChooserMethod t AppChooser, O.OverloadedMethodInfo info AppChooser) => OL.IsLabel t (O.MethodProxy info AppChooser) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "gtk_app_chooser_get_app_info" gtk_app_chooser_get_app_info ::
Ptr AppChooser ->
IO (Ptr Gio.AppInfo.AppInfo)
appChooserGetAppInfo ::
(B.CallStack.HasCallStack, MonadIO m, IsAppChooser a) =>
a
-> m (Maybe Gio.AppInfo.AppInfo)
appChooserGetAppInfo :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAppChooser a) =>
a -> m (Maybe AppInfo)
appChooserGetAppInfo a
self = IO (Maybe AppInfo) -> m (Maybe AppInfo)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe AppInfo) -> m (Maybe AppInfo))
-> IO (Maybe AppInfo) -> m (Maybe AppInfo)
forall a b. (a -> b) -> a -> b
$ do
Ptr AppChooser
self' <- a -> IO (Ptr AppChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr AppInfo
result <- Ptr AppChooser -> IO (Ptr AppInfo)
gtk_app_chooser_get_app_info Ptr AppChooser
self'
Maybe AppInfo
maybeResult <- Ptr AppInfo -> (Ptr AppInfo -> IO AppInfo) -> IO (Maybe AppInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr AppInfo
result ((Ptr AppInfo -> IO AppInfo) -> IO (Maybe AppInfo))
-> (Ptr AppInfo -> IO AppInfo) -> IO (Maybe AppInfo)
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
result' -> do
AppInfo
result'' <- ((ManagedPtr AppInfo -> AppInfo) -> Ptr AppInfo -> IO AppInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr AppInfo -> AppInfo
Gio.AppInfo.AppInfo) Ptr AppInfo
result'
AppInfo -> IO AppInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AppInfo
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe AppInfo -> IO (Maybe AppInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AppInfo
maybeResult
#if defined(ENABLE_OVERLOADING)
data AppChooserGetAppInfoMethodInfo
instance (signature ~ (m (Maybe Gio.AppInfo.AppInfo)), MonadIO m, IsAppChooser a) => O.OverloadedMethod AppChooserGetAppInfoMethodInfo a signature where
overloadedMethod = appChooserGetAppInfo
instance O.OverloadedMethodInfo AppChooserGetAppInfoMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.AppChooser.appChooserGetAppInfo",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Interfaces-AppChooser.html#v:appChooserGetAppInfo"
})
#endif
foreign import ccall "gtk_app_chooser_get_content_type" gtk_app_chooser_get_content_type ::
Ptr AppChooser ->
IO CString
appChooserGetContentType ::
(B.CallStack.HasCallStack, MonadIO m, IsAppChooser a) =>
a
-> m T.Text
appChooserGetContentType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAppChooser a) =>
a -> m Text
appChooserGetContentType a
self = IO Text -> m Text
forall a. IO a -> m a
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 AppChooser
self' <- a -> IO (Ptr AppChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr AppChooser -> IO CString
gtk_app_chooser_get_content_type Ptr AppChooser
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"appChooserGetContentType" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data AppChooserGetContentTypeMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAppChooser a) => O.OverloadedMethod AppChooserGetContentTypeMethodInfo a signature where
overloadedMethod = appChooserGetContentType
instance O.OverloadedMethodInfo AppChooserGetContentTypeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.AppChooser.appChooserGetContentType",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Interfaces-AppChooser.html#v:appChooserGetContentType"
})
#endif
foreign import ccall "gtk_app_chooser_refresh" gtk_app_chooser_refresh ::
Ptr AppChooser ->
IO ()
appChooserRefresh ::
(B.CallStack.HasCallStack, MonadIO m, IsAppChooser a) =>
a
-> m ()
appChooserRefresh :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAppChooser a) =>
a -> m ()
appChooserRefresh a
self = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr AppChooser
self' <- a -> IO (Ptr AppChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr AppChooser -> IO ()
gtk_app_chooser_refresh Ptr AppChooser
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AppChooserRefreshMethodInfo
instance (signature ~ (m ()), MonadIO m, IsAppChooser a) => O.OverloadedMethod AppChooserRefreshMethodInfo a signature where
overloadedMethod = appChooserRefresh
instance O.OverloadedMethodInfo AppChooserRefreshMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.AppChooser.appChooserRefresh",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Interfaces-AppChooser.html#v:appChooserRefresh"
})
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AppChooser = AppChooserSignalList
type AppChooserSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("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), '("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), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("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), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])
#endif