{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.SimplePopover
(
SimplePopover(..) ,
IsSimplePopover ,
toSimplePopover ,
#if defined(ENABLE_OVERLOADING)
ResolveSimplePopoverMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SimplePopoverGetButtonTextMethodInfo ,
#endif
simplePopoverGetButtonText ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverGetMessageMethodInfo ,
#endif
simplePopoverGetMessage ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverGetReadyMethodInfo ,
#endif
simplePopoverGetReady ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverGetTextMethodInfo ,
#endif
simplePopoverGetText ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverGetTitleMethodInfo ,
#endif
simplePopoverGetTitle ,
simplePopoverNew ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverSetButtonTextMethodInfo ,
#endif
simplePopoverSetButtonText ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverSetMessageMethodInfo ,
#endif
simplePopoverSetMessage ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverSetReadyMethodInfo ,
#endif
simplePopoverSetReady ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverSetTextMethodInfo ,
#endif
simplePopoverSetText ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverSetTitleMethodInfo ,
#endif
simplePopoverSetTitle ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverButtonTextPropertyInfo ,
#endif
constructSimplePopoverButtonText ,
getSimplePopoverButtonText ,
setSimplePopoverButtonText ,
#if defined(ENABLE_OVERLOADING)
simplePopoverButtonText ,
#endif
#if defined(ENABLE_OVERLOADING)
SimplePopoverMessagePropertyInfo ,
#endif
constructSimplePopoverMessage ,
getSimplePopoverMessage ,
setSimplePopoverMessage ,
#if defined(ENABLE_OVERLOADING)
simplePopoverMessage ,
#endif
#if defined(ENABLE_OVERLOADING)
SimplePopoverReadyPropertyInfo ,
#endif
constructSimplePopoverReady ,
getSimplePopoverReady ,
setSimplePopoverReady ,
#if defined(ENABLE_OVERLOADING)
simplePopoverReady ,
#endif
#if defined(ENABLE_OVERLOADING)
SimplePopoverTextPropertyInfo ,
#endif
constructSimplePopoverText ,
getSimplePopoverText ,
setSimplePopoverText ,
#if defined(ENABLE_OVERLOADING)
simplePopoverText ,
#endif
#if defined(ENABLE_OVERLOADING)
SimplePopoverTitlePropertyInfo ,
#endif
constructSimplePopoverTitle ,
getSimplePopoverTitle ,
setSimplePopoverTitle ,
#if defined(ENABLE_OVERLOADING)
simplePopoverTitle ,
#endif
SimplePopoverActivateCallback ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverActivateSignalInfo ,
#endif
afterSimplePopoverActivate ,
onSimplePopoverActivate ,
SimplePopoverChangedCallback ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverChangedSignalInfo ,
#endif
afterSimplePopoverChanged ,
onSimplePopoverChanged ,
SimplePopoverInsertTextCallback ,
#if defined(ENABLE_OVERLOADING)
SimplePopoverInsertTextSignalInfo ,
#endif
afterSimplePopoverInsertText ,
onSimplePopoverInsertText ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Bin as Gtk.Bin
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.Popover as Gtk.Popover
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype SimplePopover = SimplePopover (SP.ManagedPtr SimplePopover)
deriving (SimplePopover -> SimplePopover -> Bool
(SimplePopover -> SimplePopover -> Bool)
-> (SimplePopover -> SimplePopover -> Bool) -> Eq SimplePopover
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SimplePopover -> SimplePopover -> Bool
== :: SimplePopover -> SimplePopover -> Bool
$c/= :: SimplePopover -> SimplePopover -> Bool
/= :: SimplePopover -> SimplePopover -> Bool
Eq)
instance SP.ManagedPtrNewtype SimplePopover where
toManagedPtr :: SimplePopover -> ManagedPtr SimplePopover
toManagedPtr (SimplePopover ManagedPtr SimplePopover
p) = ManagedPtr SimplePopover
p
foreign import ccall "dzl_simple_popover_get_type"
c_dzl_simple_popover_get_type :: IO B.Types.GType
instance B.Types.TypedObject SimplePopover where
glibType :: IO GType
glibType = IO GType
c_dzl_simple_popover_get_type
instance B.Types.GObject SimplePopover
class (SP.GObject o, O.IsDescendantOf SimplePopover o) => IsSimplePopover o
instance (SP.GObject o, O.IsDescendantOf SimplePopover o) => IsSimplePopover o
instance O.HasParentTypes SimplePopover
type instance O.ParentTypes SimplePopover = '[Gtk.Popover.Popover, Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable]
toSimplePopover :: (MIO.MonadIO m, IsSimplePopover o) => o -> m SimplePopover
toSimplePopover :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> m SimplePopover
toSimplePopover = IO SimplePopover -> m SimplePopover
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SimplePopover -> m SimplePopover)
-> (o -> IO SimplePopover) -> o -> m SimplePopover
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SimplePopover -> SimplePopover)
-> o -> IO SimplePopover
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr SimplePopover -> SimplePopover
SimplePopover
instance B.GValue.IsGValue (Maybe SimplePopover) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_simple_popover_get_type
gvalueSet_ :: Ptr GValue -> Maybe SimplePopover -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SimplePopover
P.Nothing = Ptr GValue -> Ptr SimplePopover -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr SimplePopover
forall a. Ptr a
FP.nullPtr :: FP.Ptr SimplePopover)
gvalueSet_ Ptr GValue
gv (P.Just SimplePopover
obj) = SimplePopover -> (Ptr SimplePopover -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SimplePopover
obj (Ptr GValue -> Ptr SimplePopover -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe SimplePopover)
gvalueGet_ Ptr GValue
gv = do
Ptr SimplePopover
ptr <- Ptr GValue -> IO (Ptr SimplePopover)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr SimplePopover)
if Ptr SimplePopover
ptr Ptr SimplePopover -> Ptr SimplePopover -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr SimplePopover
forall a. Ptr a
FP.nullPtr
then SimplePopover -> Maybe SimplePopover
forall a. a -> Maybe a
P.Just (SimplePopover -> Maybe SimplePopover)
-> IO SimplePopover -> IO (Maybe SimplePopover)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr SimplePopover -> SimplePopover)
-> Ptr SimplePopover -> IO SimplePopover
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SimplePopover -> SimplePopover
SimplePopover Ptr SimplePopover
ptr
else Maybe SimplePopover -> IO (Maybe SimplePopover)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SimplePopover
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveSimplePopoverMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveSimplePopoverMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveSimplePopoverMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolveSimplePopoverMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveSimplePopoverMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveSimplePopoverMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveSimplePopoverMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveSimplePopoverMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveSimplePopoverMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveSimplePopoverMethod "bindModel" o = Gtk.Popover.PopoverBindModelMethodInfo
ResolveSimplePopoverMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSimplePopoverMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSimplePopoverMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveSimplePopoverMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolveSimplePopoverMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveSimplePopoverMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolveSimplePopoverMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolveSimplePopoverMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolveSimplePopoverMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolveSimplePopoverMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolveSimplePopoverMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveSimplePopoverMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveSimplePopoverMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveSimplePopoverMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveSimplePopoverMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveSimplePopoverMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveSimplePopoverMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveSimplePopoverMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveSimplePopoverMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveSimplePopoverMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveSimplePopoverMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveSimplePopoverMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveSimplePopoverMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveSimplePopoverMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveSimplePopoverMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveSimplePopoverMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveSimplePopoverMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveSimplePopoverMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveSimplePopoverMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveSimplePopoverMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveSimplePopoverMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveSimplePopoverMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveSimplePopoverMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveSimplePopoverMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveSimplePopoverMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveSimplePopoverMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveSimplePopoverMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveSimplePopoverMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveSimplePopoverMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveSimplePopoverMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveSimplePopoverMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveSimplePopoverMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveSimplePopoverMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveSimplePopoverMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveSimplePopoverMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveSimplePopoverMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveSimplePopoverMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveSimplePopoverMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveSimplePopoverMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveSimplePopoverMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveSimplePopoverMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveSimplePopoverMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveSimplePopoverMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveSimplePopoverMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolveSimplePopoverMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSimplePopoverMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolveSimplePopoverMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveSimplePopoverMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSimplePopoverMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSimplePopoverMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveSimplePopoverMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveSimplePopoverMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveSimplePopoverMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveSimplePopoverMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveSimplePopoverMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveSimplePopoverMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveSimplePopoverMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveSimplePopoverMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveSimplePopoverMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveSimplePopoverMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveSimplePopoverMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveSimplePopoverMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveSimplePopoverMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveSimplePopoverMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveSimplePopoverMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveSimplePopoverMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveSimplePopoverMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveSimplePopoverMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveSimplePopoverMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveSimplePopoverMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSimplePopoverMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveSimplePopoverMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveSimplePopoverMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveSimplePopoverMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveSimplePopoverMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveSimplePopoverMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveSimplePopoverMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveSimplePopoverMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveSimplePopoverMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveSimplePopoverMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveSimplePopoverMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveSimplePopoverMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveSimplePopoverMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveSimplePopoverMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveSimplePopoverMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveSimplePopoverMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveSimplePopoverMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveSimplePopoverMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSimplePopoverMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSimplePopoverMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveSimplePopoverMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveSimplePopoverMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveSimplePopoverMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveSimplePopoverMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveSimplePopoverMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveSimplePopoverMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveSimplePopoverMethod "popdown" o = Gtk.Popover.PopoverPopdownMethodInfo
ResolveSimplePopoverMethod "popup" o = Gtk.Popover.PopoverPopupMethodInfo
ResolveSimplePopoverMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolveSimplePopoverMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveSimplePopoverMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveSimplePopoverMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveSimplePopoverMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveSimplePopoverMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveSimplePopoverMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveSimplePopoverMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveSimplePopoverMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveSimplePopoverMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSimplePopoverMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSimplePopoverMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveSimplePopoverMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveSimplePopoverMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolveSimplePopoverMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveSimplePopoverMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveSimplePopoverMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveSimplePopoverMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveSimplePopoverMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveSimplePopoverMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveSimplePopoverMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveSimplePopoverMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveSimplePopoverMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolveSimplePopoverMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSimplePopoverMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveSimplePopoverMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveSimplePopoverMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveSimplePopoverMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveSimplePopoverMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveSimplePopoverMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveSimplePopoverMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveSimplePopoverMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveSimplePopoverMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveSimplePopoverMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSimplePopoverMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSimplePopoverMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveSimplePopoverMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveSimplePopoverMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveSimplePopoverMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSimplePopoverMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveSimplePopoverMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveSimplePopoverMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveSimplePopoverMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveSimplePopoverMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveSimplePopoverMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSimplePopoverMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveSimplePopoverMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolveSimplePopoverMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveSimplePopoverMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSimplePopoverMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveSimplePopoverMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveSimplePopoverMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveSimplePopoverMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveSimplePopoverMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveSimplePopoverMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveSimplePopoverMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveSimplePopoverMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveSimplePopoverMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveSimplePopoverMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolveSimplePopoverMethod "getButtonText" o = SimplePopoverGetButtonTextMethodInfo
ResolveSimplePopoverMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveSimplePopoverMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveSimplePopoverMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
ResolveSimplePopoverMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveSimplePopoverMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveSimplePopoverMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolveSimplePopoverMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveSimplePopoverMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveSimplePopoverMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveSimplePopoverMethod "getConstrainTo" o = Gtk.Popover.PopoverGetConstrainToMethodInfo
ResolveSimplePopoverMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSimplePopoverMethod "getDefaultWidget" o = Gtk.Popover.PopoverGetDefaultWidgetMethodInfo
ResolveSimplePopoverMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveSimplePopoverMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveSimplePopoverMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveSimplePopoverMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveSimplePopoverMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveSimplePopoverMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveSimplePopoverMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolveSimplePopoverMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolveSimplePopoverMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolveSimplePopoverMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveSimplePopoverMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolveSimplePopoverMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveSimplePopoverMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveSimplePopoverMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveSimplePopoverMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveSimplePopoverMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveSimplePopoverMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveSimplePopoverMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveSimplePopoverMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveSimplePopoverMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveSimplePopoverMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveSimplePopoverMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveSimplePopoverMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveSimplePopoverMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveSimplePopoverMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveSimplePopoverMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveSimplePopoverMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveSimplePopoverMethod "getMessage" o = SimplePopoverGetMessageMethodInfo
ResolveSimplePopoverMethod "getModal" o = Gtk.Popover.PopoverGetModalMethodInfo
ResolveSimplePopoverMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveSimplePopoverMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveSimplePopoverMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveSimplePopoverMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveSimplePopoverMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveSimplePopoverMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveSimplePopoverMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveSimplePopoverMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveSimplePopoverMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveSimplePopoverMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolveSimplePopoverMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveSimplePopoverMethod "getPointingTo" o = Gtk.Popover.PopoverGetPointingToMethodInfo
ResolveSimplePopoverMethod "getPosition" o = Gtk.Popover.PopoverGetPositionMethodInfo
ResolveSimplePopoverMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveSimplePopoverMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveSimplePopoverMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveSimplePopoverMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveSimplePopoverMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveSimplePopoverMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveSimplePopoverMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSimplePopoverMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSimplePopoverMethod "getReady" o = SimplePopoverGetReadyMethodInfo
ResolveSimplePopoverMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveSimplePopoverMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveSimplePopoverMethod "getRelativeTo" o = Gtk.Popover.PopoverGetRelativeToMethodInfo
ResolveSimplePopoverMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveSimplePopoverMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveSimplePopoverMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolveSimplePopoverMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveSimplePopoverMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveSimplePopoverMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveSimplePopoverMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveSimplePopoverMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveSimplePopoverMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveSimplePopoverMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveSimplePopoverMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveSimplePopoverMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveSimplePopoverMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveSimplePopoverMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveSimplePopoverMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveSimplePopoverMethod "getText" o = SimplePopoverGetTextMethodInfo
ResolveSimplePopoverMethod "getTitle" o = SimplePopoverGetTitleMethodInfo
ResolveSimplePopoverMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveSimplePopoverMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveSimplePopoverMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveSimplePopoverMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveSimplePopoverMethod "getTransitionsEnabled" o = Gtk.Popover.PopoverGetTransitionsEnabledMethodInfo
ResolveSimplePopoverMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveSimplePopoverMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveSimplePopoverMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveSimplePopoverMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveSimplePopoverMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveSimplePopoverMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveSimplePopoverMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveSimplePopoverMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveSimplePopoverMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveSimplePopoverMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveSimplePopoverMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolveSimplePopoverMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveSimplePopoverMethod "setButtonText" o = SimplePopoverSetButtonTextMethodInfo
ResolveSimplePopoverMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveSimplePopoverMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveSimplePopoverMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveSimplePopoverMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveSimplePopoverMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveSimplePopoverMethod "setConstrainTo" o = Gtk.Popover.PopoverSetConstrainToMethodInfo
ResolveSimplePopoverMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSimplePopoverMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSimplePopoverMethod "setDefaultWidget" o = Gtk.Popover.PopoverSetDefaultWidgetMethodInfo
ResolveSimplePopoverMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveSimplePopoverMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveSimplePopoverMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveSimplePopoverMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveSimplePopoverMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveSimplePopoverMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolveSimplePopoverMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolveSimplePopoverMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolveSimplePopoverMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveSimplePopoverMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolveSimplePopoverMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveSimplePopoverMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveSimplePopoverMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveSimplePopoverMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveSimplePopoverMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveSimplePopoverMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveSimplePopoverMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveSimplePopoverMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveSimplePopoverMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveSimplePopoverMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveSimplePopoverMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveSimplePopoverMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveSimplePopoverMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveSimplePopoverMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveSimplePopoverMethod "setMessage" o = SimplePopoverSetMessageMethodInfo
ResolveSimplePopoverMethod "setModal" o = Gtk.Popover.PopoverSetModalMethodInfo
ResolveSimplePopoverMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveSimplePopoverMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveSimplePopoverMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveSimplePopoverMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveSimplePopoverMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveSimplePopoverMethod "setPointingTo" o = Gtk.Popover.PopoverSetPointingToMethodInfo
ResolveSimplePopoverMethod "setPosition" o = Gtk.Popover.PopoverSetPositionMethodInfo
ResolveSimplePopoverMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSimplePopoverMethod "setReady" o = SimplePopoverSetReadyMethodInfo
ResolveSimplePopoverMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveSimplePopoverMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolveSimplePopoverMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveSimplePopoverMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveSimplePopoverMethod "setRelativeTo" o = Gtk.Popover.PopoverSetRelativeToMethodInfo
ResolveSimplePopoverMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolveSimplePopoverMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveSimplePopoverMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveSimplePopoverMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveSimplePopoverMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveSimplePopoverMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveSimplePopoverMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveSimplePopoverMethod "setText" o = SimplePopoverSetTextMethodInfo
ResolveSimplePopoverMethod "setTitle" o = SimplePopoverSetTitleMethodInfo
ResolveSimplePopoverMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveSimplePopoverMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveSimplePopoverMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveSimplePopoverMethod "setTransitionsEnabled" o = Gtk.Popover.PopoverSetTransitionsEnabledMethodInfo
ResolveSimplePopoverMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveSimplePopoverMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveSimplePopoverMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveSimplePopoverMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveSimplePopoverMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveSimplePopoverMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveSimplePopoverMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSimplePopoverMethod t SimplePopover, O.OverloadedMethod info SimplePopover p) => OL.IsLabel t (SimplePopover -> 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 ~ ResolveSimplePopoverMethod t SimplePopover, O.OverloadedMethod info SimplePopover p, R.HasField t SimplePopover p) => R.HasField t SimplePopover p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveSimplePopoverMethod t SimplePopover, O.OverloadedMethodInfo info SimplePopover) => OL.IsLabel t (O.MethodProxy info SimplePopover) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type SimplePopoverActivateCallback =
T.Text
-> IO ()
type C_SimplePopoverActivateCallback =
Ptr SimplePopover ->
CString ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_SimplePopoverActivateCallback :: C_SimplePopoverActivateCallback -> IO (FunPtr C_SimplePopoverActivateCallback)
wrap_SimplePopoverActivateCallback ::
GObject a => (a -> SimplePopoverActivateCallback) ->
C_SimplePopoverActivateCallback
wrap_SimplePopoverActivateCallback :: forall a.
GObject a =>
(a -> SimplePopoverActivateCallback)
-> C_SimplePopoverActivateCallback
wrap_SimplePopoverActivateCallback a -> SimplePopoverActivateCallback
gi'cb Ptr SimplePopover
gi'selfPtr CString
text Ptr ()
_ = do
Text
text' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
text
Ptr SimplePopover -> (SimplePopover -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr SimplePopover
gi'selfPtr ((SimplePopover -> IO ()) -> IO ())
-> (SimplePopover -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \SimplePopover
gi'self -> a -> SimplePopoverActivateCallback
gi'cb (SimplePopover -> a
forall a b. Coercible a b => a -> b
Coerce.coerce SimplePopover
gi'self) Text
text'
onSimplePopoverActivate :: (IsSimplePopover a, MonadIO m) => a -> ((?self :: a) => SimplePopoverActivateCallback) -> m SignalHandlerId
onSimplePopoverActivate :: forall a (m :: * -> *).
(IsSimplePopover a, MonadIO m) =>
a
-> ((?self::a) => SimplePopoverActivateCallback)
-> m SignalHandlerId
onSimplePopoverActivate a
obj (?self::a) => SimplePopoverActivateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> SimplePopoverActivateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SimplePopoverActivateCallback
SimplePopoverActivateCallback
cb
let wrapped' :: C_SimplePopoverActivateCallback
wrapped' = (a -> SimplePopoverActivateCallback)
-> C_SimplePopoverActivateCallback
forall a.
GObject a =>
(a -> SimplePopoverActivateCallback)
-> C_SimplePopoverActivateCallback
wrap_SimplePopoverActivateCallback a -> SimplePopoverActivateCallback
wrapped
FunPtr C_SimplePopoverActivateCallback
wrapped'' <- C_SimplePopoverActivateCallback
-> IO (FunPtr C_SimplePopoverActivateCallback)
mk_SimplePopoverActivateCallback C_SimplePopoverActivateCallback
wrapped'
a
-> Text
-> FunPtr C_SimplePopoverActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_SimplePopoverActivateCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterSimplePopoverActivate :: (IsSimplePopover a, MonadIO m) => a -> ((?self :: a) => SimplePopoverActivateCallback) -> m SignalHandlerId
afterSimplePopoverActivate :: forall a (m :: * -> *).
(IsSimplePopover a, MonadIO m) =>
a
-> ((?self::a) => SimplePopoverActivateCallback)
-> m SignalHandlerId
afterSimplePopoverActivate a
obj (?self::a) => SimplePopoverActivateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> SimplePopoverActivateCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SimplePopoverActivateCallback
SimplePopoverActivateCallback
cb
let wrapped' :: C_SimplePopoverActivateCallback
wrapped' = (a -> SimplePopoverActivateCallback)
-> C_SimplePopoverActivateCallback
forall a.
GObject a =>
(a -> SimplePopoverActivateCallback)
-> C_SimplePopoverActivateCallback
wrap_SimplePopoverActivateCallback a -> SimplePopoverActivateCallback
wrapped
FunPtr C_SimplePopoverActivateCallback
wrapped'' <- C_SimplePopoverActivateCallback
-> IO (FunPtr C_SimplePopoverActivateCallback)
mk_SimplePopoverActivateCallback C_SimplePopoverActivateCallback
wrapped'
a
-> Text
-> FunPtr C_SimplePopoverActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_SimplePopoverActivateCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data SimplePopoverActivateSignalInfo
instance SignalInfo SimplePopoverActivateSignalInfo where
type HaskellCallbackType SimplePopoverActivateSignalInfo = SimplePopoverActivateCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_SimplePopoverActivateCallback cb
cb'' <- mk_SimplePopoverActivateCallback cb'
connectSignalFunPtr obj "activate" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover::activate"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#g:signal:activate"})
#endif
type SimplePopoverChangedCallback =
IO ()
type C_SimplePopoverChangedCallback =
Ptr SimplePopover ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_SimplePopoverChangedCallback :: C_SimplePopoverChangedCallback -> IO (FunPtr C_SimplePopoverChangedCallback)
wrap_SimplePopoverChangedCallback ::
GObject a => (a -> SimplePopoverChangedCallback) ->
C_SimplePopoverChangedCallback
wrap_SimplePopoverChangedCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_SimplePopoverChangedCallback
wrap_SimplePopoverChangedCallback a -> IO ()
gi'cb Ptr SimplePopover
gi'selfPtr Ptr ()
_ = do
Ptr SimplePopover -> (SimplePopover -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr SimplePopover
gi'selfPtr ((SimplePopover -> IO ()) -> IO ())
-> (SimplePopover -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \SimplePopover
gi'self -> a -> IO ()
gi'cb (SimplePopover -> a
forall a b. Coercible a b => a -> b
Coerce.coerce SimplePopover
gi'self)
onSimplePopoverChanged :: (IsSimplePopover a, MonadIO m) => a -> ((?self :: a) => SimplePopoverChangedCallback) -> m SignalHandlerId
onSimplePopoverChanged :: forall a (m :: * -> *).
(IsSimplePopover a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onSimplePopoverChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_SimplePopoverChangedCallback
wrapped' = (a -> IO ()) -> C_SimplePopoverChangedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_SimplePopoverChangedCallback
wrap_SimplePopoverChangedCallback a -> IO ()
wrapped
FunPtr C_SimplePopoverChangedCallback
wrapped'' <- C_SimplePopoverChangedCallback
-> IO (FunPtr C_SimplePopoverChangedCallback)
mk_SimplePopoverChangedCallback C_SimplePopoverChangedCallback
wrapped'
a
-> Text
-> FunPtr C_SimplePopoverChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"changed" FunPtr C_SimplePopoverChangedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterSimplePopoverChanged :: (IsSimplePopover a, MonadIO m) => a -> ((?self :: a) => SimplePopoverChangedCallback) -> m SignalHandlerId
afterSimplePopoverChanged :: forall a (m :: * -> *).
(IsSimplePopover a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterSimplePopoverChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_SimplePopoverChangedCallback
wrapped' = (a -> IO ()) -> C_SimplePopoverChangedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_SimplePopoverChangedCallback
wrap_SimplePopoverChangedCallback a -> IO ()
wrapped
FunPtr C_SimplePopoverChangedCallback
wrapped'' <- C_SimplePopoverChangedCallback
-> IO (FunPtr C_SimplePopoverChangedCallback)
mk_SimplePopoverChangedCallback C_SimplePopoverChangedCallback
wrapped'
a
-> Text
-> FunPtr C_SimplePopoverChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"changed" FunPtr C_SimplePopoverChangedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data SimplePopoverChangedSignalInfo
instance SignalInfo SimplePopoverChangedSignalInfo where
type HaskellCallbackType SimplePopoverChangedSignalInfo = SimplePopoverChangedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_SimplePopoverChangedCallback cb
cb'' <- mk_SimplePopoverChangedCallback cb'
connectSignalFunPtr obj "changed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover::changed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#g:signal:changed"})
#endif
type SimplePopoverInsertTextCallback =
Word32
-> T.Text
-> Word32
-> IO Bool
type C_SimplePopoverInsertTextCallback =
Ptr SimplePopover ->
Word32 ->
CString ->
Word32 ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_SimplePopoverInsertTextCallback :: C_SimplePopoverInsertTextCallback -> IO (FunPtr C_SimplePopoverInsertTextCallback)
wrap_SimplePopoverInsertTextCallback ::
GObject a => (a -> SimplePopoverInsertTextCallback) ->
C_SimplePopoverInsertTextCallback
wrap_SimplePopoverInsertTextCallback :: forall a.
GObject a =>
(a -> SimplePopoverInsertTextCallback)
-> C_SimplePopoverInsertTextCallback
wrap_SimplePopoverInsertTextCallback a -> SimplePopoverInsertTextCallback
gi'cb Ptr SimplePopover
gi'selfPtr Word32
position CString
chars Word32
nChars Ptr ()
_ = do
Text
chars' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
chars
Bool
result <- Ptr SimplePopover -> (SimplePopover -> IO Bool) -> IO Bool
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr SimplePopover
gi'selfPtr ((SimplePopover -> IO Bool) -> IO Bool)
-> (SimplePopover -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \SimplePopover
gi'self -> a -> SimplePopoverInsertTextCallback
gi'cb (SimplePopover -> a
forall a b. Coercible a b => a -> b
Coerce.coerce SimplePopover
gi'self) Word32
position Text
chars' Word32
nChars
let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
result
CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onSimplePopoverInsertText :: (IsSimplePopover a, MonadIO m) => a -> ((?self :: a) => SimplePopoverInsertTextCallback) -> m SignalHandlerId
onSimplePopoverInsertText :: forall a (m :: * -> *).
(IsSimplePopover a, MonadIO m) =>
a
-> ((?self::a) => SimplePopoverInsertTextCallback)
-> m SignalHandlerId
onSimplePopoverInsertText a
obj (?self::a) => SimplePopoverInsertTextCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> SimplePopoverInsertTextCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SimplePopoverInsertTextCallback
SimplePopoverInsertTextCallback
cb
let wrapped' :: C_SimplePopoverInsertTextCallback
wrapped' = (a -> SimplePopoverInsertTextCallback)
-> C_SimplePopoverInsertTextCallback
forall a.
GObject a =>
(a -> SimplePopoverInsertTextCallback)
-> C_SimplePopoverInsertTextCallback
wrap_SimplePopoverInsertTextCallback a -> SimplePopoverInsertTextCallback
wrapped
FunPtr C_SimplePopoverInsertTextCallback
wrapped'' <- C_SimplePopoverInsertTextCallback
-> IO (FunPtr C_SimplePopoverInsertTextCallback)
mk_SimplePopoverInsertTextCallback C_SimplePopoverInsertTextCallback
wrapped'
a
-> Text
-> FunPtr C_SimplePopoverInsertTextCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"insert-text" FunPtr C_SimplePopoverInsertTextCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterSimplePopoverInsertText :: (IsSimplePopover a, MonadIO m) => a -> ((?self :: a) => SimplePopoverInsertTextCallback) -> m SignalHandlerId
afterSimplePopoverInsertText :: forall a (m :: * -> *).
(IsSimplePopover a, MonadIO m) =>
a
-> ((?self::a) => SimplePopoverInsertTextCallback)
-> m SignalHandlerId
afterSimplePopoverInsertText a
obj (?self::a) => SimplePopoverInsertTextCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> SimplePopoverInsertTextCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SimplePopoverInsertTextCallback
SimplePopoverInsertTextCallback
cb
let wrapped' :: C_SimplePopoverInsertTextCallback
wrapped' = (a -> SimplePopoverInsertTextCallback)
-> C_SimplePopoverInsertTextCallback
forall a.
GObject a =>
(a -> SimplePopoverInsertTextCallback)
-> C_SimplePopoverInsertTextCallback
wrap_SimplePopoverInsertTextCallback a -> SimplePopoverInsertTextCallback
wrapped
FunPtr C_SimplePopoverInsertTextCallback
wrapped'' <- C_SimplePopoverInsertTextCallback
-> IO (FunPtr C_SimplePopoverInsertTextCallback)
mk_SimplePopoverInsertTextCallback C_SimplePopoverInsertTextCallback
wrapped'
a
-> Text
-> FunPtr C_SimplePopoverInsertTextCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"insert-text" FunPtr C_SimplePopoverInsertTextCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data SimplePopoverInsertTextSignalInfo
instance SignalInfo SimplePopoverInsertTextSignalInfo where
type HaskellCallbackType SimplePopoverInsertTextSignalInfo = SimplePopoverInsertTextCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_SimplePopoverInsertTextCallback cb
cb'' <- mk_SimplePopoverInsertTextCallback cb'
connectSignalFunPtr obj "insert-text" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover::insert-text"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#g:signal:insertText"})
#endif
getSimplePopoverButtonText :: (MonadIO m, IsSimplePopover o) => o -> m T.Text
getSimplePopoverButtonText :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> m Text
getSimplePopoverButtonText o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"getSimplePopoverButtonText" (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
"button-text"
setSimplePopoverButtonText :: (MonadIO m, IsSimplePopover o) => o -> T.Text -> m ()
setSimplePopoverButtonText :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> Text -> m ()
setSimplePopoverButtonText o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"button-text" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructSimplePopoverButtonText :: (IsSimplePopover o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSimplePopoverButtonText :: forall o (m :: * -> *).
(IsSimplePopover o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSimplePopoverButtonText 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
"button-text" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data SimplePopoverButtonTextPropertyInfo
instance AttrInfo SimplePopoverButtonTextPropertyInfo where
type AttrAllowedOps SimplePopoverButtonTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint SimplePopoverButtonTextPropertyInfo = IsSimplePopover
type AttrSetTypeConstraint SimplePopoverButtonTextPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint SimplePopoverButtonTextPropertyInfo = (~) T.Text
type AttrTransferType SimplePopoverButtonTextPropertyInfo = T.Text
type AttrGetType SimplePopoverButtonTextPropertyInfo = T.Text
type AttrLabel SimplePopoverButtonTextPropertyInfo = "button-text"
type AttrOrigin SimplePopoverButtonTextPropertyInfo = SimplePopover
attrGet = getSimplePopoverButtonText
attrSet = setSimplePopoverButtonText
attrTransfer _ v = do
return v
attrConstruct = constructSimplePopoverButtonText
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.buttonText"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#g:attr:buttonText"
})
#endif
getSimplePopoverMessage :: (MonadIO m, IsSimplePopover o) => o -> m T.Text
getSimplePopoverMessage :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> m Text
getSimplePopoverMessage o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"getSimplePopoverMessage" (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
"message"
setSimplePopoverMessage :: (MonadIO m, IsSimplePopover o) => o -> T.Text -> m ()
setSimplePopoverMessage :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> Text -> m ()
setSimplePopoverMessage o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"message" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructSimplePopoverMessage :: (IsSimplePopover o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSimplePopoverMessage :: forall o (m :: * -> *).
(IsSimplePopover o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSimplePopoverMessage 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
"message" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data SimplePopoverMessagePropertyInfo
instance AttrInfo SimplePopoverMessagePropertyInfo where
type AttrAllowedOps SimplePopoverMessagePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint SimplePopoverMessagePropertyInfo = IsSimplePopover
type AttrSetTypeConstraint SimplePopoverMessagePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint SimplePopoverMessagePropertyInfo = (~) T.Text
type AttrTransferType SimplePopoverMessagePropertyInfo = T.Text
type AttrGetType SimplePopoverMessagePropertyInfo = T.Text
type AttrLabel SimplePopoverMessagePropertyInfo = "message"
type AttrOrigin SimplePopoverMessagePropertyInfo = SimplePopover
attrGet = getSimplePopoverMessage
attrSet = setSimplePopoverMessage
attrTransfer _ v = do
return v
attrConstruct = constructSimplePopoverMessage
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.message"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#g:attr:message"
})
#endif
getSimplePopoverReady :: (MonadIO m, IsSimplePopover o) => o -> m Bool
getSimplePopoverReady :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> m Bool
getSimplePopoverReady o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"ready"
setSimplePopoverReady :: (MonadIO m, IsSimplePopover o) => o -> Bool -> m ()
setSimplePopoverReady :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> Bool -> m ()
setSimplePopoverReady o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"ready" Bool
val
constructSimplePopoverReady :: (IsSimplePopover o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSimplePopoverReady :: forall o (m :: * -> *).
(IsSimplePopover o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSimplePopoverReady Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"ready" Bool
val
#if defined(ENABLE_OVERLOADING)
data SimplePopoverReadyPropertyInfo
instance AttrInfo SimplePopoverReadyPropertyInfo where
type AttrAllowedOps SimplePopoverReadyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint SimplePopoverReadyPropertyInfo = IsSimplePopover
type AttrSetTypeConstraint SimplePopoverReadyPropertyInfo = (~) Bool
type AttrTransferTypeConstraint SimplePopoverReadyPropertyInfo = (~) Bool
type AttrTransferType SimplePopoverReadyPropertyInfo = Bool
type AttrGetType SimplePopoverReadyPropertyInfo = Bool
type AttrLabel SimplePopoverReadyPropertyInfo = "ready"
type AttrOrigin SimplePopoverReadyPropertyInfo = SimplePopover
attrGet = getSimplePopoverReady
attrSet = setSimplePopoverReady
attrTransfer _ v = do
return v
attrConstruct = constructSimplePopoverReady
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.ready"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#g:attr:ready"
})
#endif
getSimplePopoverText :: (MonadIO m, IsSimplePopover o) => o -> m T.Text
getSimplePopoverText :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> m Text
getSimplePopoverText o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"getSimplePopoverText" (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
"text"
setSimplePopoverText :: (MonadIO m, IsSimplePopover o) => o -> T.Text -> m ()
setSimplePopoverText :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> Text -> m ()
setSimplePopoverText o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"text" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructSimplePopoverText :: (IsSimplePopover o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSimplePopoverText :: forall o (m :: * -> *).
(IsSimplePopover o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSimplePopoverText 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
"text" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data SimplePopoverTextPropertyInfo
instance AttrInfo SimplePopoverTextPropertyInfo where
type AttrAllowedOps SimplePopoverTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint SimplePopoverTextPropertyInfo = IsSimplePopover
type AttrSetTypeConstraint SimplePopoverTextPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint SimplePopoverTextPropertyInfo = (~) T.Text
type AttrTransferType SimplePopoverTextPropertyInfo = T.Text
type AttrGetType SimplePopoverTextPropertyInfo = T.Text
type AttrLabel SimplePopoverTextPropertyInfo = "text"
type AttrOrigin SimplePopoverTextPropertyInfo = SimplePopover
attrGet = getSimplePopoverText
attrSet = setSimplePopoverText
attrTransfer _ v = do
return v
attrConstruct = constructSimplePopoverText
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.text"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#g:attr:text"
})
#endif
getSimplePopoverTitle :: (MonadIO m, IsSimplePopover o) => o -> m T.Text
getSimplePopoverTitle :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> m Text
getSimplePopoverTitle o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"getSimplePopoverTitle" (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"
setSimplePopoverTitle :: (MonadIO m, IsSimplePopover o) => o -> T.Text -> m ()
setSimplePopoverTitle :: forall (m :: * -> *) o.
(MonadIO m, IsSimplePopover o) =>
o -> Text -> m ()
setSimplePopoverTitle o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> 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)
constructSimplePopoverTitle :: (IsSimplePopover o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSimplePopoverTitle :: forall o (m :: * -> *).
(IsSimplePopover o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSimplePopoverTitle 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
"title" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data SimplePopoverTitlePropertyInfo
instance AttrInfo SimplePopoverTitlePropertyInfo where
type AttrAllowedOps SimplePopoverTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint SimplePopoverTitlePropertyInfo = IsSimplePopover
type AttrSetTypeConstraint SimplePopoverTitlePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint SimplePopoverTitlePropertyInfo = (~) T.Text
type AttrTransferType SimplePopoverTitlePropertyInfo = T.Text
type AttrGetType SimplePopoverTitlePropertyInfo = T.Text
type AttrLabel SimplePopoverTitlePropertyInfo = "title"
type AttrOrigin SimplePopoverTitlePropertyInfo = SimplePopover
attrGet = getSimplePopoverTitle
attrSet = setSimplePopoverTitle
attrTransfer _ v = do
return v
attrConstruct = constructSimplePopoverTitle
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.title"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#g:attr:title"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SimplePopover
type instance O.AttributeList SimplePopover = SimplePopoverAttributeList
type SimplePopoverAttributeList = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("buttonText", SimplePopoverButtonTextPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("constrainTo", Gtk.Popover.PopoverConstrainToPropertyInfo), '("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), '("message", SimplePopoverMessagePropertyInfo), '("modal", Gtk.Popover.PopoverModalPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("pointingTo", Gtk.Popover.PopoverPointingToPropertyInfo), '("position", Gtk.Popover.PopoverPositionPropertyInfo), '("ready", SimplePopoverReadyPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("relativeTo", Gtk.Popover.PopoverRelativeToPropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("text", SimplePopoverTextPropertyInfo), '("title", SimplePopoverTitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("transitionsEnabled", Gtk.Popover.PopoverTransitionsEnabledPropertyInfo), '("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)
simplePopoverButtonText :: AttrLabelProxy "buttonText"
simplePopoverButtonText = AttrLabelProxy
simplePopoverMessage :: AttrLabelProxy "message"
simplePopoverMessage = AttrLabelProxy
simplePopoverReady :: AttrLabelProxy "ready"
simplePopoverReady = AttrLabelProxy
simplePopoverText :: AttrLabelProxy "text"
simplePopoverText = AttrLabelProxy
simplePopoverTitle :: AttrLabelProxy "title"
simplePopoverTitle = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SimplePopover = SimplePopoverSignalList
type SimplePopoverSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("activate", SimplePopoverActivateSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("changed", SimplePopoverChangedSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("closed", Gtk.Popover.PopoverClosedSignalInfo), '("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), '("insertText", SimplePopoverInsertTextSignalInfo), '("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), '("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), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_simple_popover_new" dzl_simple_popover_new ::
IO (Ptr SimplePopover)
simplePopoverNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m SimplePopover
simplePopoverNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m SimplePopover
simplePopoverNew = IO SimplePopover -> m SimplePopover
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SimplePopover -> m SimplePopover)
-> IO SimplePopover -> m SimplePopover
forall a b. (a -> b) -> a -> b
$ do
Ptr SimplePopover
result <- IO (Ptr SimplePopover)
dzl_simple_popover_new
Text -> Ptr SimplePopover -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"simplePopoverNew" Ptr SimplePopover
result
SimplePopover
result' <- ((ManagedPtr SimplePopover -> SimplePopover)
-> Ptr SimplePopover -> IO SimplePopover
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr SimplePopover -> SimplePopover
SimplePopover) Ptr SimplePopover
result
SimplePopover -> IO SimplePopover
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SimplePopover
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "dzl_simple_popover_get_button_text" dzl_simple_popover_get_button_text ::
Ptr SimplePopover ->
IO CString
simplePopoverGetButtonText ::
(B.CallStack.HasCallStack, MonadIO m, IsSimplePopover a) =>
a
-> m T.Text
simplePopoverGetButtonText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimplePopover a) =>
a -> m Text
simplePopoverGetButtonText 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 SimplePopover
self' <- a -> IO (Ptr SimplePopover)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr SimplePopover -> IO CString
dzl_simple_popover_get_button_text Ptr SimplePopover
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"simplePopoverGetButtonText" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText 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 SimplePopoverGetButtonTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSimplePopover a) => O.OverloadedMethod SimplePopoverGetButtonTextMethodInfo a signature where
overloadedMethod = simplePopoverGetButtonText
instance O.OverloadedMethodInfo SimplePopoverGetButtonTextMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.simplePopoverGetButtonText",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#v:simplePopoverGetButtonText"
})
#endif
foreign import ccall "dzl_simple_popover_get_message" dzl_simple_popover_get_message ::
Ptr SimplePopover ->
IO CString
simplePopoverGetMessage ::
(B.CallStack.HasCallStack, MonadIO m, IsSimplePopover a) =>
a
-> m T.Text
simplePopoverGetMessage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimplePopover a) =>
a -> m Text
simplePopoverGetMessage 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 SimplePopover
self' <- a -> IO (Ptr SimplePopover)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr SimplePopover -> IO CString
dzl_simple_popover_get_message Ptr SimplePopover
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"simplePopoverGetMessage" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText 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 SimplePopoverGetMessageMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSimplePopover a) => O.OverloadedMethod SimplePopoverGetMessageMethodInfo a signature where
overloadedMethod = simplePopoverGetMessage
instance O.OverloadedMethodInfo SimplePopoverGetMessageMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.simplePopoverGetMessage",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#v:simplePopoverGetMessage"
})
#endif
foreign import ccall "dzl_simple_popover_get_ready" dzl_simple_popover_get_ready ::
Ptr SimplePopover ->
IO CInt
simplePopoverGetReady ::
(B.CallStack.HasCallStack, MonadIO m, IsSimplePopover a) =>
a
-> m Bool
simplePopoverGetReady :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimplePopover a) =>
a -> m Bool
simplePopoverGetReady a
self = IO Bool -> m Bool
forall a. IO a -> m a
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 SimplePopover
self' <- a -> IO (Ptr SimplePopover)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CInt
result <- Ptr SimplePopover -> IO CInt
dzl_simple_popover_get_ready Ptr SimplePopover
self'
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
self
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SimplePopoverGetReadyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSimplePopover a) => O.OverloadedMethod SimplePopoverGetReadyMethodInfo a signature where
overloadedMethod = simplePopoverGetReady
instance O.OverloadedMethodInfo SimplePopoverGetReadyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.simplePopoverGetReady",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#v:simplePopoverGetReady"
})
#endif
foreign import ccall "dzl_simple_popover_get_text" dzl_simple_popover_get_text ::
Ptr SimplePopover ->
IO CString
simplePopoverGetText ::
(B.CallStack.HasCallStack, MonadIO m, IsSimplePopover a) =>
a
-> m T.Text
simplePopoverGetText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimplePopover a) =>
a -> m Text
simplePopoverGetText 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 SimplePopover
self' <- a -> IO (Ptr SimplePopover)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr SimplePopover -> IO CString
dzl_simple_popover_get_text Ptr SimplePopover
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"simplePopoverGetText" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText 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 SimplePopoverGetTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSimplePopover a) => O.OverloadedMethod SimplePopoverGetTextMethodInfo a signature where
overloadedMethod = simplePopoverGetText
instance O.OverloadedMethodInfo SimplePopoverGetTextMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.simplePopoverGetText",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#v:simplePopoverGetText"
})
#endif
foreign import ccall "dzl_simple_popover_get_title" dzl_simple_popover_get_title ::
Ptr SimplePopover ->
IO CString
simplePopoverGetTitle ::
(B.CallStack.HasCallStack, MonadIO m, IsSimplePopover a) =>
a
-> m T.Text
simplePopoverGetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimplePopover a) =>
a -> m Text
simplePopoverGetTitle 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 SimplePopover
self' <- a -> IO (Ptr SimplePopover)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr SimplePopover -> IO CString
dzl_simple_popover_get_title Ptr SimplePopover
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"simplePopoverGetTitle" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText 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 SimplePopoverGetTitleMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSimplePopover a) => O.OverloadedMethod SimplePopoverGetTitleMethodInfo a signature where
overloadedMethod = simplePopoverGetTitle
instance O.OverloadedMethodInfo SimplePopoverGetTitleMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.simplePopoverGetTitle",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#v:simplePopoverGetTitle"
})
#endif
foreign import ccall "dzl_simple_popover_set_button_text" dzl_simple_popover_set_button_text ::
Ptr SimplePopover ->
CString ->
IO ()
simplePopoverSetButtonText ::
(B.CallStack.HasCallStack, MonadIO m, IsSimplePopover a) =>
a
-> T.Text
-> m ()
simplePopoverSetButtonText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimplePopover a) =>
a -> Text -> m ()
simplePopoverSetButtonText a
self Text
buttonText = 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 SimplePopover
self' <- a -> IO (Ptr SimplePopover)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
buttonText' <- Text -> IO CString
textToCString Text
buttonText
Ptr SimplePopover -> CString -> IO ()
dzl_simple_popover_set_button_text Ptr SimplePopover
self' CString
buttonText'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
buttonText'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SimplePopoverSetButtonTextMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSimplePopover a) => O.OverloadedMethod SimplePopoverSetButtonTextMethodInfo a signature where
overloadedMethod = simplePopoverSetButtonText
instance O.OverloadedMethodInfo SimplePopoverSetButtonTextMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.simplePopoverSetButtonText",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#v:simplePopoverSetButtonText"
})
#endif
foreign import ccall "dzl_simple_popover_set_message" dzl_simple_popover_set_message ::
Ptr SimplePopover ->
CString ->
IO ()
simplePopoverSetMessage ::
(B.CallStack.HasCallStack, MonadIO m, IsSimplePopover a) =>
a
-> T.Text
-> m ()
simplePopoverSetMessage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimplePopover a) =>
a -> Text -> m ()
simplePopoverSetMessage a
self Text
message = 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 SimplePopover
self' <- a -> IO (Ptr SimplePopover)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
message' <- Text -> IO CString
textToCString Text
message
Ptr SimplePopover -> CString -> IO ()
dzl_simple_popover_set_message Ptr SimplePopover
self' CString
message'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
message'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SimplePopoverSetMessageMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSimplePopover a) => O.OverloadedMethod SimplePopoverSetMessageMethodInfo a signature where
overloadedMethod = simplePopoverSetMessage
instance O.OverloadedMethodInfo SimplePopoverSetMessageMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.simplePopoverSetMessage",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#v:simplePopoverSetMessage"
})
#endif
foreign import ccall "dzl_simple_popover_set_ready" dzl_simple_popover_set_ready ::
Ptr SimplePopover ->
CInt ->
IO ()
simplePopoverSetReady ::
(B.CallStack.HasCallStack, MonadIO m, IsSimplePopover a) =>
a
-> Bool
-> m ()
simplePopoverSetReady :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimplePopover a) =>
a -> Bool -> m ()
simplePopoverSetReady a
self Bool
ready = 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 SimplePopover
self' <- a -> IO (Ptr SimplePopover)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
let ready' :: CInt
ready' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
ready
Ptr SimplePopover -> CInt -> IO ()
dzl_simple_popover_set_ready Ptr SimplePopover
self' CInt
ready'
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 SimplePopoverSetReadyMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSimplePopover a) => O.OverloadedMethod SimplePopoverSetReadyMethodInfo a signature where
overloadedMethod = simplePopoverSetReady
instance O.OverloadedMethodInfo SimplePopoverSetReadyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.simplePopoverSetReady",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#v:simplePopoverSetReady"
})
#endif
foreign import ccall "dzl_simple_popover_set_text" dzl_simple_popover_set_text ::
Ptr SimplePopover ->
CString ->
IO ()
simplePopoverSetText ::
(B.CallStack.HasCallStack, MonadIO m, IsSimplePopover a) =>
a
-> T.Text
-> m ()
simplePopoverSetText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimplePopover a) =>
a -> Text -> m ()
simplePopoverSetText a
self Text
text = 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 SimplePopover
self' <- a -> IO (Ptr SimplePopover)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
text' <- Text -> IO CString
textToCString Text
text
Ptr SimplePopover -> CString -> IO ()
dzl_simple_popover_set_text Ptr SimplePopover
self' CString
text'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SimplePopoverSetTextMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSimplePopover a) => O.OverloadedMethod SimplePopoverSetTextMethodInfo a signature where
overloadedMethod = simplePopoverSetText
instance O.OverloadedMethodInfo SimplePopoverSetTextMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.simplePopoverSetText",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#v:simplePopoverSetText"
})
#endif
foreign import ccall "dzl_simple_popover_set_title" dzl_simple_popover_set_title ::
Ptr SimplePopover ->
CString ->
IO ()
simplePopoverSetTitle ::
(B.CallStack.HasCallStack, MonadIO m, IsSimplePopover a) =>
a
-> T.Text
-> m ()
simplePopoverSetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSimplePopover a) =>
a -> Text -> m ()
simplePopoverSetTitle a
self Text
title = 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 SimplePopover
self' <- a -> IO (Ptr SimplePopover)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
title' <- Text -> IO CString
textToCString Text
title
Ptr SimplePopover -> CString -> IO ()
dzl_simple_popover_set_title Ptr SimplePopover
self' CString
title'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SimplePopoverSetTitleMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSimplePopover a) => O.OverloadedMethod SimplePopoverSetTitleMethodInfo a signature where
overloadedMethod = simplePopoverSetTitle
instance O.OverloadedMethodInfo SimplePopoverSetTitleMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SimplePopover.simplePopoverSetTitle",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-SimplePopover.html#v:simplePopoverSetTitle"
})
#endif