{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.FrameClock
(
FrameClock(..) ,
IsFrameClock ,
toFrameClock ,
#if defined(ENABLE_OVERLOADING)
ResolveFrameClockMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
FrameClockBeginUpdatingMethodInfo ,
#endif
frameClockBeginUpdating ,
#if defined(ENABLE_OVERLOADING)
FrameClockEndUpdatingMethodInfo ,
#endif
frameClockEndUpdating ,
#if defined(ENABLE_OVERLOADING)
FrameClockGetCurrentTimingsMethodInfo ,
#endif
frameClockGetCurrentTimings ,
#if defined(ENABLE_OVERLOADING)
FrameClockGetFrameCounterMethodInfo ,
#endif
frameClockGetFrameCounter ,
#if defined(ENABLE_OVERLOADING)
FrameClockGetFrameTimeMethodInfo ,
#endif
frameClockGetFrameTime ,
#if defined(ENABLE_OVERLOADING)
FrameClockGetHistoryStartMethodInfo ,
#endif
frameClockGetHistoryStart ,
#if defined(ENABLE_OVERLOADING)
FrameClockGetRefreshInfoMethodInfo ,
#endif
frameClockGetRefreshInfo ,
#if defined(ENABLE_OVERLOADING)
FrameClockGetTimingsMethodInfo ,
#endif
frameClockGetTimings ,
#if defined(ENABLE_OVERLOADING)
FrameClockRequestPhaseMethodInfo ,
#endif
frameClockRequestPhase ,
C_FrameClockAfterPaintCallback ,
FrameClockAfterPaintCallback ,
#if defined(ENABLE_OVERLOADING)
FrameClockAfterPaintSignalInfo ,
#endif
afterFrameClockAfterPaint ,
genClosure_FrameClockAfterPaint ,
mk_FrameClockAfterPaintCallback ,
noFrameClockAfterPaintCallback ,
onFrameClockAfterPaint ,
wrap_FrameClockAfterPaintCallback ,
C_FrameClockBeforePaintCallback ,
FrameClockBeforePaintCallback ,
#if defined(ENABLE_OVERLOADING)
FrameClockBeforePaintSignalInfo ,
#endif
afterFrameClockBeforePaint ,
genClosure_FrameClockBeforePaint ,
mk_FrameClockBeforePaintCallback ,
noFrameClockBeforePaintCallback ,
onFrameClockBeforePaint ,
wrap_FrameClockBeforePaintCallback ,
C_FrameClockFlushEventsCallback ,
FrameClockFlushEventsCallback ,
#if defined(ENABLE_OVERLOADING)
FrameClockFlushEventsSignalInfo ,
#endif
afterFrameClockFlushEvents ,
genClosure_FrameClockFlushEvents ,
mk_FrameClockFlushEventsCallback ,
noFrameClockFlushEventsCallback ,
onFrameClockFlushEvents ,
wrap_FrameClockFlushEventsCallback ,
C_FrameClockLayoutCallback ,
FrameClockLayoutCallback ,
#if defined(ENABLE_OVERLOADING)
FrameClockLayoutSignalInfo ,
#endif
afterFrameClockLayout ,
genClosure_FrameClockLayout ,
mk_FrameClockLayoutCallback ,
noFrameClockLayoutCallback ,
onFrameClockLayout ,
wrap_FrameClockLayoutCallback ,
C_FrameClockPaintCallback ,
FrameClockPaintCallback ,
#if defined(ENABLE_OVERLOADING)
FrameClockPaintSignalInfo ,
#endif
afterFrameClockPaint ,
genClosure_FrameClockPaint ,
mk_FrameClockPaintCallback ,
noFrameClockPaintCallback ,
onFrameClockPaint ,
wrap_FrameClockPaintCallback ,
C_FrameClockResumeEventsCallback ,
FrameClockResumeEventsCallback ,
#if defined(ENABLE_OVERLOADING)
FrameClockResumeEventsSignalInfo ,
#endif
afterFrameClockResumeEvents ,
genClosure_FrameClockResumeEvents ,
mk_FrameClockResumeEventsCallback ,
noFrameClockResumeEventsCallback ,
onFrameClockResumeEvents ,
wrap_FrameClockResumeEventsCallback ,
C_FrameClockUpdateCallback ,
FrameClockUpdateCallback ,
#if defined(ENABLE_OVERLOADING)
FrameClockUpdateSignalInfo ,
#endif
afterFrameClockUpdate ,
genClosure_FrameClockUpdate ,
mk_FrameClockUpdateCallback ,
noFrameClockUpdateCallback ,
onFrameClockUpdate ,
wrap_FrameClockUpdateCallback ,
) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
newtype FrameClock = FrameClock (SP.ManagedPtr FrameClock)
deriving (FrameClock -> FrameClock -> Bool
(FrameClock -> FrameClock -> Bool)
-> (FrameClock -> FrameClock -> Bool) -> Eq FrameClock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FrameClock -> FrameClock -> Bool
$c/= :: FrameClock -> FrameClock -> Bool
== :: FrameClock -> FrameClock -> Bool
$c== :: FrameClock -> FrameClock -> Bool
Eq)
instance SP.ManagedPtrNewtype FrameClock where
toManagedPtr :: FrameClock -> ManagedPtr FrameClock
toManagedPtr (FrameClock ManagedPtr FrameClock
p) = ManagedPtr FrameClock
p
foreign import ccall "gdk_frame_clock_get_type"
c_gdk_frame_clock_get_type :: IO B.Types.GType
instance B.Types.TypedObject FrameClock where
glibType :: IO GType
glibType = IO GType
c_gdk_frame_clock_get_type
instance B.Types.GObject FrameClock
instance B.GValue.IsGValue FrameClock where
toGValue :: FrameClock -> IO GValue
toGValue FrameClock
o = do
GType
gtype <- IO GType
c_gdk_frame_clock_get_type
FrameClock -> (Ptr FrameClock -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FrameClock
o (GType
-> (GValue -> Ptr FrameClock -> IO ())
-> Ptr FrameClock
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr FrameClock -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO FrameClock
fromGValue GValue
gv = do
Ptr FrameClock
ptr <- GValue -> IO (Ptr FrameClock)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr FrameClock)
(ManagedPtr FrameClock -> FrameClock)
-> Ptr FrameClock -> IO FrameClock
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr FrameClock -> FrameClock
FrameClock Ptr FrameClock
ptr
class (SP.GObject o, O.IsDescendantOf FrameClock o) => IsFrameClock o
instance (SP.GObject o, O.IsDescendantOf FrameClock o) => IsFrameClock o
instance O.HasParentTypes FrameClock
type instance O.ParentTypes FrameClock = '[GObject.Object.Object]
toFrameClock :: (MonadIO m, IsFrameClock o) => o -> m FrameClock
toFrameClock :: o -> m FrameClock
toFrameClock = IO FrameClock -> m FrameClock
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FrameClock -> m FrameClock)
-> (o -> IO FrameClock) -> o -> m FrameClock
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr FrameClock -> FrameClock) -> o -> IO FrameClock
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr FrameClock -> FrameClock
FrameClock
#if defined(ENABLE_OVERLOADING)
type family ResolveFrameClockMethod (t :: Symbol) (o :: *) :: * where
ResolveFrameClockMethod "beginUpdating" o = FrameClockBeginUpdatingMethodInfo
ResolveFrameClockMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveFrameClockMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveFrameClockMethod "endUpdating" o = FrameClockEndUpdatingMethodInfo
ResolveFrameClockMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveFrameClockMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveFrameClockMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveFrameClockMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveFrameClockMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveFrameClockMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveFrameClockMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveFrameClockMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveFrameClockMethod "requestPhase" o = FrameClockRequestPhaseMethodInfo
ResolveFrameClockMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveFrameClockMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveFrameClockMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveFrameClockMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveFrameClockMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveFrameClockMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveFrameClockMethod "getCurrentTimings" o = FrameClockGetCurrentTimingsMethodInfo
ResolveFrameClockMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveFrameClockMethod "getFrameCounter" o = FrameClockGetFrameCounterMethodInfo
ResolveFrameClockMethod "getFrameTime" o = FrameClockGetFrameTimeMethodInfo
ResolveFrameClockMethod "getHistoryStart" o = FrameClockGetHistoryStartMethodInfo
ResolveFrameClockMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveFrameClockMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveFrameClockMethod "getRefreshInfo" o = FrameClockGetRefreshInfoMethodInfo
ResolveFrameClockMethod "getTimings" o = FrameClockGetTimingsMethodInfo
ResolveFrameClockMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveFrameClockMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveFrameClockMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveFrameClockMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveFrameClockMethod t FrameClock, O.MethodInfo info FrameClock p) => OL.IsLabel t (FrameClock -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
type FrameClockAfterPaintCallback =
IO ()
noFrameClockAfterPaintCallback :: Maybe FrameClockAfterPaintCallback
noFrameClockAfterPaintCallback :: Maybe (IO ())
noFrameClockAfterPaintCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_FrameClockAfterPaintCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FrameClockAfterPaintCallback :: C_FrameClockAfterPaintCallback -> IO (FunPtr C_FrameClockAfterPaintCallback)
genClosure_FrameClockAfterPaint :: MonadIO m => FrameClockAfterPaintCallback -> m (GClosure C_FrameClockAfterPaintCallback)
genClosure_FrameClockAfterPaint :: IO () -> m (GClosure C_FrameClockAfterPaintCallback)
genClosure_FrameClockAfterPaint IO ()
cb = IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockAfterPaintCallback IO ()
cb
C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockAfterPaintCallback C_FrameClockAfterPaintCallback
cb' IO (FunPtr C_FrameClockAfterPaintCallback)
-> (FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_FrameClockAfterPaintCallback ::
FrameClockAfterPaintCallback ->
C_FrameClockAfterPaintCallback
wrap_FrameClockAfterPaintCallback :: IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockAfterPaintCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onFrameClockAfterPaint :: (IsFrameClock a, MonadIO m) => a -> FrameClockAfterPaintCallback -> m SignalHandlerId
onFrameClockAfterPaint :: a -> IO () -> m SignalHandlerId
onFrameClockAfterPaint a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockAfterPaintCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockAfterPaintCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"after-paint" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFrameClockAfterPaint :: (IsFrameClock a, MonadIO m) => a -> FrameClockAfterPaintCallback -> m SignalHandlerId
afterFrameClockAfterPaint :: a -> IO () -> m SignalHandlerId
afterFrameClockAfterPaint a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockAfterPaintCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockAfterPaintCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"after-paint" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FrameClockAfterPaintSignalInfo
instance SignalInfo FrameClockAfterPaintSignalInfo where
type HaskellCallbackType FrameClockAfterPaintSignalInfo = FrameClockAfterPaintCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FrameClockAfterPaintCallback cb
cb'' <- mk_FrameClockAfterPaintCallback cb'
connectSignalFunPtr obj "after-paint" cb'' connectMode detail
#endif
type FrameClockBeforePaintCallback =
IO ()
noFrameClockBeforePaintCallback :: Maybe FrameClockBeforePaintCallback
noFrameClockBeforePaintCallback :: Maybe (IO ())
noFrameClockBeforePaintCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_FrameClockBeforePaintCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FrameClockBeforePaintCallback :: C_FrameClockBeforePaintCallback -> IO (FunPtr C_FrameClockBeforePaintCallback)
genClosure_FrameClockBeforePaint :: MonadIO m => FrameClockBeforePaintCallback -> m (GClosure C_FrameClockBeforePaintCallback)
genClosure_FrameClockBeforePaint :: IO () -> m (GClosure C_FrameClockAfterPaintCallback)
genClosure_FrameClockBeforePaint IO ()
cb = IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockBeforePaintCallback IO ()
cb
C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockBeforePaintCallback C_FrameClockAfterPaintCallback
cb' IO (FunPtr C_FrameClockAfterPaintCallback)
-> (FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_FrameClockBeforePaintCallback ::
FrameClockBeforePaintCallback ->
C_FrameClockBeforePaintCallback
wrap_FrameClockBeforePaintCallback :: IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockBeforePaintCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onFrameClockBeforePaint :: (IsFrameClock a, MonadIO m) => a -> FrameClockBeforePaintCallback -> m SignalHandlerId
onFrameClockBeforePaint :: a -> IO () -> m SignalHandlerId
onFrameClockBeforePaint a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockBeforePaintCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockBeforePaintCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"before-paint" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFrameClockBeforePaint :: (IsFrameClock a, MonadIO m) => a -> FrameClockBeforePaintCallback -> m SignalHandlerId
afterFrameClockBeforePaint :: a -> IO () -> m SignalHandlerId
afterFrameClockBeforePaint a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockBeforePaintCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockBeforePaintCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"before-paint" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FrameClockBeforePaintSignalInfo
instance SignalInfo FrameClockBeforePaintSignalInfo where
type HaskellCallbackType FrameClockBeforePaintSignalInfo = FrameClockBeforePaintCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FrameClockBeforePaintCallback cb
cb'' <- mk_FrameClockBeforePaintCallback cb'
connectSignalFunPtr obj "before-paint" cb'' connectMode detail
#endif
type FrameClockFlushEventsCallback =
IO ()
noFrameClockFlushEventsCallback :: Maybe FrameClockFlushEventsCallback
noFrameClockFlushEventsCallback :: Maybe (IO ())
noFrameClockFlushEventsCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_FrameClockFlushEventsCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FrameClockFlushEventsCallback :: C_FrameClockFlushEventsCallback -> IO (FunPtr C_FrameClockFlushEventsCallback)
genClosure_FrameClockFlushEvents :: MonadIO m => FrameClockFlushEventsCallback -> m (GClosure C_FrameClockFlushEventsCallback)
genClosure_FrameClockFlushEvents :: IO () -> m (GClosure C_FrameClockAfterPaintCallback)
genClosure_FrameClockFlushEvents IO ()
cb = IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockFlushEventsCallback IO ()
cb
C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockFlushEventsCallback C_FrameClockAfterPaintCallback
cb' IO (FunPtr C_FrameClockAfterPaintCallback)
-> (FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_FrameClockFlushEventsCallback ::
FrameClockFlushEventsCallback ->
C_FrameClockFlushEventsCallback
wrap_FrameClockFlushEventsCallback :: IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockFlushEventsCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onFrameClockFlushEvents :: (IsFrameClock a, MonadIO m) => a -> FrameClockFlushEventsCallback -> m SignalHandlerId
onFrameClockFlushEvents :: a -> IO () -> m SignalHandlerId
onFrameClockFlushEvents a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockFlushEventsCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockFlushEventsCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"flush-events" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFrameClockFlushEvents :: (IsFrameClock a, MonadIO m) => a -> FrameClockFlushEventsCallback -> m SignalHandlerId
afterFrameClockFlushEvents :: a -> IO () -> m SignalHandlerId
afterFrameClockFlushEvents a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockFlushEventsCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockFlushEventsCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"flush-events" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FrameClockFlushEventsSignalInfo
instance SignalInfo FrameClockFlushEventsSignalInfo where
type HaskellCallbackType FrameClockFlushEventsSignalInfo = FrameClockFlushEventsCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FrameClockFlushEventsCallback cb
cb'' <- mk_FrameClockFlushEventsCallback cb'
connectSignalFunPtr obj "flush-events" cb'' connectMode detail
#endif
type FrameClockLayoutCallback =
IO ()
noFrameClockLayoutCallback :: Maybe FrameClockLayoutCallback
noFrameClockLayoutCallback :: Maybe (IO ())
noFrameClockLayoutCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_FrameClockLayoutCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FrameClockLayoutCallback :: C_FrameClockLayoutCallback -> IO (FunPtr C_FrameClockLayoutCallback)
genClosure_FrameClockLayout :: MonadIO m => FrameClockLayoutCallback -> m (GClosure C_FrameClockLayoutCallback)
genClosure_FrameClockLayout :: IO () -> m (GClosure C_FrameClockAfterPaintCallback)
genClosure_FrameClockLayout IO ()
cb = IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockLayoutCallback IO ()
cb
C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockLayoutCallback C_FrameClockAfterPaintCallback
cb' IO (FunPtr C_FrameClockAfterPaintCallback)
-> (FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_FrameClockLayoutCallback ::
FrameClockLayoutCallback ->
C_FrameClockLayoutCallback
wrap_FrameClockLayoutCallback :: IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockLayoutCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onFrameClockLayout :: (IsFrameClock a, MonadIO m) => a -> FrameClockLayoutCallback -> m SignalHandlerId
onFrameClockLayout :: a -> IO () -> m SignalHandlerId
onFrameClockLayout a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockLayoutCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockLayoutCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"layout" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFrameClockLayout :: (IsFrameClock a, MonadIO m) => a -> FrameClockLayoutCallback -> m SignalHandlerId
afterFrameClockLayout :: a -> IO () -> m SignalHandlerId
afterFrameClockLayout a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockLayoutCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockLayoutCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"layout" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FrameClockLayoutSignalInfo
instance SignalInfo FrameClockLayoutSignalInfo where
type HaskellCallbackType FrameClockLayoutSignalInfo = FrameClockLayoutCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FrameClockLayoutCallback cb
cb'' <- mk_FrameClockLayoutCallback cb'
connectSignalFunPtr obj "layout" cb'' connectMode detail
#endif
type FrameClockPaintCallback =
IO ()
noFrameClockPaintCallback :: Maybe FrameClockPaintCallback
noFrameClockPaintCallback :: Maybe (IO ())
noFrameClockPaintCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_FrameClockPaintCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FrameClockPaintCallback :: C_FrameClockPaintCallback -> IO (FunPtr C_FrameClockPaintCallback)
genClosure_FrameClockPaint :: MonadIO m => FrameClockPaintCallback -> m (GClosure C_FrameClockPaintCallback)
genClosure_FrameClockPaint :: IO () -> m (GClosure C_FrameClockAfterPaintCallback)
genClosure_FrameClockPaint IO ()
cb = IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockPaintCallback IO ()
cb
C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockPaintCallback C_FrameClockAfterPaintCallback
cb' IO (FunPtr C_FrameClockAfterPaintCallback)
-> (FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_FrameClockPaintCallback ::
FrameClockPaintCallback ->
C_FrameClockPaintCallback
wrap_FrameClockPaintCallback :: IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockPaintCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onFrameClockPaint :: (IsFrameClock a, MonadIO m) => a -> FrameClockPaintCallback -> m SignalHandlerId
onFrameClockPaint :: a -> IO () -> m SignalHandlerId
onFrameClockPaint a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockPaintCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockPaintCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"paint" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFrameClockPaint :: (IsFrameClock a, MonadIO m) => a -> FrameClockPaintCallback -> m SignalHandlerId
afterFrameClockPaint :: a -> IO () -> m SignalHandlerId
afterFrameClockPaint a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockPaintCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockPaintCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"paint" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FrameClockPaintSignalInfo
instance SignalInfo FrameClockPaintSignalInfo where
type HaskellCallbackType FrameClockPaintSignalInfo = FrameClockPaintCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FrameClockPaintCallback cb
cb'' <- mk_FrameClockPaintCallback cb'
connectSignalFunPtr obj "paint" cb'' connectMode detail
#endif
type FrameClockResumeEventsCallback =
IO ()
noFrameClockResumeEventsCallback :: Maybe FrameClockResumeEventsCallback
noFrameClockResumeEventsCallback :: Maybe (IO ())
noFrameClockResumeEventsCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_FrameClockResumeEventsCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FrameClockResumeEventsCallback :: C_FrameClockResumeEventsCallback -> IO (FunPtr C_FrameClockResumeEventsCallback)
genClosure_FrameClockResumeEvents :: MonadIO m => FrameClockResumeEventsCallback -> m (GClosure C_FrameClockResumeEventsCallback)
genClosure_FrameClockResumeEvents :: IO () -> m (GClosure C_FrameClockAfterPaintCallback)
genClosure_FrameClockResumeEvents IO ()
cb = IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockResumeEventsCallback IO ()
cb
C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockResumeEventsCallback C_FrameClockAfterPaintCallback
cb' IO (FunPtr C_FrameClockAfterPaintCallback)
-> (FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_FrameClockResumeEventsCallback ::
FrameClockResumeEventsCallback ->
C_FrameClockResumeEventsCallback
wrap_FrameClockResumeEventsCallback :: IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockResumeEventsCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onFrameClockResumeEvents :: (IsFrameClock a, MonadIO m) => a -> FrameClockResumeEventsCallback -> m SignalHandlerId
onFrameClockResumeEvents :: a -> IO () -> m SignalHandlerId
onFrameClockResumeEvents a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockResumeEventsCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockResumeEventsCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"resume-events" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFrameClockResumeEvents :: (IsFrameClock a, MonadIO m) => a -> FrameClockResumeEventsCallback -> m SignalHandlerId
afterFrameClockResumeEvents :: a -> IO () -> m SignalHandlerId
afterFrameClockResumeEvents a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockResumeEventsCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockResumeEventsCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"resume-events" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FrameClockResumeEventsSignalInfo
instance SignalInfo FrameClockResumeEventsSignalInfo where
type HaskellCallbackType FrameClockResumeEventsSignalInfo = FrameClockResumeEventsCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FrameClockResumeEventsCallback cb
cb'' <- mk_FrameClockResumeEventsCallback cb'
connectSignalFunPtr obj "resume-events" cb'' connectMode detail
#endif
type FrameClockUpdateCallback =
IO ()
noFrameClockUpdateCallback :: Maybe FrameClockUpdateCallback
noFrameClockUpdateCallback :: Maybe (IO ())
noFrameClockUpdateCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_FrameClockUpdateCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FrameClockUpdateCallback :: C_FrameClockUpdateCallback -> IO (FunPtr C_FrameClockUpdateCallback)
genClosure_FrameClockUpdate :: MonadIO m => FrameClockUpdateCallback -> m (GClosure C_FrameClockUpdateCallback)
genClosure_FrameClockUpdate :: IO () -> m (GClosure C_FrameClockAfterPaintCallback)
genClosure_FrameClockUpdate IO ()
cb = IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
-> m (GClosure C_FrameClockAfterPaintCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockUpdateCallback IO ()
cb
C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockUpdateCallback C_FrameClockAfterPaintCallback
cb' IO (FunPtr C_FrameClockAfterPaintCallback)
-> (FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback))
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FrameClockAfterPaintCallback
-> IO (GClosure C_FrameClockAfterPaintCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_FrameClockUpdateCallback ::
FrameClockUpdateCallback ->
C_FrameClockUpdateCallback
wrap_FrameClockUpdateCallback :: IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockUpdateCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onFrameClockUpdate :: (IsFrameClock a, MonadIO m) => a -> FrameClockUpdateCallback -> m SignalHandlerId
onFrameClockUpdate :: a -> IO () -> m SignalHandlerId
onFrameClockUpdate a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockUpdateCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockUpdateCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"update" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFrameClockUpdate :: (IsFrameClock a, MonadIO m) => a -> FrameClockUpdateCallback -> m SignalHandlerId
afterFrameClockUpdate :: a -> IO () -> m SignalHandlerId
afterFrameClockUpdate a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_FrameClockAfterPaintCallback
cb' = IO () -> C_FrameClockAfterPaintCallback
wrap_FrameClockUpdateCallback IO ()
cb
FunPtr C_FrameClockAfterPaintCallback
cb'' <- C_FrameClockAfterPaintCallback
-> IO (FunPtr C_FrameClockAfterPaintCallback)
mk_FrameClockUpdateCallback C_FrameClockAfterPaintCallback
cb'
a
-> Text
-> FunPtr C_FrameClockAfterPaintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"update" FunPtr C_FrameClockAfterPaintCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data FrameClockUpdateSignalInfo
instance SignalInfo FrameClockUpdateSignalInfo where
type HaskellCallbackType FrameClockUpdateSignalInfo = FrameClockUpdateCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FrameClockUpdateCallback cb
cb'' <- mk_FrameClockUpdateCallback cb'
connectSignalFunPtr obj "update" cb'' connectMode detail
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FrameClock
type instance O.AttributeList FrameClock = FrameClockAttributeList
type FrameClockAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FrameClock = FrameClockSignalList
type FrameClockSignalList = ('[ '("afterPaint", FrameClockAfterPaintSignalInfo), '("beforePaint", FrameClockBeforePaintSignalInfo), '("flushEvents", FrameClockFlushEventsSignalInfo), '("layout", FrameClockLayoutSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("paint", FrameClockPaintSignalInfo), '("resumeEvents", FrameClockResumeEventsSignalInfo), '("update", FrameClockUpdateSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gdk_frame_clock_begin_updating" gdk_frame_clock_begin_updating ::
Ptr FrameClock ->
IO ()
frameClockBeginUpdating ::
(B.CallStack.HasCallStack, MonadIO m, IsFrameClock a) =>
a
-> m ()
frameClockBeginUpdating :: a -> m ()
frameClockBeginUpdating a
frameClock = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr FrameClock
frameClock' <- a -> IO (Ptr FrameClock)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
frameClock
Ptr FrameClock -> IO ()
gdk_frame_clock_begin_updating Ptr FrameClock
frameClock'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
frameClock
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FrameClockBeginUpdatingMethodInfo
instance (signature ~ (m ()), MonadIO m, IsFrameClock a) => O.MethodInfo FrameClockBeginUpdatingMethodInfo a signature where
overloadedMethod = frameClockBeginUpdating
#endif
foreign import ccall "gdk_frame_clock_end_updating" gdk_frame_clock_end_updating ::
Ptr FrameClock ->
IO ()
frameClockEndUpdating ::
(B.CallStack.HasCallStack, MonadIO m, IsFrameClock a) =>
a
-> m ()
frameClockEndUpdating :: a -> m ()
frameClockEndUpdating a
frameClock = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr FrameClock
frameClock' <- a -> IO (Ptr FrameClock)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
frameClock
Ptr FrameClock -> IO ()
gdk_frame_clock_end_updating Ptr FrameClock
frameClock'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
frameClock
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FrameClockEndUpdatingMethodInfo
instance (signature ~ (m ()), MonadIO m, IsFrameClock a) => O.MethodInfo FrameClockEndUpdatingMethodInfo a signature where
overloadedMethod = frameClockEndUpdating
#endif
foreign import ccall "gdk_frame_clock_get_current_timings" gdk_frame_clock_get_current_timings ::
Ptr FrameClock ->
IO (Ptr Gdk.FrameTimings.FrameTimings)
frameClockGetCurrentTimings ::
(B.CallStack.HasCallStack, MonadIO m, IsFrameClock a) =>
a
-> m (Maybe Gdk.FrameTimings.FrameTimings)
frameClockGetCurrentTimings :: a -> m (Maybe FrameTimings)
frameClockGetCurrentTimings a
frameClock = IO (Maybe FrameTimings) -> m (Maybe FrameTimings)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FrameTimings) -> m (Maybe FrameTimings))
-> IO (Maybe FrameTimings) -> m (Maybe FrameTimings)
forall a b. (a -> b) -> a -> b
$ do
Ptr FrameClock
frameClock' <- a -> IO (Ptr FrameClock)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
frameClock
Ptr FrameTimings
result <- Ptr FrameClock -> IO (Ptr FrameTimings)
gdk_frame_clock_get_current_timings Ptr FrameClock
frameClock'
Maybe FrameTimings
maybeResult <- Ptr FrameTimings
-> (Ptr FrameTimings -> IO FrameTimings) -> IO (Maybe FrameTimings)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FrameTimings
result ((Ptr FrameTimings -> IO FrameTimings) -> IO (Maybe FrameTimings))
-> (Ptr FrameTimings -> IO FrameTimings) -> IO (Maybe FrameTimings)
forall a b. (a -> b) -> a -> b
$ \Ptr FrameTimings
result' -> do
FrameTimings
result'' <- ((ManagedPtr FrameTimings -> FrameTimings)
-> Ptr FrameTimings -> IO FrameTimings
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr FrameTimings -> FrameTimings
Gdk.FrameTimings.FrameTimings) Ptr FrameTimings
result'
FrameTimings -> IO FrameTimings
forall (m :: * -> *) a. Monad m => a -> m a
return FrameTimings
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
frameClock
Maybe FrameTimings -> IO (Maybe FrameTimings)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FrameTimings
maybeResult
#if defined(ENABLE_OVERLOADING)
data FrameClockGetCurrentTimingsMethodInfo
instance (signature ~ (m (Maybe Gdk.FrameTimings.FrameTimings)), MonadIO m, IsFrameClock a) => O.MethodInfo FrameClockGetCurrentTimingsMethodInfo a signature where
overloadedMethod = frameClockGetCurrentTimings
#endif
foreign import ccall "gdk_frame_clock_get_frame_counter" gdk_frame_clock_get_frame_counter ::
Ptr FrameClock ->
IO Int64
frameClockGetFrameCounter ::
(B.CallStack.HasCallStack, MonadIO m, IsFrameClock a) =>
a
-> m Int64
frameClockGetFrameCounter :: a -> m Int64
frameClockGetFrameCounter a
frameClock = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
Ptr FrameClock
frameClock' <- a -> IO (Ptr FrameClock)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
frameClock
Int64
result <- Ptr FrameClock -> IO Int64
gdk_frame_clock_get_frame_counter Ptr FrameClock
frameClock'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
frameClock
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
#if defined(ENABLE_OVERLOADING)
data FrameClockGetFrameCounterMethodInfo
instance (signature ~ (m Int64), MonadIO m, IsFrameClock a) => O.MethodInfo FrameClockGetFrameCounterMethodInfo a signature where
overloadedMethod = frameClockGetFrameCounter
#endif
foreign import ccall "gdk_frame_clock_get_frame_time" gdk_frame_clock_get_frame_time ::
Ptr FrameClock ->
IO Int64
frameClockGetFrameTime ::
(B.CallStack.HasCallStack, MonadIO m, IsFrameClock a) =>
a
-> m Int64
frameClockGetFrameTime :: a -> m Int64
frameClockGetFrameTime a
frameClock = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
Ptr FrameClock
frameClock' <- a -> IO (Ptr FrameClock)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
frameClock
Int64
result <- Ptr FrameClock -> IO Int64
gdk_frame_clock_get_frame_time Ptr FrameClock
frameClock'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
frameClock
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
#if defined(ENABLE_OVERLOADING)
data FrameClockGetFrameTimeMethodInfo
instance (signature ~ (m Int64), MonadIO m, IsFrameClock a) => O.MethodInfo FrameClockGetFrameTimeMethodInfo a signature where
overloadedMethod = frameClockGetFrameTime
#endif
foreign import ccall "gdk_frame_clock_get_history_start" gdk_frame_clock_get_history_start ::
Ptr FrameClock ->
IO Int64
frameClockGetHistoryStart ::
(B.CallStack.HasCallStack, MonadIO m, IsFrameClock a) =>
a
-> m Int64
frameClockGetHistoryStart :: a -> m Int64
frameClockGetHistoryStart a
frameClock = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
Ptr FrameClock
frameClock' <- a -> IO (Ptr FrameClock)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
frameClock
Int64
result <- Ptr FrameClock -> IO Int64
gdk_frame_clock_get_history_start Ptr FrameClock
frameClock'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
frameClock
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
#if defined(ENABLE_OVERLOADING)
data FrameClockGetHistoryStartMethodInfo
instance (signature ~ (m Int64), MonadIO m, IsFrameClock a) => O.MethodInfo FrameClockGetHistoryStartMethodInfo a signature where
overloadedMethod = frameClockGetHistoryStart
#endif
foreign import ccall "gdk_frame_clock_get_refresh_info" gdk_frame_clock_get_refresh_info ::
Ptr FrameClock ->
Int64 ->
Ptr Int64 ->
Ptr Int64 ->
IO ()
frameClockGetRefreshInfo ::
(B.CallStack.HasCallStack, MonadIO m, IsFrameClock a) =>
a
-> Int64
-> m ((Int64, Int64))
frameClockGetRefreshInfo :: a -> Int64 -> m (Int64, Int64)
frameClockGetRefreshInfo a
frameClock Int64
baseTime = IO (Int64, Int64) -> m (Int64, Int64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int64, Int64) -> m (Int64, Int64))
-> IO (Int64, Int64) -> m (Int64, Int64)
forall a b. (a -> b) -> a -> b
$ do
Ptr FrameClock
frameClock' <- a -> IO (Ptr FrameClock)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
frameClock
Ptr Int64
refreshIntervalReturn <- IO (Ptr Int64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int64)
Ptr Int64
presentationTimeReturn <- IO (Ptr Int64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int64)
Ptr FrameClock -> Int64 -> Ptr Int64 -> Ptr Int64 -> IO ()
gdk_frame_clock_get_refresh_info Ptr FrameClock
frameClock' Int64
baseTime Ptr Int64
refreshIntervalReturn Ptr Int64
presentationTimeReturn
Int64
refreshIntervalReturn' <- Ptr Int64 -> IO Int64
forall a. Storable a => Ptr a -> IO a
peek Ptr Int64
refreshIntervalReturn
Int64
presentationTimeReturn' <- Ptr Int64 -> IO Int64
forall a. Storable a => Ptr a -> IO a
peek Ptr Int64
presentationTimeReturn
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
frameClock
Ptr Int64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int64
refreshIntervalReturn
Ptr Int64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int64
presentationTimeReturn
(Int64, Int64) -> IO (Int64, Int64)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int64
refreshIntervalReturn', Int64
presentationTimeReturn')
#if defined(ENABLE_OVERLOADING)
data FrameClockGetRefreshInfoMethodInfo
instance (signature ~ (Int64 -> m ((Int64, Int64))), MonadIO m, IsFrameClock a) => O.MethodInfo FrameClockGetRefreshInfoMethodInfo a signature where
overloadedMethod = frameClockGetRefreshInfo
#endif
foreign import ccall "gdk_frame_clock_get_timings" gdk_frame_clock_get_timings ::
Ptr FrameClock ->
Int64 ->
IO (Ptr Gdk.FrameTimings.FrameTimings)
frameClockGetTimings ::
(B.CallStack.HasCallStack, MonadIO m, IsFrameClock a) =>
a
-> Int64
-> m (Maybe Gdk.FrameTimings.FrameTimings)
frameClockGetTimings :: a -> Int64 -> m (Maybe FrameTimings)
frameClockGetTimings a
frameClock Int64
frameCounter = IO (Maybe FrameTimings) -> m (Maybe FrameTimings)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FrameTimings) -> m (Maybe FrameTimings))
-> IO (Maybe FrameTimings) -> m (Maybe FrameTimings)
forall a b. (a -> b) -> a -> b
$ do
Ptr FrameClock
frameClock' <- a -> IO (Ptr FrameClock)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
frameClock
Ptr FrameTimings
result <- Ptr FrameClock -> Int64 -> IO (Ptr FrameTimings)
gdk_frame_clock_get_timings Ptr FrameClock
frameClock' Int64
frameCounter
Maybe FrameTimings
maybeResult <- Ptr FrameTimings
-> (Ptr FrameTimings -> IO FrameTimings) -> IO (Maybe FrameTimings)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FrameTimings
result ((Ptr FrameTimings -> IO FrameTimings) -> IO (Maybe FrameTimings))
-> (Ptr FrameTimings -> IO FrameTimings) -> IO (Maybe FrameTimings)
forall a b. (a -> b) -> a -> b
$ \Ptr FrameTimings
result' -> do
FrameTimings
result'' <- ((ManagedPtr FrameTimings -> FrameTimings)
-> Ptr FrameTimings -> IO FrameTimings
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr FrameTimings -> FrameTimings
Gdk.FrameTimings.FrameTimings) Ptr FrameTimings
result'
FrameTimings -> IO FrameTimings
forall (m :: * -> *) a. Monad m => a -> m a
return FrameTimings
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
frameClock
Maybe FrameTimings -> IO (Maybe FrameTimings)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FrameTimings
maybeResult
#if defined(ENABLE_OVERLOADING)
data FrameClockGetTimingsMethodInfo
instance (signature ~ (Int64 -> m (Maybe Gdk.FrameTimings.FrameTimings)), MonadIO m, IsFrameClock a) => O.MethodInfo FrameClockGetTimingsMethodInfo a signature where
overloadedMethod = frameClockGetTimings
#endif
foreign import ccall "gdk_frame_clock_request_phase" gdk_frame_clock_request_phase ::
Ptr FrameClock ->
CUInt ->
IO ()
frameClockRequestPhase ::
(B.CallStack.HasCallStack, MonadIO m, IsFrameClock a) =>
a
-> [Gdk.Flags.FrameClockPhase]
-> m ()
frameClockRequestPhase :: a -> [FrameClockPhase] -> m ()
frameClockRequestPhase a
frameClock [FrameClockPhase]
phase = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr FrameClock
frameClock' <- a -> IO (Ptr FrameClock)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
frameClock
let phase' :: CUInt
phase' = [FrameClockPhase] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [FrameClockPhase]
phase
Ptr FrameClock -> CUInt -> IO ()
gdk_frame_clock_request_phase Ptr FrameClock
frameClock' CUInt
phase'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
frameClock
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FrameClockRequestPhaseMethodInfo
instance (signature ~ ([Gdk.Flags.FrameClockPhase] -> m ()), MonadIO m, IsFrameClock a) => O.MethodInfo FrameClockRequestPhaseMethodInfo a signature where
overloadedMethod = frameClockRequestPhase
#endif