{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.CpuGraph
(
CpuGraph(..) ,
IsCpuGraph ,
toCpuGraph ,
#if defined(ENABLE_OVERLOADING)
ResolveCpuGraphMethod ,
#endif
cpuGraphNewFull ,
#if defined(ENABLE_OVERLOADING)
CpuGraphMaxSamplesPropertyInfo ,
#endif
constructCpuGraphMaxSamples ,
#if defined(ENABLE_OVERLOADING)
cpuGraphMaxSamples ,
#endif
getCpuGraphMaxSamples ,
#if defined(ENABLE_OVERLOADING)
CpuGraphTimespanPropertyInfo ,
#endif
constructCpuGraphTimespan ,
#if defined(ENABLE_OVERLOADING)
cpuGraphTimespan ,
#endif
getCpuGraphTimespan ,
) 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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.RectangleInt as Cairo.RectangleInt
import {-# SOURCE #-} qualified GI.Dazzle.Interfaces.GraphRenderer as Dazzle.GraphRenderer
import {-# SOURCE #-} qualified GI.Dazzle.Objects.GraphColumn as Dazzle.GraphColumn
import {-# SOURCE #-} qualified GI.Dazzle.Objects.GraphModel as Dazzle.GraphModel
import {-# SOURCE #-} qualified GI.Dazzle.Objects.GraphView as Dazzle.GraphView
import {-# SOURCE #-} qualified GI.Dazzle.Structs.GraphModelIter as Dazzle.GraphModelIter
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.DrawingArea as Gtk.DrawingArea
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#else
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import {-# SOURCE #-} qualified GI.Dazzle.Objects.GraphView as Dazzle.GraphView
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.DrawingArea as Gtk.DrawingArea
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#endif
newtype CpuGraph = CpuGraph (SP.ManagedPtr CpuGraph)
deriving (CpuGraph -> CpuGraph -> Bool
(CpuGraph -> CpuGraph -> Bool)
-> (CpuGraph -> CpuGraph -> Bool) -> Eq CpuGraph
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CpuGraph -> CpuGraph -> Bool
== :: CpuGraph -> CpuGraph -> Bool
$c/= :: CpuGraph -> CpuGraph -> Bool
/= :: CpuGraph -> CpuGraph -> Bool
Eq)
instance SP.ManagedPtrNewtype CpuGraph where
toManagedPtr :: CpuGraph -> ManagedPtr CpuGraph
toManagedPtr (CpuGraph ManagedPtr CpuGraph
p) = ManagedPtr CpuGraph
p
foreign import ccall "dzl_cpu_graph_get_type"
c_dzl_cpu_graph_get_type :: IO B.Types.GType
instance B.Types.TypedObject CpuGraph where
glibType :: IO GType
glibType = IO GType
c_dzl_cpu_graph_get_type
instance B.Types.GObject CpuGraph
class (SP.GObject o, O.IsDescendantOf CpuGraph o) => IsCpuGraph o
instance (SP.GObject o, O.IsDescendantOf CpuGraph o) => IsCpuGraph o
instance O.HasParentTypes CpuGraph
type instance O.ParentTypes CpuGraph = '[Dazzle.GraphView.GraphView, Gtk.DrawingArea.DrawingArea, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable]
toCpuGraph :: (MIO.MonadIO m, IsCpuGraph o) => o -> m CpuGraph
toCpuGraph :: forall (m :: * -> *) o.
(MonadIO m, IsCpuGraph o) =>
o -> m CpuGraph
toCpuGraph = IO CpuGraph -> m CpuGraph
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO CpuGraph -> m CpuGraph)
-> (o -> IO CpuGraph) -> o -> m CpuGraph
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr CpuGraph -> CpuGraph) -> o -> IO CpuGraph
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr CpuGraph -> CpuGraph
CpuGraph
instance B.GValue.IsGValue (Maybe CpuGraph) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_cpu_graph_get_type
gvalueSet_ :: Ptr GValue -> Maybe CpuGraph -> IO ()
gvalueSet_ Ptr GValue
gv Maybe CpuGraph
P.Nothing = Ptr GValue -> Ptr CpuGraph -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr CpuGraph
forall a. Ptr a
FP.nullPtr :: FP.Ptr CpuGraph)
gvalueSet_ Ptr GValue
gv (P.Just CpuGraph
obj) = CpuGraph -> (Ptr CpuGraph -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr CpuGraph
obj (Ptr GValue -> Ptr CpuGraph -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe CpuGraph)
gvalueGet_ Ptr GValue
gv = do
Ptr CpuGraph
ptr <- Ptr GValue -> IO (Ptr CpuGraph)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr CpuGraph)
if Ptr CpuGraph
ptr Ptr CpuGraph -> Ptr CpuGraph -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CpuGraph
forall a. Ptr a
FP.nullPtr
then CpuGraph -> Maybe CpuGraph
forall a. a -> Maybe a
P.Just (CpuGraph -> Maybe CpuGraph) -> IO CpuGraph -> IO (Maybe CpuGraph)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr CpuGraph -> CpuGraph) -> Ptr CpuGraph -> IO CpuGraph
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr CpuGraph -> CpuGraph
CpuGraph Ptr CpuGraph
ptr
else Maybe CpuGraph -> IO (Maybe CpuGraph)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CpuGraph
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveCpuGraphMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveCpuGraphMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveCpuGraphMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveCpuGraphMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveCpuGraphMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveCpuGraphMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveCpuGraphMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveCpuGraphMethod "addRenderer" o = Dazzle.GraphView.GraphViewAddRendererMethodInfo
ResolveCpuGraphMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveCpuGraphMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveCpuGraphMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveCpuGraphMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveCpuGraphMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveCpuGraphMethod "childNotify" o = Gtk.Widget.WidgetChildNotifyMethodInfo
ResolveCpuGraphMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveCpuGraphMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveCpuGraphMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveCpuGraphMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveCpuGraphMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveCpuGraphMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveCpuGraphMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveCpuGraphMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveCpuGraphMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveCpuGraphMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveCpuGraphMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveCpuGraphMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveCpuGraphMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveCpuGraphMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveCpuGraphMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveCpuGraphMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveCpuGraphMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveCpuGraphMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveCpuGraphMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveCpuGraphMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveCpuGraphMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveCpuGraphMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveCpuGraphMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveCpuGraphMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveCpuGraphMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveCpuGraphMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveCpuGraphMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveCpuGraphMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveCpuGraphMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveCpuGraphMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveCpuGraphMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveCpuGraphMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveCpuGraphMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveCpuGraphMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveCpuGraphMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveCpuGraphMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveCpuGraphMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveCpuGraphMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveCpuGraphMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveCpuGraphMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveCpuGraphMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveCpuGraphMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveCpuGraphMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveCpuGraphMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveCpuGraphMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveCpuGraphMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveCpuGraphMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveCpuGraphMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveCpuGraphMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveCpuGraphMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveCpuGraphMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveCpuGraphMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveCpuGraphMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveCpuGraphMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveCpuGraphMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveCpuGraphMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveCpuGraphMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveCpuGraphMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveCpuGraphMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveCpuGraphMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveCpuGraphMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveCpuGraphMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveCpuGraphMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveCpuGraphMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveCpuGraphMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveCpuGraphMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveCpuGraphMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveCpuGraphMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveCpuGraphMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveCpuGraphMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveCpuGraphMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveCpuGraphMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveCpuGraphMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveCpuGraphMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveCpuGraphMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveCpuGraphMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveCpuGraphMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveCpuGraphMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveCpuGraphMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveCpuGraphMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveCpuGraphMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveCpuGraphMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveCpuGraphMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveCpuGraphMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveCpuGraphMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveCpuGraphMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveCpuGraphMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveCpuGraphMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveCpuGraphMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveCpuGraphMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveCpuGraphMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveCpuGraphMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveCpuGraphMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveCpuGraphMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveCpuGraphMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveCpuGraphMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveCpuGraphMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveCpuGraphMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveCpuGraphMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveCpuGraphMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveCpuGraphMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveCpuGraphMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveCpuGraphMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveCpuGraphMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveCpuGraphMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveCpuGraphMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveCpuGraphMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveCpuGraphMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveCpuGraphMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveCpuGraphMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveCpuGraphMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveCpuGraphMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveCpuGraphMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveCpuGraphMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveCpuGraphMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveCpuGraphMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveCpuGraphMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveCpuGraphMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveCpuGraphMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveCpuGraphMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveCpuGraphMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveCpuGraphMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveCpuGraphMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveCpuGraphMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveCpuGraphMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveCpuGraphMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveCpuGraphMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveCpuGraphMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveCpuGraphMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveCpuGraphMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveCpuGraphMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveCpuGraphMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveCpuGraphMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveCpuGraphMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveCpuGraphMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveCpuGraphMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveCpuGraphMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveCpuGraphMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveCpuGraphMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveCpuGraphMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveCpuGraphMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveCpuGraphMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveCpuGraphMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveCpuGraphMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveCpuGraphMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveCpuGraphMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveCpuGraphMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveCpuGraphMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveCpuGraphMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveCpuGraphMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveCpuGraphMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveCpuGraphMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveCpuGraphMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveCpuGraphMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveCpuGraphMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveCpuGraphMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveCpuGraphMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveCpuGraphMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveCpuGraphMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveCpuGraphMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveCpuGraphMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveCpuGraphMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveCpuGraphMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveCpuGraphMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveCpuGraphMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveCpuGraphMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveCpuGraphMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveCpuGraphMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveCpuGraphMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveCpuGraphMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveCpuGraphMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveCpuGraphMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveCpuGraphMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveCpuGraphMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveCpuGraphMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveCpuGraphMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveCpuGraphMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveCpuGraphMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveCpuGraphMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveCpuGraphMethod "getModel" o = Dazzle.GraphView.GraphViewGetModelMethodInfo
ResolveCpuGraphMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveCpuGraphMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveCpuGraphMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveCpuGraphMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveCpuGraphMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveCpuGraphMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveCpuGraphMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveCpuGraphMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveCpuGraphMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveCpuGraphMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveCpuGraphMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveCpuGraphMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveCpuGraphMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveCpuGraphMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveCpuGraphMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveCpuGraphMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveCpuGraphMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveCpuGraphMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveCpuGraphMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveCpuGraphMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveCpuGraphMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveCpuGraphMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveCpuGraphMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveCpuGraphMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveCpuGraphMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveCpuGraphMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveCpuGraphMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveCpuGraphMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveCpuGraphMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveCpuGraphMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveCpuGraphMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveCpuGraphMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveCpuGraphMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveCpuGraphMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveCpuGraphMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveCpuGraphMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveCpuGraphMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveCpuGraphMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveCpuGraphMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveCpuGraphMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveCpuGraphMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveCpuGraphMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveCpuGraphMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveCpuGraphMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveCpuGraphMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveCpuGraphMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveCpuGraphMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveCpuGraphMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveCpuGraphMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveCpuGraphMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveCpuGraphMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveCpuGraphMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveCpuGraphMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveCpuGraphMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveCpuGraphMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveCpuGraphMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveCpuGraphMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveCpuGraphMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveCpuGraphMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveCpuGraphMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveCpuGraphMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveCpuGraphMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveCpuGraphMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveCpuGraphMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveCpuGraphMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveCpuGraphMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveCpuGraphMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveCpuGraphMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveCpuGraphMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveCpuGraphMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveCpuGraphMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveCpuGraphMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveCpuGraphMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveCpuGraphMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveCpuGraphMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveCpuGraphMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveCpuGraphMethod "setModel" o = Dazzle.GraphView.GraphViewSetModelMethodInfo
ResolveCpuGraphMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveCpuGraphMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveCpuGraphMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveCpuGraphMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveCpuGraphMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveCpuGraphMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveCpuGraphMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveCpuGraphMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveCpuGraphMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveCpuGraphMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveCpuGraphMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveCpuGraphMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveCpuGraphMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveCpuGraphMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveCpuGraphMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveCpuGraphMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveCpuGraphMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveCpuGraphMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveCpuGraphMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveCpuGraphMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveCpuGraphMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveCpuGraphMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveCpuGraphMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveCpuGraphMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveCpuGraphMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveCpuGraphMethod t CpuGraph, O.OverloadedMethod info CpuGraph p) => OL.IsLabel t (CpuGraph -> 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 ~ ResolveCpuGraphMethod t CpuGraph, O.OverloadedMethod info CpuGraph p, R.HasField t CpuGraph p) => R.HasField t CpuGraph p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveCpuGraphMethod t CpuGraph, O.OverloadedMethodInfo info CpuGraph) => OL.IsLabel t (O.MethodProxy info CpuGraph) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getCpuGraphMaxSamples :: (MonadIO m, IsCpuGraph o) => o -> m Word32
getCpuGraphMaxSamples :: forall (m :: * -> *) o. (MonadIO m, IsCpuGraph o) => o -> m Word32
getCpuGraphMaxSamples o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"max-samples"
constructCpuGraphMaxSamples :: (IsCpuGraph o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructCpuGraphMaxSamples :: forall o (m :: * -> *).
(IsCpuGraph o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructCpuGraphMaxSamples Word32
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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"max-samples" Word32
val
#if defined(ENABLE_OVERLOADING)
data CpuGraphMaxSamplesPropertyInfo
instance AttrInfo CpuGraphMaxSamplesPropertyInfo where
type AttrAllowedOps CpuGraphMaxSamplesPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint CpuGraphMaxSamplesPropertyInfo = IsCpuGraph
type AttrSetTypeConstraint CpuGraphMaxSamplesPropertyInfo = (~) Word32
type AttrTransferTypeConstraint CpuGraphMaxSamplesPropertyInfo = (~) Word32
type AttrTransferType CpuGraphMaxSamplesPropertyInfo = Word32
type AttrGetType CpuGraphMaxSamplesPropertyInfo = Word32
type AttrLabel CpuGraphMaxSamplesPropertyInfo = "max-samples"
type AttrOrigin CpuGraphMaxSamplesPropertyInfo = CpuGraph
attrGet = getCpuGraphMaxSamples
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructCpuGraphMaxSamples
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.CpuGraph.maxSamples"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-CpuGraph.html#g:attr:maxSamples"
})
#endif
getCpuGraphTimespan :: (MonadIO m, IsCpuGraph o) => o -> m Int64
getCpuGraphTimespan :: forall (m :: * -> *) o. (MonadIO m, IsCpuGraph o) => o -> m Int64
getCpuGraphTimespan o
obj = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int64
forall a. GObject a => a -> String -> IO Int64
B.Properties.getObjectPropertyInt64 o
obj String
"timespan"
constructCpuGraphTimespan :: (IsCpuGraph o, MIO.MonadIO m) => Int64 -> m (GValueConstruct o)
constructCpuGraphTimespan :: forall o (m :: * -> *).
(IsCpuGraph o, MonadIO m) =>
Int64 -> m (GValueConstruct o)
constructCpuGraphTimespan Int64
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 -> Int64 -> IO (GValueConstruct o)
forall o. String -> Int64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt64 String
"timespan" Int64
val
#if defined(ENABLE_OVERLOADING)
data CpuGraphTimespanPropertyInfo
instance AttrInfo CpuGraphTimespanPropertyInfo where
type AttrAllowedOps CpuGraphTimespanPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint CpuGraphTimespanPropertyInfo = IsCpuGraph
type AttrSetTypeConstraint CpuGraphTimespanPropertyInfo = (~) Int64
type AttrTransferTypeConstraint CpuGraphTimespanPropertyInfo = (~) Int64
type AttrTransferType CpuGraphTimespanPropertyInfo = Int64
type AttrGetType CpuGraphTimespanPropertyInfo = Int64
type AttrLabel CpuGraphTimespanPropertyInfo = "timespan"
type AttrOrigin CpuGraphTimespanPropertyInfo = CpuGraph
attrGet = getCpuGraphTimespan
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructCpuGraphTimespan
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.CpuGraph.timespan"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-CpuGraph.html#g:attr:timespan"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CpuGraph
type instance O.AttributeList CpuGraph = CpuGraphAttributeList
type CpuGraphAttributeList = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("maxSamples", CpuGraphMaxSamplesPropertyInfo), '("model", Dazzle.GraphView.GraphViewModelPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("timespan", CpuGraphTimespanPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
cpuGraphMaxSamples :: AttrLabelProxy "maxSamples"
cpuGraphMaxSamples = AttrLabelProxy
cpuGraphTimespan :: AttrLabelProxy "timespan"
cpuGraphTimespan = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList CpuGraph = CpuGraphSignalList
type CpuGraphSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_cpu_graph_new_full" dzl_cpu_graph_new_full ::
Int64 ->
Word32 ->
IO (Ptr CpuGraph)
cpuGraphNewFull ::
(B.CallStack.HasCallStack, MonadIO m) =>
Int64
-> Word32
-> m CpuGraph
cpuGraphNewFull :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Int64 -> Word32 -> m CpuGraph
cpuGraphNewFull Int64
timespan Word32
maxSamples = IO CpuGraph -> m CpuGraph
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CpuGraph -> m CpuGraph) -> IO CpuGraph -> m CpuGraph
forall a b. (a -> b) -> a -> b
$ do
Ptr CpuGraph
result <- Int64 -> Word32 -> IO (Ptr CpuGraph)
dzl_cpu_graph_new_full Int64
timespan Word32
maxSamples
Text -> Ptr CpuGraph -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cpuGraphNewFull" Ptr CpuGraph
result
CpuGraph
result' <- ((ManagedPtr CpuGraph -> CpuGraph) -> Ptr CpuGraph -> IO CpuGraph
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CpuGraph -> CpuGraph
CpuGraph) Ptr CpuGraph
result
CpuGraph -> IO CpuGraph
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CpuGraph
result'
#if defined(ENABLE_OVERLOADING)
#endif