{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.Tree
(
Tree(..) ,
IsTree ,
toTree ,
#if defined(ENABLE_OVERLOADING)
ResolveTreeMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TreeAddBuilderMethodInfo ,
#endif
treeAddBuilder ,
#if defined(ENABLE_OVERLOADING)
TreeExpandToNodeMethodInfo ,
#endif
treeExpandToNode ,
#if defined(ENABLE_OVERLOADING)
TreeFindChildNodeMethodInfo ,
#endif
treeFindChildNode ,
#if defined(ENABLE_OVERLOADING)
TreeFindCustomMethodInfo ,
#endif
treeFindCustom ,
#if defined(ENABLE_OVERLOADING)
TreeFindItemMethodInfo ,
#endif
treeFindItem ,
#if defined(ENABLE_OVERLOADING)
TreeGetContextMenuMethodInfo ,
#endif
treeGetContextMenu ,
#if defined(ENABLE_OVERLOADING)
TreeGetRootMethodInfo ,
#endif
treeGetRoot ,
#if defined(ENABLE_OVERLOADING)
TreeGetSelectedMethodInfo ,
#endif
treeGetSelected ,
#if defined(ENABLE_OVERLOADING)
TreeGetShowIconsMethodInfo ,
#endif
treeGetShowIcons ,
#if defined(ENABLE_OVERLOADING)
TreeRebuildMethodInfo ,
#endif
treeRebuild ,
#if defined(ENABLE_OVERLOADING)
TreeRemoveBuilderMethodInfo ,
#endif
treeRemoveBuilder ,
#if defined(ENABLE_OVERLOADING)
TreeScrollToNodeMethodInfo ,
#endif
treeScrollToNode ,
#if defined(ENABLE_OVERLOADING)
TreeSetContextMenuMethodInfo ,
#endif
treeSetContextMenu ,
#if defined(ENABLE_OVERLOADING)
TreeSetFilterMethodInfo ,
#endif
treeSetFilter ,
#if defined(ENABLE_OVERLOADING)
TreeSetRootMethodInfo ,
#endif
treeSetRoot ,
#if defined(ENABLE_OVERLOADING)
TreeSetShowIconsMethodInfo ,
#endif
treeSetShowIcons ,
#if defined(ENABLE_OVERLOADING)
TreeUnselectAllMethodInfo ,
#endif
treeUnselectAll ,
#if defined(ENABLE_OVERLOADING)
TreeAlwaysExpandPropertyInfo ,
#endif
constructTreeAlwaysExpand ,
getTreeAlwaysExpand ,
#if defined(ENABLE_OVERLOADING)
treeAlwaysExpand ,
#endif
#if defined(ENABLE_OVERLOADING)
TreeContextMenuPropertyInfo ,
#endif
constructTreeContextMenu ,
getTreeContextMenu ,
setTreeContextMenu ,
#if defined(ENABLE_OVERLOADING)
treeContextMenu ,
#endif
#if defined(ENABLE_OVERLOADING)
TreeRootPropertyInfo ,
#endif
constructTreeRoot ,
getTreeRoot ,
setTreeRoot ,
#if defined(ENABLE_OVERLOADING)
treeRoot ,
#endif
#if defined(ENABLE_OVERLOADING)
TreeSelectionPropertyInfo ,
#endif
clearTreeSelection ,
constructTreeSelection ,
getTreeSelection ,
setTreeSelection ,
#if defined(ENABLE_OVERLOADING)
treeSelection ,
#endif
#if defined(ENABLE_OVERLOADING)
TreeShowIconsPropertyInfo ,
#endif
constructTreeShowIcons ,
getTreeShowIcons ,
setTreeShowIcons ,
#if defined(ENABLE_OVERLOADING)
treeShowIcons ,
#endif
TreeActionCallback ,
#if defined(ENABLE_OVERLOADING)
TreeActionSignalInfo ,
#endif
afterTreeAction ,
onTreeAction ,
TreePopulatePopupCallback ,
#if defined(ENABLE_OVERLOADING)
TreePopulatePopupSignalInfo ,
#endif
afterTreePopulatePopup ,
onTreePopulatePopup ,
) 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.Dazzle.Callbacks as Dazzle.Callbacks
import {-# SOURCE #-} qualified GI.Dazzle.Objects.TreeBuilder as Dazzle.TreeBuilder
import {-# SOURCE #-} qualified GI.Dazzle.Objects.TreeNode as Dazzle.TreeNode
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Interfaces.Scrollable as Gtk.Scrollable
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.TreeView as Gtk.TreeView
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype Tree = Tree (SP.ManagedPtr Tree)
deriving (Tree -> Tree -> Bool
(Tree -> Tree -> Bool) -> (Tree -> Tree -> Bool) -> Eq Tree
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Tree -> Tree -> Bool
== :: Tree -> Tree -> Bool
$c/= :: Tree -> Tree -> Bool
/= :: Tree -> Tree -> Bool
Eq)
instance SP.ManagedPtrNewtype Tree where
toManagedPtr :: Tree -> ManagedPtr Tree
toManagedPtr (Tree ManagedPtr Tree
p) = ManagedPtr Tree
p
foreign import ccall "dzl_tree_get_type"
c_dzl_tree_get_type :: IO B.Types.GType
instance B.Types.TypedObject Tree where
glibType :: IO GType
glibType = IO GType
c_dzl_tree_get_type
instance B.Types.GObject Tree
class (SP.GObject o, O.IsDescendantOf Tree o) => IsTree o
instance (SP.GObject o, O.IsDescendantOf Tree o) => IsTree o
instance O.HasParentTypes Tree
type instance O.ParentTypes Tree = '[Gtk.TreeView.TreeView, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, Gtk.Scrollable.Scrollable]
toTree :: (MIO.MonadIO m, IsTree o) => o -> m Tree
toTree :: forall (m :: * -> *) o. (MonadIO m, IsTree o) => o -> m Tree
toTree = IO Tree -> m Tree
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Tree -> m Tree) -> (o -> IO Tree) -> o -> m Tree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Tree -> Tree) -> o -> IO Tree
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Tree -> Tree
Tree
instance B.GValue.IsGValue (Maybe Tree) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_tree_get_type
gvalueSet_ :: Ptr GValue -> Maybe Tree -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Tree
P.Nothing = Ptr GValue -> Ptr Tree -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Tree
forall a. Ptr a
FP.nullPtr :: FP.Ptr Tree)
gvalueSet_ Ptr GValue
gv (P.Just Tree
obj) = Tree -> (Ptr Tree -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Tree
obj (Ptr GValue -> Ptr Tree -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Tree)
gvalueGet_ Ptr GValue
gv = do
Ptr Tree
ptr <- Ptr GValue -> IO (Ptr Tree)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Tree)
if Ptr Tree
ptr Ptr Tree -> Ptr Tree -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Tree
forall a. Ptr a
FP.nullPtr
then Tree -> Maybe Tree
forall a. a -> Maybe a
P.Just (Tree -> Maybe Tree) -> IO Tree -> IO (Maybe Tree)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Tree -> Tree) -> Ptr Tree -> IO Tree
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Tree -> Tree
Tree Ptr Tree
ptr
else Maybe Tree -> IO (Maybe Tree)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Tree
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveTreeMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveTreeMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveTreeMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolveTreeMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveTreeMethod "addBuilder" o = TreeAddBuilderMethodInfo
ResolveTreeMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveTreeMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveTreeMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveTreeMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveTreeMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveTreeMethod "appendColumn" o = Gtk.TreeView.TreeViewAppendColumnMethodInfo
ResolveTreeMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveTreeMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveTreeMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveTreeMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolveTreeMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveTreeMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolveTreeMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolveTreeMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolveTreeMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolveTreeMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolveTreeMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveTreeMethod "collapseAll" o = Gtk.TreeView.TreeViewCollapseAllMethodInfo
ResolveTreeMethod "collapseRow" o = Gtk.TreeView.TreeViewCollapseRowMethodInfo
ResolveTreeMethod "columnsAutosize" o = Gtk.TreeView.TreeViewColumnsAutosizeMethodInfo
ResolveTreeMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveTreeMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveTreeMethod "convertBinWindowToTreeCoords" o = Gtk.TreeView.TreeViewConvertBinWindowToTreeCoordsMethodInfo
ResolveTreeMethod "convertBinWindowToWidgetCoords" o = Gtk.TreeView.TreeViewConvertBinWindowToWidgetCoordsMethodInfo
ResolveTreeMethod "convertTreeToBinWindowCoords" o = Gtk.TreeView.TreeViewConvertTreeToBinWindowCoordsMethodInfo
ResolveTreeMethod "convertTreeToWidgetCoords" o = Gtk.TreeView.TreeViewConvertTreeToWidgetCoordsMethodInfo
ResolveTreeMethod "convertWidgetToBinWindowCoords" o = Gtk.TreeView.TreeViewConvertWidgetToBinWindowCoordsMethodInfo
ResolveTreeMethod "convertWidgetToTreeCoords" o = Gtk.TreeView.TreeViewConvertWidgetToTreeCoordsMethodInfo
ResolveTreeMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveTreeMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveTreeMethod "createRowDragIcon" o = Gtk.TreeView.TreeViewCreateRowDragIconMethodInfo
ResolveTreeMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveTreeMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveTreeMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveTreeMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveTreeMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveTreeMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveTreeMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveTreeMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveTreeMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveTreeMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveTreeMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveTreeMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveTreeMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveTreeMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveTreeMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveTreeMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveTreeMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveTreeMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveTreeMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveTreeMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveTreeMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveTreeMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveTreeMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveTreeMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveTreeMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveTreeMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveTreeMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveTreeMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveTreeMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveTreeMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveTreeMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveTreeMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveTreeMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveTreeMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveTreeMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveTreeMethod "enableModelDragDest" o = Gtk.TreeView.TreeViewEnableModelDragDestMethodInfo
ResolveTreeMethod "enableModelDragSource" o = Gtk.TreeView.TreeViewEnableModelDragSourceMethodInfo
ResolveTreeMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveTreeMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveTreeMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveTreeMethod "expandAll" o = Gtk.TreeView.TreeViewExpandAllMethodInfo
ResolveTreeMethod "expandRow" o = Gtk.TreeView.TreeViewExpandRowMethodInfo
ResolveTreeMethod "expandToNode" o = TreeExpandToNodeMethodInfo
ResolveTreeMethod "expandToPath" o = Gtk.TreeView.TreeViewExpandToPathMethodInfo
ResolveTreeMethod "findChildNode" o = TreeFindChildNodeMethodInfo
ResolveTreeMethod "findCustom" o = TreeFindCustomMethodInfo
ResolveTreeMethod "findItem" o = TreeFindItemMethodInfo
ResolveTreeMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolveTreeMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveTreeMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolveTreeMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveTreeMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveTreeMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveTreeMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveTreeMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveTreeMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveTreeMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveTreeMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveTreeMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveTreeMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveTreeMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveTreeMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveTreeMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveTreeMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveTreeMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveTreeMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveTreeMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveTreeMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveTreeMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveTreeMethod "insertColumn" o = Gtk.TreeView.TreeViewInsertColumnMethodInfo
ResolveTreeMethod "insertColumnWithDataFunc" o = Gtk.TreeView.TreeViewInsertColumnWithDataFuncMethodInfo
ResolveTreeMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveTreeMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveTreeMethod "isBlankAtPos" o = Gtk.TreeView.TreeViewIsBlankAtPosMethodInfo
ResolveTreeMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveTreeMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveTreeMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveTreeMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveTreeMethod "isRubberBandingActive" o = Gtk.TreeView.TreeViewIsRubberBandingActiveMethodInfo
ResolveTreeMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveTreeMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveTreeMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveTreeMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveTreeMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveTreeMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveTreeMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveTreeMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveTreeMethod "mapExpandedRows" o = Gtk.TreeView.TreeViewMapExpandedRowsMethodInfo
ResolveTreeMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveTreeMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveTreeMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveTreeMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveTreeMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveTreeMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveTreeMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveTreeMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveTreeMethod "moveColumnAfter" o = Gtk.TreeView.TreeViewMoveColumnAfterMethodInfo
ResolveTreeMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveTreeMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveTreeMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveTreeMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveTreeMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveTreeMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveTreeMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveTreeMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveTreeMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveTreeMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolveTreeMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveTreeMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveTreeMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveTreeMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveTreeMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveTreeMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveTreeMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveTreeMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveTreeMethod "rebuild" o = TreeRebuildMethodInfo
ResolveTreeMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveTreeMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveTreeMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveTreeMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveTreeMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolveTreeMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveTreeMethod "removeBuilder" o = TreeRemoveBuilderMethodInfo
ResolveTreeMethod "removeColumn" o = Gtk.TreeView.TreeViewRemoveColumnMethodInfo
ResolveTreeMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveTreeMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveTreeMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveTreeMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveTreeMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveTreeMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveTreeMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveTreeMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolveTreeMethod "rowActivated" o = Gtk.TreeView.TreeViewRowActivatedMethodInfo
ResolveTreeMethod "rowExpanded" o = Gtk.TreeView.TreeViewRowExpandedMethodInfo
ResolveTreeMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveTreeMethod "scrollToCell" o = Gtk.TreeView.TreeViewScrollToCellMethodInfo
ResolveTreeMethod "scrollToNode" o = TreeScrollToNodeMethodInfo
ResolveTreeMethod "scrollToPoint" o = Gtk.TreeView.TreeViewScrollToPointMethodInfo
ResolveTreeMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveTreeMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveTreeMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveTreeMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveTreeMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveTreeMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveTreeMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveTreeMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveTreeMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveTreeMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveTreeMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveTreeMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveTreeMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveTreeMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveTreeMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveTreeMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveTreeMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveTreeMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveTreeMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveTreeMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveTreeMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveTreeMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveTreeMethod "unselectAll" o = TreeUnselectAllMethodInfo
ResolveTreeMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolveTreeMethod "unsetRowsDragDest" o = Gtk.TreeView.TreeViewUnsetRowsDragDestMethodInfo
ResolveTreeMethod "unsetRowsDragSource" o = Gtk.TreeView.TreeViewUnsetRowsDragSourceMethodInfo
ResolveTreeMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveTreeMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveTreeMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveTreeMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveTreeMethod "getActivateOnSingleClick" o = Gtk.TreeView.TreeViewGetActivateOnSingleClickMethodInfo
ResolveTreeMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveTreeMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveTreeMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveTreeMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveTreeMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveTreeMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveTreeMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveTreeMethod "getBackgroundArea" o = Gtk.TreeView.TreeViewGetBackgroundAreaMethodInfo
ResolveTreeMethod "getBinWindow" o = Gtk.TreeView.TreeViewGetBinWindowMethodInfo
ResolveTreeMethod "getBorder" o = Gtk.Scrollable.ScrollableGetBorderMethodInfo
ResolveTreeMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolveTreeMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveTreeMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveTreeMethod "getCellArea" o = Gtk.TreeView.TreeViewGetCellAreaMethodInfo
ResolveTreeMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveTreeMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveTreeMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolveTreeMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveTreeMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveTreeMethod "getColumn" o = Gtk.TreeView.TreeViewGetColumnMethodInfo
ResolveTreeMethod "getColumns" o = Gtk.TreeView.TreeViewGetColumnsMethodInfo
ResolveTreeMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveTreeMethod "getContextMenu" o = TreeGetContextMenuMethodInfo
ResolveTreeMethod "getCursor" o = Gtk.TreeView.TreeViewGetCursorMethodInfo
ResolveTreeMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveTreeMethod "getDestRowAtPos" o = Gtk.TreeView.TreeViewGetDestRowAtPosMethodInfo
ResolveTreeMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveTreeMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveTreeMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveTreeMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveTreeMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveTreeMethod "getDragDestRow" o = Gtk.TreeView.TreeViewGetDragDestRowMethodInfo
ResolveTreeMethod "getEnableSearch" o = Gtk.TreeView.TreeViewGetEnableSearchMethodInfo
ResolveTreeMethod "getEnableTreeLines" o = Gtk.TreeView.TreeViewGetEnableTreeLinesMethodInfo
ResolveTreeMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveTreeMethod "getExpanderColumn" o = Gtk.TreeView.TreeViewGetExpanderColumnMethodInfo
ResolveTreeMethod "getFixedHeightMode" o = Gtk.TreeView.TreeViewGetFixedHeightModeMethodInfo
ResolveTreeMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolveTreeMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolveTreeMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolveTreeMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveTreeMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolveTreeMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveTreeMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveTreeMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveTreeMethod "getGridLines" o = Gtk.TreeView.TreeViewGetGridLinesMethodInfo
ResolveTreeMethod "getHadjustment" o = Gtk.TreeView.TreeViewGetHadjustmentMethodInfo
ResolveTreeMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveTreeMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveTreeMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveTreeMethod "getHeadersClickable" o = Gtk.TreeView.TreeViewGetHeadersClickableMethodInfo
ResolveTreeMethod "getHeadersVisible" o = Gtk.TreeView.TreeViewGetHeadersVisibleMethodInfo
ResolveTreeMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveTreeMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveTreeMethod "getHoverExpand" o = Gtk.TreeView.TreeViewGetHoverExpandMethodInfo
ResolveTreeMethod "getHoverSelection" o = Gtk.TreeView.TreeViewGetHoverSelectionMethodInfo
ResolveTreeMethod "getHscrollPolicy" o = Gtk.Scrollable.ScrollableGetHscrollPolicyMethodInfo
ResolveTreeMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveTreeMethod "getLevelIndentation" o = Gtk.TreeView.TreeViewGetLevelIndentationMethodInfo
ResolveTreeMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveTreeMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveTreeMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveTreeMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveTreeMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveTreeMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveTreeMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveTreeMethod "getModel" o = Gtk.TreeView.TreeViewGetModelMethodInfo
ResolveTreeMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveTreeMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveTreeMethod "getNColumns" o = Gtk.TreeView.TreeViewGetNColumnsMethodInfo
ResolveTreeMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveTreeMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveTreeMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveTreeMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveTreeMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveTreeMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveTreeMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveTreeMethod "getPathAtPos" o = Gtk.TreeView.TreeViewGetPathAtPosMethodInfo
ResolveTreeMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolveTreeMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveTreeMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveTreeMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveTreeMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveTreeMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveTreeMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveTreeMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveTreeMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveTreeMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveTreeMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveTreeMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveTreeMethod "getReorderable" o = Gtk.TreeView.TreeViewGetReorderableMethodInfo
ResolveTreeMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveTreeMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveTreeMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolveTreeMethod "getRoot" o = TreeGetRootMethodInfo
ResolveTreeMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveTreeMethod "getRubberBanding" o = Gtk.TreeView.TreeViewGetRubberBandingMethodInfo
ResolveTreeMethod "getRulesHint" o = Gtk.TreeView.TreeViewGetRulesHintMethodInfo
ResolveTreeMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveTreeMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveTreeMethod "getSearchColumn" o = Gtk.TreeView.TreeViewGetSearchColumnMethodInfo
ResolveTreeMethod "getSearchEntry" o = Gtk.TreeView.TreeViewGetSearchEntryMethodInfo
ResolveTreeMethod "getSelected" o = TreeGetSelectedMethodInfo
ResolveTreeMethod "getSelection" o = Gtk.TreeView.TreeViewGetSelectionMethodInfo
ResolveTreeMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveTreeMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveTreeMethod "getShowExpanders" o = Gtk.TreeView.TreeViewGetShowExpandersMethodInfo
ResolveTreeMethod "getShowIcons" o = TreeGetShowIconsMethodInfo
ResolveTreeMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveTreeMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveTreeMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveTreeMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveTreeMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveTreeMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveTreeMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveTreeMethod "getTooltipColumn" o = Gtk.TreeView.TreeViewGetTooltipColumnMethodInfo
ResolveTreeMethod "getTooltipContext" o = Gtk.TreeView.TreeViewGetTooltipContextMethodInfo
ResolveTreeMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveTreeMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveTreeMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveTreeMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveTreeMethod "getVadjustment" o = Gtk.TreeView.TreeViewGetVadjustmentMethodInfo
ResolveTreeMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveTreeMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveTreeMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveTreeMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveTreeMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveTreeMethod "getVisibleRange" o = Gtk.TreeView.TreeViewGetVisibleRangeMethodInfo
ResolveTreeMethod "getVisibleRect" o = Gtk.TreeView.TreeViewGetVisibleRectMethodInfo
ResolveTreeMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveTreeMethod "getVscrollPolicy" o = Gtk.Scrollable.ScrollableGetVscrollPolicyMethodInfo
ResolveTreeMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveTreeMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveTreeMethod "setActivateOnSingleClick" o = Gtk.TreeView.TreeViewSetActivateOnSingleClickMethodInfo
ResolveTreeMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveTreeMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveTreeMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolveTreeMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveTreeMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveTreeMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveTreeMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveTreeMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveTreeMethod "setColumnDragFunction" o = Gtk.TreeView.TreeViewSetColumnDragFunctionMethodInfo
ResolveTreeMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveTreeMethod "setContextMenu" o = TreeSetContextMenuMethodInfo
ResolveTreeMethod "setCursor" o = Gtk.TreeView.TreeViewSetCursorMethodInfo
ResolveTreeMethod "setCursorOnCell" o = Gtk.TreeView.TreeViewSetCursorOnCellMethodInfo
ResolveTreeMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveTreeMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveTreeMethod "setDestroyCountFunc" o = Gtk.TreeView.TreeViewSetDestroyCountFuncMethodInfo
ResolveTreeMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveTreeMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveTreeMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveTreeMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveTreeMethod "setDragDestRow" o = Gtk.TreeView.TreeViewSetDragDestRowMethodInfo
ResolveTreeMethod "setEnableSearch" o = Gtk.TreeView.TreeViewSetEnableSearchMethodInfo
ResolveTreeMethod "setEnableTreeLines" o = Gtk.TreeView.TreeViewSetEnableTreeLinesMethodInfo
ResolveTreeMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveTreeMethod "setExpanderColumn" o = Gtk.TreeView.TreeViewSetExpanderColumnMethodInfo
ResolveTreeMethod "setFilter" o = TreeSetFilterMethodInfo
ResolveTreeMethod "setFixedHeightMode" o = Gtk.TreeView.TreeViewSetFixedHeightModeMethodInfo
ResolveTreeMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolveTreeMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolveTreeMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolveTreeMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveTreeMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolveTreeMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveTreeMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveTreeMethod "setGridLines" o = Gtk.TreeView.TreeViewSetGridLinesMethodInfo
ResolveTreeMethod "setHadjustment" o = Gtk.TreeView.TreeViewSetHadjustmentMethodInfo
ResolveTreeMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveTreeMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveTreeMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveTreeMethod "setHeadersClickable" o = Gtk.TreeView.TreeViewSetHeadersClickableMethodInfo
ResolveTreeMethod "setHeadersVisible" o = Gtk.TreeView.TreeViewSetHeadersVisibleMethodInfo
ResolveTreeMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveTreeMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveTreeMethod "setHoverExpand" o = Gtk.TreeView.TreeViewSetHoverExpandMethodInfo
ResolveTreeMethod "setHoverSelection" o = Gtk.TreeView.TreeViewSetHoverSelectionMethodInfo
ResolveTreeMethod "setHscrollPolicy" o = Gtk.Scrollable.ScrollableSetHscrollPolicyMethodInfo
ResolveTreeMethod "setLevelIndentation" o = Gtk.TreeView.TreeViewSetLevelIndentationMethodInfo
ResolveTreeMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveTreeMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveTreeMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveTreeMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveTreeMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveTreeMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveTreeMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveTreeMethod "setModel" o = Gtk.TreeView.TreeViewSetModelMethodInfo
ResolveTreeMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveTreeMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveTreeMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveTreeMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveTreeMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveTreeMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveTreeMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveTreeMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolveTreeMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveTreeMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveTreeMethod "setReorderable" o = Gtk.TreeView.TreeViewSetReorderableMethodInfo
ResolveTreeMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolveTreeMethod "setRoot" o = TreeSetRootMethodInfo
ResolveTreeMethod "setRowSeparatorFunc" o = Gtk.TreeView.TreeViewSetRowSeparatorFuncMethodInfo
ResolveTreeMethod "setRubberBanding" o = Gtk.TreeView.TreeViewSetRubberBandingMethodInfo
ResolveTreeMethod "setRulesHint" o = Gtk.TreeView.TreeViewSetRulesHintMethodInfo
ResolveTreeMethod "setSearchColumn" o = Gtk.TreeView.TreeViewSetSearchColumnMethodInfo
ResolveTreeMethod "setSearchEntry" o = Gtk.TreeView.TreeViewSetSearchEntryMethodInfo
ResolveTreeMethod "setSearchEqualFunc" o = Gtk.TreeView.TreeViewSetSearchEqualFuncMethodInfo
ResolveTreeMethod "setSearchPositionFunc" o = Gtk.TreeView.TreeViewSetSearchPositionFuncMethodInfo
ResolveTreeMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveTreeMethod "setShowExpanders" o = Gtk.TreeView.TreeViewSetShowExpandersMethodInfo
ResolveTreeMethod "setShowIcons" o = TreeSetShowIconsMethodInfo
ResolveTreeMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveTreeMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveTreeMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveTreeMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveTreeMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveTreeMethod "setTooltipCell" o = Gtk.TreeView.TreeViewSetTooltipCellMethodInfo
ResolveTreeMethod "setTooltipColumn" o = Gtk.TreeView.TreeViewSetTooltipColumnMethodInfo
ResolveTreeMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveTreeMethod "setTooltipRow" o = Gtk.TreeView.TreeViewSetTooltipRowMethodInfo
ResolveTreeMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveTreeMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveTreeMethod "setVadjustment" o = Gtk.TreeView.TreeViewSetVadjustmentMethodInfo
ResolveTreeMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveTreeMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveTreeMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveTreeMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveTreeMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveTreeMethod "setVscrollPolicy" o = Gtk.Scrollable.ScrollableSetVscrollPolicyMethodInfo
ResolveTreeMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveTreeMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTreeMethod t Tree, O.OverloadedMethod info Tree p) => OL.IsLabel t (Tree -> 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 ~ ResolveTreeMethod t Tree, O.OverloadedMethod info Tree p, R.HasField t Tree p) => R.HasField t Tree p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveTreeMethod t Tree, O.OverloadedMethodInfo info Tree) => OL.IsLabel t (O.MethodProxy info Tree) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type TreeActionCallback =
T.Text
-> T.Text
-> T.Text
-> IO ()
type C_TreeActionCallback =
Ptr Tree ->
CString ->
CString ->
CString ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_TreeActionCallback :: C_TreeActionCallback -> IO (FunPtr C_TreeActionCallback)
wrap_TreeActionCallback ::
GObject a => (a -> TreeActionCallback) ->
C_TreeActionCallback
wrap_TreeActionCallback :: forall a.
GObject a =>
(a -> TreeActionCallback) -> C_TreeActionCallback
wrap_TreeActionCallback a -> TreeActionCallback
gi'cb Ptr Tree
gi'selfPtr CString
object CString
p0 CString
p1 Ptr ()
_ = do
Text
object' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
object
Text
p0' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
p0
Text
p1' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
p1
Ptr Tree -> (Tree -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Tree
gi'selfPtr ((Tree -> IO ()) -> IO ()) -> (Tree -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Tree
gi'self -> a -> TreeActionCallback
gi'cb (Tree -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Tree
gi'self) Text
object' Text
p0' Text
p1'
onTreeAction :: (IsTree a, MonadIO m) => a -> ((?self :: a) => TreeActionCallback) -> m SignalHandlerId
onTreeAction :: forall a (m :: * -> *).
(IsTree a, MonadIO m) =>
a -> ((?self::a) => TreeActionCallback) -> m SignalHandlerId
onTreeAction a
obj (?self::a) => TreeActionCallback
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 -> TreeActionCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => TreeActionCallback
TreeActionCallback
cb
let wrapped' :: C_TreeActionCallback
wrapped' = (a -> TreeActionCallback) -> C_TreeActionCallback
forall a.
GObject a =>
(a -> TreeActionCallback) -> C_TreeActionCallback
wrap_TreeActionCallback a -> TreeActionCallback
wrapped
FunPtr C_TreeActionCallback
wrapped'' <- C_TreeActionCallback -> IO (FunPtr C_TreeActionCallback)
mk_TreeActionCallback C_TreeActionCallback
wrapped'
a
-> Text
-> FunPtr C_TreeActionCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"action" FunPtr C_TreeActionCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTreeAction :: (IsTree a, MonadIO m) => a -> ((?self :: a) => TreeActionCallback) -> m SignalHandlerId
afterTreeAction :: forall a (m :: * -> *).
(IsTree a, MonadIO m) =>
a -> ((?self::a) => TreeActionCallback) -> m SignalHandlerId
afterTreeAction a
obj (?self::a) => TreeActionCallback
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 -> TreeActionCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => TreeActionCallback
TreeActionCallback
cb
let wrapped' :: C_TreeActionCallback
wrapped' = (a -> TreeActionCallback) -> C_TreeActionCallback
forall a.
GObject a =>
(a -> TreeActionCallback) -> C_TreeActionCallback
wrap_TreeActionCallback a -> TreeActionCallback
wrapped
FunPtr C_TreeActionCallback
wrapped'' <- C_TreeActionCallback -> IO (FunPtr C_TreeActionCallback)
mk_TreeActionCallback C_TreeActionCallback
wrapped'
a
-> Text
-> FunPtr C_TreeActionCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"action" FunPtr C_TreeActionCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TreeActionSignalInfo
instance SignalInfo TreeActionSignalInfo where
type HaskellCallbackType TreeActionSignalInfo = TreeActionCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_TreeActionCallback cb
cb'' <- mk_TreeActionCallback cb'
connectSignalFunPtr obj "action" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree::action"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#g:signal:action"})
#endif
type =
Gtk.Widget.Widget
-> IO ()
type =
Ptr Tree ->
Ptr Gtk.Widget.Widget ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
:: C_TreePopulatePopupCallback -> IO (FunPtr C_TreePopulatePopupCallback)
wrap_TreePopulatePopupCallback ::
GObject a => (a -> TreePopulatePopupCallback) ->
C_TreePopulatePopupCallback
a -> TreePopulatePopupCallback
gi'cb Ptr Tree
gi'selfPtr Ptr Widget
object Ptr ()
_ = do
Widget
object' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
object
Ptr Tree -> (Tree -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Tree
gi'selfPtr ((Tree -> IO ()) -> IO ()) -> (Tree -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Tree
gi'self -> a -> TreePopulatePopupCallback
gi'cb (Tree -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Tree
gi'self) Widget
object'
onTreePopulatePopup :: (IsTree a, MonadIO m) => a -> ((?self :: a) => TreePopulatePopupCallback) -> m SignalHandlerId
a
obj (?self::a) => TreePopulatePopupCallback
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 -> TreePopulatePopupCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => TreePopulatePopupCallback
TreePopulatePopupCallback
cb
let wrapped' :: C_TreePopulatePopupCallback
wrapped' = (a -> TreePopulatePopupCallback) -> C_TreePopulatePopupCallback
forall a.
GObject a =>
(a -> TreePopulatePopupCallback) -> C_TreePopulatePopupCallback
wrap_TreePopulatePopupCallback a -> TreePopulatePopupCallback
wrapped
FunPtr C_TreePopulatePopupCallback
wrapped'' <- C_TreePopulatePopupCallback
-> IO (FunPtr C_TreePopulatePopupCallback)
mk_TreePopulatePopupCallback C_TreePopulatePopupCallback
wrapped'
a
-> Text
-> FunPtr C_TreePopulatePopupCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"populate-popup" FunPtr C_TreePopulatePopupCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterTreePopulatePopup :: (IsTree a, MonadIO m) => a -> ((?self :: a) => TreePopulatePopupCallback) -> m SignalHandlerId
a
obj (?self::a) => TreePopulatePopupCallback
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 -> TreePopulatePopupCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => TreePopulatePopupCallback
TreePopulatePopupCallback
cb
let wrapped' :: C_TreePopulatePopupCallback
wrapped' = (a -> TreePopulatePopupCallback) -> C_TreePopulatePopupCallback
forall a.
GObject a =>
(a -> TreePopulatePopupCallback) -> C_TreePopulatePopupCallback
wrap_TreePopulatePopupCallback a -> TreePopulatePopupCallback
wrapped
FunPtr C_TreePopulatePopupCallback
wrapped'' <- C_TreePopulatePopupCallback
-> IO (FunPtr C_TreePopulatePopupCallback)
mk_TreePopulatePopupCallback C_TreePopulatePopupCallback
wrapped'
a
-> Text
-> FunPtr C_TreePopulatePopupCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"populate-popup" FunPtr C_TreePopulatePopupCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data TreePopulatePopupSignalInfo
instance SignalInfo TreePopulatePopupSignalInfo where
type HaskellCallbackType TreePopulatePopupSignalInfo = TreePopulatePopupCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_TreePopulatePopupCallback cb
cb'' <- mk_TreePopulatePopupCallback cb'
connectSignalFunPtr obj "populate-popup" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree::populate-popup"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#g:signal:populatePopup"})
#endif
getTreeAlwaysExpand :: (MonadIO m, IsTree o) => o -> m Bool
getTreeAlwaysExpand :: forall (m :: * -> *) o. (MonadIO m, IsTree o) => o -> m Bool
getTreeAlwaysExpand 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
"always-expand"
constructTreeAlwaysExpand :: (IsTree o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTreeAlwaysExpand :: forall o (m :: * -> *).
(IsTree o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTreeAlwaysExpand 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
"always-expand" Bool
val
#if defined(ENABLE_OVERLOADING)
data TreeAlwaysExpandPropertyInfo
instance AttrInfo TreeAlwaysExpandPropertyInfo where
type AttrAllowedOps TreeAlwaysExpandPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TreeAlwaysExpandPropertyInfo = IsTree
type AttrSetTypeConstraint TreeAlwaysExpandPropertyInfo = (~) Bool
type AttrTransferTypeConstraint TreeAlwaysExpandPropertyInfo = (~) Bool
type AttrTransferType TreeAlwaysExpandPropertyInfo = Bool
type AttrGetType TreeAlwaysExpandPropertyInfo = Bool
type AttrLabel TreeAlwaysExpandPropertyInfo = "always-expand"
type AttrOrigin TreeAlwaysExpandPropertyInfo = Tree
attrGet = getTreeAlwaysExpand
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructTreeAlwaysExpand
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.alwaysExpand"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#g:attr:alwaysExpand"
})
#endif
getTreeContextMenu :: (MonadIO m, IsTree o) => o -> m (Maybe Gio.MenuModel.MenuModel)
o
obj = IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe MenuModel) -> m (Maybe MenuModel))
-> IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr MenuModel -> MenuModel)
-> IO (Maybe MenuModel)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"context-menu" ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel
setTreeContextMenu :: (MonadIO m, IsTree o, Gio.MenuModel.IsMenuModel a) => o -> a -> m ()
o
obj a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"context-menu" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructTreeContextMenu :: (IsTree o, MIO.MonadIO m, Gio.MenuModel.IsMenuModel a) => a -> m (GValueConstruct o)
a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"context-menu" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data TreeContextMenuPropertyInfo
instance AttrInfo TreeContextMenuPropertyInfo where
type AttrAllowedOps TreeContextMenuPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TreeContextMenuPropertyInfo = IsTree
type AttrSetTypeConstraint TreeContextMenuPropertyInfo = Gio.MenuModel.IsMenuModel
type AttrTransferTypeConstraint TreeContextMenuPropertyInfo = Gio.MenuModel.IsMenuModel
type AttrTransferType TreeContextMenuPropertyInfo = Gio.MenuModel.MenuModel
type AttrGetType TreeContextMenuPropertyInfo = (Maybe Gio.MenuModel.MenuModel)
type AttrLabel TreeContextMenuPropertyInfo = "context-menu"
type AttrOrigin TreeContextMenuPropertyInfo = Tree
attrGet = getTreeContextMenu
attrSet = setTreeContextMenu
attrTransfer _ v = do
unsafeCastTo Gio.MenuModel.MenuModel v
attrConstruct = constructTreeContextMenu
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.contextMenu"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#g:attr:contextMenu"
})
#endif
getTreeRoot :: (MonadIO m, IsTree o) => o -> m (Maybe Dazzle.TreeNode.TreeNode)
getTreeRoot :: forall (m :: * -> *) o.
(MonadIO m, IsTree o) =>
o -> m (Maybe TreeNode)
getTreeRoot o
obj = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TreeNode -> TreeNode)
-> IO (Maybe TreeNode)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"root" ManagedPtr TreeNode -> TreeNode
Dazzle.TreeNode.TreeNode
setTreeRoot :: (MonadIO m, IsTree o, Dazzle.TreeNode.IsTreeNode a) => o -> a -> m ()
setTreeRoot :: forall (m :: * -> *) o a.
(MonadIO m, IsTree o, IsTreeNode a) =>
o -> a -> m ()
setTreeRoot o
obj a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"root" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructTreeRoot :: (IsTree o, MIO.MonadIO m, Dazzle.TreeNode.IsTreeNode a) => a -> m (GValueConstruct o)
constructTreeRoot :: forall o (m :: * -> *) a.
(IsTree o, MonadIO m, IsTreeNode a) =>
a -> m (GValueConstruct o)
constructTreeRoot a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"root" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data TreeRootPropertyInfo
instance AttrInfo TreeRootPropertyInfo where
type AttrAllowedOps TreeRootPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TreeRootPropertyInfo = IsTree
type AttrSetTypeConstraint TreeRootPropertyInfo = Dazzle.TreeNode.IsTreeNode
type AttrTransferTypeConstraint TreeRootPropertyInfo = Dazzle.TreeNode.IsTreeNode
type AttrTransferType TreeRootPropertyInfo = Dazzle.TreeNode.TreeNode
type AttrGetType TreeRootPropertyInfo = (Maybe Dazzle.TreeNode.TreeNode)
type AttrLabel TreeRootPropertyInfo = "root"
type AttrOrigin TreeRootPropertyInfo = Tree
attrGet = getTreeRoot
attrSet = setTreeRoot
attrTransfer _ v = do
unsafeCastTo Dazzle.TreeNode.TreeNode v
attrConstruct = constructTreeRoot
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.root"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#g:attr:root"
})
#endif
getTreeSelection :: (MonadIO m, IsTree o) => o -> m (Maybe Dazzle.TreeNode.TreeNode)
getTreeSelection :: forall (m :: * -> *) o.
(MonadIO m, IsTree o) =>
o -> m (Maybe TreeNode)
getTreeSelection o
obj = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr TreeNode -> TreeNode)
-> IO (Maybe TreeNode)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"selection" ManagedPtr TreeNode -> TreeNode
Dazzle.TreeNode.TreeNode
setTreeSelection :: (MonadIO m, IsTree o, Dazzle.TreeNode.IsTreeNode a) => o -> a -> m ()
setTreeSelection :: forall (m :: * -> *) o a.
(MonadIO m, IsTree o, IsTreeNode a) =>
o -> a -> m ()
setTreeSelection o
obj a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"selection" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructTreeSelection :: (IsTree o, MIO.MonadIO m, Dazzle.TreeNode.IsTreeNode a) => a -> m (GValueConstruct o)
constructTreeSelection :: forall o (m :: * -> *) a.
(IsTree o, MonadIO m, IsTreeNode a) =>
a -> m (GValueConstruct o)
constructTreeSelection a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"selection" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearTreeSelection :: (MonadIO m, IsTree o) => o -> m ()
clearTreeSelection :: forall (m :: * -> *) o. (MonadIO m, IsTree o) => o -> m ()
clearTreeSelection o
obj = 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
$ o -> String -> Maybe TreeNode -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"selection" (Maybe TreeNode
forall a. Maybe a
Nothing :: Maybe Dazzle.TreeNode.TreeNode)
#if defined(ENABLE_OVERLOADING)
data TreeSelectionPropertyInfo
instance AttrInfo TreeSelectionPropertyInfo where
type AttrAllowedOps TreeSelectionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint TreeSelectionPropertyInfo = IsTree
type AttrSetTypeConstraint TreeSelectionPropertyInfo = Dazzle.TreeNode.IsTreeNode
type AttrTransferTypeConstraint TreeSelectionPropertyInfo = Dazzle.TreeNode.IsTreeNode
type AttrTransferType TreeSelectionPropertyInfo = Dazzle.TreeNode.TreeNode
type AttrGetType TreeSelectionPropertyInfo = (Maybe Dazzle.TreeNode.TreeNode)
type AttrLabel TreeSelectionPropertyInfo = "selection"
type AttrOrigin TreeSelectionPropertyInfo = Tree
attrGet = getTreeSelection
attrSet = setTreeSelection
attrTransfer _ v = do
unsafeCastTo Dazzle.TreeNode.TreeNode v
attrConstruct = constructTreeSelection
attrClear = clearTreeSelection
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.selection"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#g:attr:selection"
})
#endif
getTreeShowIcons :: (MonadIO m, IsTree o) => o -> m Bool
getTreeShowIcons :: forall (m :: * -> *) o. (MonadIO m, IsTree o) => o -> m Bool
getTreeShowIcons 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
"show-icons"
setTreeShowIcons :: (MonadIO m, IsTree o) => o -> Bool -> m ()
setTreeShowIcons :: forall (m :: * -> *) o. (MonadIO m, IsTree o) => o -> Bool -> m ()
setTreeShowIcons 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
"show-icons" Bool
val
constructTreeShowIcons :: (IsTree o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTreeShowIcons :: forall o (m :: * -> *).
(IsTree o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTreeShowIcons 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
"show-icons" Bool
val
#if defined(ENABLE_OVERLOADING)
data TreeShowIconsPropertyInfo
instance AttrInfo TreeShowIconsPropertyInfo where
type AttrAllowedOps TreeShowIconsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TreeShowIconsPropertyInfo = IsTree
type AttrSetTypeConstraint TreeShowIconsPropertyInfo = (~) Bool
type AttrTransferTypeConstraint TreeShowIconsPropertyInfo = (~) Bool
type AttrTransferType TreeShowIconsPropertyInfo = Bool
type AttrGetType TreeShowIconsPropertyInfo = Bool
type AttrLabel TreeShowIconsPropertyInfo = "show-icons"
type AttrOrigin TreeShowIconsPropertyInfo = Tree
attrGet = getTreeShowIcons
attrSet = setTreeShowIcons
attrTransfer _ v = do
return v
attrConstruct = constructTreeShowIcons
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.showIcons"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#g:attr:showIcons"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Tree
type instance O.AttributeList Tree = TreeAttributeList
type TreeAttributeList = ('[ '("activateOnSingleClick", Gtk.TreeView.TreeViewActivateOnSingleClickPropertyInfo), '("alwaysExpand", TreeAlwaysExpandPropertyInfo), '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("contextMenu", TreeContextMenuPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("enableGridLines", Gtk.TreeView.TreeViewEnableGridLinesPropertyInfo), '("enableSearch", Gtk.TreeView.TreeViewEnableSearchPropertyInfo), '("enableTreeLines", Gtk.TreeView.TreeViewEnableTreeLinesPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("expanderColumn", Gtk.TreeView.TreeViewExpanderColumnPropertyInfo), '("fixedHeightMode", Gtk.TreeView.TreeViewFixedHeightModePropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("hadjustment", Gtk.Scrollable.ScrollableHadjustmentPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("headersClickable", Gtk.TreeView.TreeViewHeadersClickablePropertyInfo), '("headersVisible", Gtk.TreeView.TreeViewHeadersVisiblePropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("hoverExpand", Gtk.TreeView.TreeViewHoverExpandPropertyInfo), '("hoverSelection", Gtk.TreeView.TreeViewHoverSelectionPropertyInfo), '("hscrollPolicy", Gtk.Scrollable.ScrollableHscrollPolicyPropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("levelIndentation", Gtk.TreeView.TreeViewLevelIndentationPropertyInfo), '("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), '("model", Gtk.TreeView.TreeViewModelPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("reorderable", Gtk.TreeView.TreeViewReorderablePropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("root", TreeRootPropertyInfo), '("rubberBanding", Gtk.TreeView.TreeViewRubberBandingPropertyInfo), '("rulesHint", Gtk.TreeView.TreeViewRulesHintPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("searchColumn", Gtk.TreeView.TreeViewSearchColumnPropertyInfo), '("selection", TreeSelectionPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("showExpanders", Gtk.TreeView.TreeViewShowExpandersPropertyInfo), '("showIcons", TreeShowIconsPropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("tooltipColumn", Gtk.TreeView.TreeViewTooltipColumnPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("vadjustment", Gtk.Scrollable.ScrollableVadjustmentPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("vscrollPolicy", Gtk.Scrollable.ScrollableVscrollPolicyPropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
treeAlwaysExpand :: AttrLabelProxy "alwaysExpand"
treeAlwaysExpand = AttrLabelProxy
treeContextMenu :: AttrLabelProxy "contextMenu"
treeContextMenu = AttrLabelProxy
treeRoot :: AttrLabelProxy "root"
treeRoot = AttrLabelProxy
treeSelection :: AttrLabelProxy "selection"
treeSelection = AttrLabelProxy
treeShowIcons :: AttrLabelProxy "showIcons"
treeShowIcons = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Tree = TreeSignalList
type TreeSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("action", TreeActionSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("columnsChanged", Gtk.TreeView.TreeViewColumnsChangedSignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("cursorChanged", Gtk.TreeView.TreeViewCursorChangedSignalInfo), '("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), '("expandCollapseCursorRow", Gtk.TreeView.TreeViewExpandCollapseCursorRowSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveCursor", Gtk.TreeView.TreeViewMoveCursorSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("populatePopup", TreePopulatePopupSignalInfo), '("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), '("rowActivated", Gtk.TreeView.TreeViewRowActivatedSignalInfo), '("rowCollapsed", Gtk.TreeView.TreeViewRowCollapsedSignalInfo), '("rowExpanded", Gtk.TreeView.TreeViewRowExpandedSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectAll", Gtk.TreeView.TreeViewSelectAllSignalInfo), '("selectCursorParent", Gtk.TreeView.TreeViewSelectCursorParentSignalInfo), '("selectCursorRow", Gtk.TreeView.TreeViewSelectCursorRowSignalInfo), '("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), '("startInteractiveSearch", Gtk.TreeView.TreeViewStartInteractiveSearchSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("testCollapseRow", Gtk.TreeView.TreeViewTestCollapseRowSignalInfo), '("testExpandRow", Gtk.TreeView.TreeViewTestExpandRowSignalInfo), '("toggleCursorRow", Gtk.TreeView.TreeViewToggleCursorRowSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("unselectAll", Gtk.TreeView.TreeViewUnselectAllSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_tree_add_builder" dzl_tree_add_builder ::
Ptr Tree ->
Ptr Dazzle.TreeBuilder.TreeBuilder ->
IO ()
treeAddBuilder ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a, Dazzle.TreeBuilder.IsTreeBuilder b) =>
a
-> b
-> m ()
treeAddBuilder :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTree a, IsTreeBuilder b) =>
a -> b -> m ()
treeAddBuilder a
self b
builder = 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 Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TreeBuilder
builder' <- b -> IO (Ptr TreeBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
builder
Ptr Tree -> Ptr TreeBuilder -> IO ()
dzl_tree_add_builder Ptr Tree
self' Ptr TreeBuilder
builder'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
builder
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TreeAddBuilderMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTree a, Dazzle.TreeBuilder.IsTreeBuilder b) => O.OverloadedMethod TreeAddBuilderMethodInfo a signature where
overloadedMethod = treeAddBuilder
instance O.OverloadedMethodInfo TreeAddBuilderMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeAddBuilder",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeAddBuilder"
})
#endif
foreign import ccall "dzl_tree_expand_to_node" dzl_tree_expand_to_node ::
Ptr Tree ->
Ptr Dazzle.TreeNode.TreeNode ->
IO ()
treeExpandToNode ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a, Dazzle.TreeNode.IsTreeNode b) =>
a
-> b
-> m ()
treeExpandToNode :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTree a, IsTreeNode b) =>
a -> b -> m ()
treeExpandToNode a
self b
node = 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 Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TreeNode
node' <- b -> IO (Ptr TreeNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
node
Ptr Tree -> Ptr TreeNode -> IO ()
dzl_tree_expand_to_node Ptr Tree
self' Ptr TreeNode
node'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
node
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TreeExpandToNodeMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTree a, Dazzle.TreeNode.IsTreeNode b) => O.OverloadedMethod TreeExpandToNodeMethodInfo a signature where
overloadedMethod = treeExpandToNode
instance O.OverloadedMethodInfo TreeExpandToNodeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeExpandToNode",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeExpandToNode"
})
#endif
foreign import ccall "dzl_tree_find_child_node" dzl_tree_find_child_node ::
Ptr Tree ->
Ptr Dazzle.TreeNode.TreeNode ->
FunPtr Dazzle.Callbacks.C_TreeFindFunc ->
Ptr () ->
IO (Ptr Dazzle.TreeNode.TreeNode)
treeFindChildNode ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a, Dazzle.TreeNode.IsTreeNode b) =>
a
-> b
-> Dazzle.Callbacks.TreeFindFunc
-> m (Maybe Dazzle.TreeNode.TreeNode)
treeFindChildNode :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTree a, IsTreeNode b) =>
a -> b -> TreeFindFunc -> m (Maybe TreeNode)
treeFindChildNode a
self b
node TreeFindFunc
findFunc = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ do
Ptr Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TreeNode
node' <- b -> IO (Ptr TreeNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
node
FunPtr C_TreeFindFunc
findFunc' <- C_TreeFindFunc -> IO (FunPtr C_TreeFindFunc)
Dazzle.Callbacks.mk_TreeFindFunc (Maybe (Ptr (FunPtr C_TreeFindFunc))
-> TreeFindFunc_WithClosures -> C_TreeFindFunc
Dazzle.Callbacks.wrap_TreeFindFunc Maybe (Ptr (FunPtr C_TreeFindFunc))
forall a. Maybe a
Nothing (TreeFindFunc -> TreeFindFunc_WithClosures
Dazzle.Callbacks.drop_closures_TreeFindFunc TreeFindFunc
findFunc))
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr TreeNode
result <- Ptr Tree
-> Ptr TreeNode
-> FunPtr C_TreeFindFunc
-> Ptr ()
-> IO (Ptr TreeNode)
dzl_tree_find_child_node Ptr Tree
self' Ptr TreeNode
node' FunPtr C_TreeFindFunc
findFunc' Ptr ()
forall a. Ptr a
userData
Maybe TreeNode
maybeResult <- Ptr TreeNode
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeNode
result ((Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode))
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeNode
result' -> do
TreeNode
result'' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TreeNode -> TreeNode
Dazzle.TreeNode.TreeNode) Ptr TreeNode
result'
TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result''
Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_TreeFindFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_TreeFindFunc
findFunc'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
node
Maybe TreeNode -> IO (Maybe TreeNode)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeNode
maybeResult
#if defined(ENABLE_OVERLOADING)
data TreeFindChildNodeMethodInfo
instance (signature ~ (b -> Dazzle.Callbacks.TreeFindFunc -> m (Maybe Dazzle.TreeNode.TreeNode)), MonadIO m, IsTree a, Dazzle.TreeNode.IsTreeNode b) => O.OverloadedMethod TreeFindChildNodeMethodInfo a signature where
overloadedMethod = treeFindChildNode
instance O.OverloadedMethodInfo TreeFindChildNodeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeFindChildNode",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeFindChildNode"
})
#endif
foreign import ccall "dzl_tree_find_custom" dzl_tree_find_custom ::
Ptr Tree ->
FunPtr GLib.Callbacks.C_EqualFunc ->
Ptr () ->
IO (Ptr Dazzle.TreeNode.TreeNode)
treeFindCustom ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
a
-> GLib.Callbacks.EqualFunc
-> Ptr ()
-> m (Maybe Dazzle.TreeNode.TreeNode)
treeFindCustom :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTree a) =>
a -> EqualFunc -> Ptr () -> m (Maybe TreeNode)
treeFindCustom a
self EqualFunc
equalFunc Ptr ()
key = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ do
Ptr Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
FunPtr C_EqualFunc
equalFunc' <- C_EqualFunc -> IO (FunPtr C_EqualFunc)
GLib.Callbacks.mk_EqualFunc (Maybe (Ptr (FunPtr C_EqualFunc))
-> EqualFunc_WithClosures -> C_EqualFunc
GLib.Callbacks.wrap_EqualFunc Maybe (Ptr (FunPtr C_EqualFunc))
forall a. Maybe a
Nothing (EqualFunc -> EqualFunc_WithClosures
GLib.Callbacks.drop_closures_EqualFunc EqualFunc
equalFunc))
Ptr TreeNode
result <- Ptr Tree -> FunPtr C_EqualFunc -> Ptr () -> IO (Ptr TreeNode)
dzl_tree_find_custom Ptr Tree
self' FunPtr C_EqualFunc
equalFunc' Ptr ()
key
Maybe TreeNode
maybeResult <- Ptr TreeNode
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeNode
result ((Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode))
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeNode
result' -> do
TreeNode
result'' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TreeNode -> TreeNode
Dazzle.TreeNode.TreeNode) Ptr TreeNode
result'
TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result''
Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_EqualFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_EqualFunc
equalFunc'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe TreeNode -> IO (Maybe TreeNode)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeNode
maybeResult
#if defined(ENABLE_OVERLOADING)
data TreeFindCustomMethodInfo
instance (signature ~ (GLib.Callbacks.EqualFunc -> Ptr () -> m (Maybe Dazzle.TreeNode.TreeNode)), MonadIO m, IsTree a) => O.OverloadedMethod TreeFindCustomMethodInfo a signature where
overloadedMethod = treeFindCustom
instance O.OverloadedMethodInfo TreeFindCustomMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeFindCustom",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeFindCustom"
})
#endif
foreign import ccall "dzl_tree_find_item" dzl_tree_find_item ::
Ptr Tree ->
Ptr GObject.Object.Object ->
IO (Ptr Dazzle.TreeNode.TreeNode)
treeFindItem ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a, GObject.Object.IsObject b) =>
a
-> Maybe (b)
-> m (Maybe Dazzle.TreeNode.TreeNode)
treeFindItem :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTree a, IsObject b) =>
a -> Maybe b -> m (Maybe TreeNode)
treeFindItem a
self Maybe b
item = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ do
Ptr Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Object
maybeItem <- case Maybe b
item of
Maybe b
Nothing -> Ptr Object -> IO (Ptr Object)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
Just b
jItem -> do
Ptr Object
jItem' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jItem
Ptr Object -> IO (Ptr Object)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jItem'
Ptr TreeNode
result <- Ptr Tree -> Ptr Object -> IO (Ptr TreeNode)
dzl_tree_find_item Ptr Tree
self' Ptr Object
maybeItem
Maybe TreeNode
maybeResult <- Ptr TreeNode
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeNode
result ((Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode))
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeNode
result' -> do
TreeNode
result'' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TreeNode -> TreeNode
Dazzle.TreeNode.TreeNode) Ptr TreeNode
result'
TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
item b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe TreeNode -> IO (Maybe TreeNode)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeNode
maybeResult
#if defined(ENABLE_OVERLOADING)
data TreeFindItemMethodInfo
instance (signature ~ (Maybe (b) -> m (Maybe Dazzle.TreeNode.TreeNode)), MonadIO m, IsTree a, GObject.Object.IsObject b) => O.OverloadedMethod TreeFindItemMethodInfo a signature where
overloadedMethod = treeFindItem
instance O.OverloadedMethodInfo TreeFindItemMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeFindItem",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeFindItem"
})
#endif
foreign import ccall "dzl_tree_get_context_menu" ::
Ptr Tree ->
IO (Ptr Gio.MenuModel.MenuModel)
treeGetContextMenu ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
a
-> m (Maybe Gio.MenuModel.MenuModel)
a
self = IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MenuModel) -> m (Maybe MenuModel))
-> IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ do
Ptr Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr MenuModel
result <- Ptr Tree -> IO (Ptr MenuModel)
dzl_tree_get_context_menu Ptr Tree
self'
Maybe MenuModel
maybeResult <- Ptr MenuModel
-> (Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr MenuModel
result ((Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel))
-> (Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ \Ptr MenuModel
result' -> do
MenuModel
result'' <- ((ManagedPtr MenuModel -> MenuModel)
-> Ptr MenuModel -> IO MenuModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel) Ptr MenuModel
result'
MenuModel -> IO MenuModel
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MenuModel
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe MenuModel -> IO (Maybe MenuModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MenuModel
maybeResult
#if defined(ENABLE_OVERLOADING)
data TreeGetContextMenuMethodInfo
instance (signature ~ (m (Maybe Gio.MenuModel.MenuModel)), MonadIO m, IsTree a) => O.OverloadedMethod TreeGetContextMenuMethodInfo a signature where
overloadedMethod = treeGetContextMenu
instance O.OverloadedMethodInfo TreeGetContextMenuMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeGetContextMenu",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeGetContextMenu"
})
#endif
foreign import ccall "dzl_tree_get_root" dzl_tree_get_root ::
Ptr Tree ->
IO (Ptr Dazzle.TreeNode.TreeNode)
treeGetRoot ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
a
-> m (Maybe Dazzle.TreeNode.TreeNode)
treeGetRoot :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTree a) =>
a -> m (Maybe TreeNode)
treeGetRoot a
self = IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreeNode) -> m (Maybe TreeNode))
-> IO (Maybe TreeNode) -> m (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ do
Ptr Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TreeNode
result <- Ptr Tree -> IO (Ptr TreeNode)
dzl_tree_get_root Ptr Tree
self'
Maybe TreeNode
maybeResult <- Ptr TreeNode
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreeNode
result ((Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode))
-> (Ptr TreeNode -> IO TreeNode) -> IO (Maybe TreeNode)
forall a b. (a -> b) -> a -> b
$ \Ptr TreeNode
result' -> do
TreeNode
result'' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TreeNode -> TreeNode
Dazzle.TreeNode.TreeNode) Ptr TreeNode
result'
TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe TreeNode -> IO (Maybe TreeNode)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreeNode
maybeResult
#if defined(ENABLE_OVERLOADING)
data TreeGetRootMethodInfo
instance (signature ~ (m (Maybe Dazzle.TreeNode.TreeNode)), MonadIO m, IsTree a) => O.OverloadedMethod TreeGetRootMethodInfo a signature where
overloadedMethod = treeGetRoot
instance O.OverloadedMethodInfo TreeGetRootMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeGetRoot",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeGetRoot"
})
#endif
foreign import ccall "dzl_tree_get_selected" dzl_tree_get_selected ::
Ptr Tree ->
IO (Ptr Dazzle.TreeNode.TreeNode)
treeGetSelected ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
a
-> m Dazzle.TreeNode.TreeNode
treeGetSelected :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTree a) =>
a -> m TreeNode
treeGetSelected a
self = IO TreeNode -> m TreeNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeNode -> m TreeNode) -> IO TreeNode -> m TreeNode
forall a b. (a -> b) -> a -> b
$ do
Ptr Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TreeNode
result <- Ptr Tree -> IO (Ptr TreeNode)
dzl_tree_get_selected Ptr Tree
self'
Text -> Ptr TreeNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"treeGetSelected" Ptr TreeNode
result
TreeNode
result' <- ((ManagedPtr TreeNode -> TreeNode) -> Ptr TreeNode -> IO TreeNode
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TreeNode -> TreeNode
Dazzle.TreeNode.TreeNode) Ptr TreeNode
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
TreeNode -> IO TreeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TreeNode
result'
#if defined(ENABLE_OVERLOADING)
data TreeGetSelectedMethodInfo
instance (signature ~ (m Dazzle.TreeNode.TreeNode), MonadIO m, IsTree a) => O.OverloadedMethod TreeGetSelectedMethodInfo a signature where
overloadedMethod = treeGetSelected
instance O.OverloadedMethodInfo TreeGetSelectedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeGetSelected",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeGetSelected"
})
#endif
foreign import ccall "dzl_tree_get_show_icons" dzl_tree_get_show_icons ::
Ptr Tree ->
IO CInt
treeGetShowIcons ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
a
-> m Bool
treeGetShowIcons :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTree a) =>
a -> m Bool
treeGetShowIcons 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 Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CInt
result <- Ptr Tree -> IO CInt
dzl_tree_get_show_icons Ptr Tree
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 TreeGetShowIconsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTree a) => O.OverloadedMethod TreeGetShowIconsMethodInfo a signature where
overloadedMethod = treeGetShowIcons
instance O.OverloadedMethodInfo TreeGetShowIconsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeGetShowIcons",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeGetShowIcons"
})
#endif
foreign import ccall "dzl_tree_rebuild" dzl_tree_rebuild ::
Ptr Tree ->
IO ()
treeRebuild ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
a
-> m ()
treeRebuild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTree a) =>
a -> m ()
treeRebuild a
self = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Tree -> IO ()
dzl_tree_rebuild Ptr Tree
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TreeRebuildMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTree a) => O.OverloadedMethod TreeRebuildMethodInfo a signature where
overloadedMethod = treeRebuild
instance O.OverloadedMethodInfo TreeRebuildMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeRebuild",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeRebuild"
})
#endif
foreign import ccall "dzl_tree_remove_builder" dzl_tree_remove_builder ::
Ptr Tree ->
Ptr Dazzle.TreeBuilder.TreeBuilder ->
IO ()
treeRemoveBuilder ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a, Dazzle.TreeBuilder.IsTreeBuilder b) =>
a
-> b
-> m ()
treeRemoveBuilder :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTree a, IsTreeBuilder b) =>
a -> b -> m ()
treeRemoveBuilder a
self b
builder = 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 Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TreeBuilder
builder' <- b -> IO (Ptr TreeBuilder)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
builder
Ptr Tree -> Ptr TreeBuilder -> IO ()
dzl_tree_remove_builder Ptr Tree
self' Ptr TreeBuilder
builder'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
builder
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TreeRemoveBuilderMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTree a, Dazzle.TreeBuilder.IsTreeBuilder b) => O.OverloadedMethod TreeRemoveBuilderMethodInfo a signature where
overloadedMethod = treeRemoveBuilder
instance O.OverloadedMethodInfo TreeRemoveBuilderMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeRemoveBuilder",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeRemoveBuilder"
})
#endif
foreign import ccall "dzl_tree_scroll_to_node" dzl_tree_scroll_to_node ::
Ptr Tree ->
Ptr Dazzle.TreeNode.TreeNode ->
IO ()
treeScrollToNode ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a, Dazzle.TreeNode.IsTreeNode b) =>
a
-> b
-> m ()
treeScrollToNode :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTree a, IsTreeNode b) =>
a -> b -> m ()
treeScrollToNode a
self b
node = 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 Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TreeNode
node' <- b -> IO (Ptr TreeNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
node
Ptr Tree -> Ptr TreeNode -> IO ()
dzl_tree_scroll_to_node Ptr Tree
self' Ptr TreeNode
node'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
node
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TreeScrollToNodeMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTree a, Dazzle.TreeNode.IsTreeNode b) => O.OverloadedMethod TreeScrollToNodeMethodInfo a signature where
overloadedMethod = treeScrollToNode
instance O.OverloadedMethodInfo TreeScrollToNodeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeScrollToNode",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeScrollToNode"
})
#endif
foreign import ccall "dzl_tree_set_context_menu" ::
Ptr Tree ->
Ptr Gio.MenuModel.MenuModel ->
IO ()
treeSetContextMenu ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a, Gio.MenuModel.IsMenuModel b) =>
a
-> b
-> m ()
a
self b
contextMenu = 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 Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr MenuModel
contextMenu' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
contextMenu
Ptr Tree -> Ptr MenuModel -> IO ()
dzl_tree_set_context_menu Ptr Tree
self' Ptr MenuModel
contextMenu'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
contextMenu
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TreeSetContextMenuMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTree a, Gio.MenuModel.IsMenuModel b) => O.OverloadedMethod TreeSetContextMenuMethodInfo a signature where
overloadedMethod = treeSetContextMenu
instance O.OverloadedMethodInfo TreeSetContextMenuMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeSetContextMenu",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeSetContextMenu"
})
#endif
foreign import ccall "dzl_tree_set_filter" dzl_tree_set_filter ::
Ptr Tree ->
FunPtr Dazzle.Callbacks.C_TreeFilterFunc ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
treeSetFilter ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
a
-> Dazzle.Callbacks.TreeFilterFunc
-> m ()
treeSetFilter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTree a) =>
a -> TreeFilterFunc -> m ()
treeSetFilter a
self TreeFilterFunc
filterFunc = 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 Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
FunPtr C_TreeFilterFunc
filterFunc' <- C_TreeFilterFunc -> IO (FunPtr C_TreeFilterFunc)
Dazzle.Callbacks.mk_TreeFilterFunc (Maybe (Ptr (FunPtr C_TreeFilterFunc))
-> TreeFilterFunc_WithClosures -> C_TreeFilterFunc
Dazzle.Callbacks.wrap_TreeFilterFunc Maybe (Ptr (FunPtr C_TreeFilterFunc))
forall a. Maybe a
Nothing (TreeFilterFunc -> TreeFilterFunc_WithClosures
Dazzle.Callbacks.drop_closures_TreeFilterFunc TreeFilterFunc
filterFunc))
let filterData :: Ptr ()
filterData = FunPtr C_TreeFilterFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_TreeFilterFunc
filterFunc'
let filterDataDestroy :: FunPtr (Ptr a -> IO ())
filterDataDestroy = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
Ptr Tree
-> FunPtr C_TreeFilterFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
dzl_tree_set_filter Ptr Tree
self' FunPtr C_TreeFilterFunc
filterFunc' Ptr ()
filterData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
filterDataDestroy
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 TreeSetFilterMethodInfo
instance (signature ~ (Dazzle.Callbacks.TreeFilterFunc -> m ()), MonadIO m, IsTree a) => O.OverloadedMethod TreeSetFilterMethodInfo a signature where
overloadedMethod = treeSetFilter
instance O.OverloadedMethodInfo TreeSetFilterMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeSetFilter",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeSetFilter"
})
#endif
foreign import ccall "dzl_tree_set_root" dzl_tree_set_root ::
Ptr Tree ->
Ptr Dazzle.TreeNode.TreeNode ->
IO ()
treeSetRoot ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a, Dazzle.TreeNode.IsTreeNode b) =>
a
-> b
-> m ()
treeSetRoot :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTree a, IsTreeNode b) =>
a -> b -> m ()
treeSetRoot a
self b
node = 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 Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr TreeNode
node' <- b -> IO (Ptr TreeNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
node
Ptr Tree -> Ptr TreeNode -> IO ()
dzl_tree_set_root Ptr Tree
self' Ptr TreeNode
node'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
node
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TreeSetRootMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsTree a, Dazzle.TreeNode.IsTreeNode b) => O.OverloadedMethod TreeSetRootMethodInfo a signature where
overloadedMethod = treeSetRoot
instance O.OverloadedMethodInfo TreeSetRootMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeSetRoot",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeSetRoot"
})
#endif
foreign import ccall "dzl_tree_set_show_icons" dzl_tree_set_show_icons ::
Ptr Tree ->
CInt ->
IO ()
treeSetShowIcons ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
a
-> Bool
-> m ()
treeSetShowIcons :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTree a) =>
a -> Bool -> m ()
treeSetShowIcons a
self Bool
showIcons = 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 Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
let showIcons' :: CInt
showIcons' = (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
showIcons
Ptr Tree -> CInt -> IO ()
dzl_tree_set_show_icons Ptr Tree
self' CInt
showIcons'
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 TreeSetShowIconsMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTree a) => O.OverloadedMethod TreeSetShowIconsMethodInfo a signature where
overloadedMethod = treeSetShowIcons
instance O.OverloadedMethodInfo TreeSetShowIconsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeSetShowIcons",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeSetShowIcons"
})
#endif
foreign import ccall "dzl_tree_unselect_all" dzl_tree_unselect_all ::
Ptr Tree ->
IO ()
treeUnselectAll ::
(B.CallStack.HasCallStack, MonadIO m, IsTree a) =>
a
-> m ()
treeUnselectAll :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTree a) =>
a -> m ()
treeUnselectAll a
self = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Tree
self' <- a -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Tree -> IO ()
dzl_tree_unselect_all Ptr Tree
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TreeUnselectAllMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTree a) => O.OverloadedMethod TreeUnselectAllMethodInfo a signature where
overloadedMethod = treeUnselectAll
instance O.OverloadedMethodInfo TreeUnselectAllMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.Tree.treeUnselectAll",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.1/docs/GI-Dazzle-Objects-Tree.html#v:treeUnselectAll"
})
#endif