{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.Snapshot
(
Snapshot(..) ,
IsSnapshot ,
toSnapshot ,
#if defined(ENABLE_OVERLOADING)
ResolveSnapshotMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SnapshotAppendBorderMethodInfo ,
#endif
snapshotAppendBorder ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendCairoMethodInfo ,
#endif
snapshotAppendCairo ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendColorMethodInfo ,
#endif
snapshotAppendColor ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendConicGradientMethodInfo ,
#endif
snapshotAppendConicGradient ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendInsetShadowMethodInfo ,
#endif
snapshotAppendInsetShadow ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendLayoutMethodInfo ,
#endif
snapshotAppendLayout ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendLinearGradientMethodInfo ,
#endif
snapshotAppendLinearGradient ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendNodeMethodInfo ,
#endif
snapshotAppendNode ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendOutsetShadowMethodInfo ,
#endif
snapshotAppendOutsetShadow ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendRadialGradientMethodInfo ,
#endif
snapshotAppendRadialGradient ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendRepeatingLinearGradientMethodInfo,
#endif
snapshotAppendRepeatingLinearGradient ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendRepeatingRadialGradientMethodInfo,
#endif
snapshotAppendRepeatingRadialGradient ,
#if defined(ENABLE_OVERLOADING)
SnapshotAppendTextureMethodInfo ,
#endif
snapshotAppendTexture ,
#if defined(ENABLE_OVERLOADING)
SnapshotGlShaderPopTextureMethodInfo ,
#endif
snapshotGlShaderPopTexture ,
snapshotNew ,
#if defined(ENABLE_OVERLOADING)
SnapshotPerspectiveMethodInfo ,
#endif
snapshotPerspective ,
#if defined(ENABLE_OVERLOADING)
SnapshotPopMethodInfo ,
#endif
snapshotPop ,
#if defined(ENABLE_OVERLOADING)
SnapshotPushBlendMethodInfo ,
#endif
snapshotPushBlend ,
#if defined(ENABLE_OVERLOADING)
SnapshotPushBlurMethodInfo ,
#endif
snapshotPushBlur ,
#if defined(ENABLE_OVERLOADING)
SnapshotPushClipMethodInfo ,
#endif
snapshotPushClip ,
#if defined(ENABLE_OVERLOADING)
SnapshotPushColorMatrixMethodInfo ,
#endif
snapshotPushColorMatrix ,
#if defined(ENABLE_OVERLOADING)
SnapshotPushCrossFadeMethodInfo ,
#endif
snapshotPushCrossFade ,
#if defined(ENABLE_OVERLOADING)
SnapshotPushGlShaderMethodInfo ,
#endif
snapshotPushGlShader ,
#if defined(ENABLE_OVERLOADING)
SnapshotPushOpacityMethodInfo ,
#endif
snapshotPushOpacity ,
#if defined(ENABLE_OVERLOADING)
SnapshotPushRepeatMethodInfo ,
#endif
snapshotPushRepeat ,
#if defined(ENABLE_OVERLOADING)
SnapshotPushRoundedClipMethodInfo ,
#endif
snapshotPushRoundedClip ,
#if defined(ENABLE_OVERLOADING)
SnapshotPushShadowMethodInfo ,
#endif
snapshotPushShadow ,
#if defined(ENABLE_OVERLOADING)
SnapshotRenderBackgroundMethodInfo ,
#endif
snapshotRenderBackground ,
#if defined(ENABLE_OVERLOADING)
SnapshotRenderFocusMethodInfo ,
#endif
snapshotRenderFocus ,
#if defined(ENABLE_OVERLOADING)
SnapshotRenderFrameMethodInfo ,
#endif
snapshotRenderFrame ,
#if defined(ENABLE_OVERLOADING)
SnapshotRenderInsertionCursorMethodInfo ,
#endif
snapshotRenderInsertionCursor ,
#if defined(ENABLE_OVERLOADING)
SnapshotRenderLayoutMethodInfo ,
#endif
snapshotRenderLayout ,
#if defined(ENABLE_OVERLOADING)
SnapshotRestoreMethodInfo ,
#endif
snapshotRestore ,
#if defined(ENABLE_OVERLOADING)
SnapshotRotateMethodInfo ,
#endif
snapshotRotate ,
#if defined(ENABLE_OVERLOADING)
SnapshotRotate3dMethodInfo ,
#endif
snapshotRotate3d ,
#if defined(ENABLE_OVERLOADING)
SnapshotSaveMethodInfo ,
#endif
snapshotSave ,
#if defined(ENABLE_OVERLOADING)
SnapshotScaleMethodInfo ,
#endif
snapshotScale ,
#if defined(ENABLE_OVERLOADING)
SnapshotScale3dMethodInfo ,
#endif
snapshotScale3d ,
#if defined(ENABLE_OVERLOADING)
SnapshotToNodeMethodInfo ,
#endif
snapshotToNode ,
#if defined(ENABLE_OVERLOADING)
SnapshotToPaintableMethodInfo ,
#endif
snapshotToPaintable ,
#if defined(ENABLE_OVERLOADING)
SnapshotTransformMethodInfo ,
#endif
snapshotTransform ,
#if defined(ENABLE_OVERLOADING)
SnapshotTransformMatrixMethodInfo ,
#endif
snapshotTransformMatrix ,
#if defined(ENABLE_OVERLOADING)
SnapshotTranslateMethodInfo ,
#endif
snapshotTranslate ,
#if defined(ENABLE_OVERLOADING)
SnapshotTranslate3dMethodInfo ,
#endif
snapshotTranslate3d ,
) 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.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 GHC.Records as R
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import qualified GI.Gdk.Objects.Texture as Gdk.Texture
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Graphene.Structs.Size as Graphene.Size
import qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3
import qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4
import qualified GI.Gsk.Enums as Gsk.Enums
import qualified GI.Gsk.Objects.GLShader as Gsk.GLShader
import qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import qualified GI.Gsk.Structs.ColorStop as Gsk.ColorStop
import qualified GI.Gsk.Structs.RoundedRect as Gsk.RoundedRect
import qualified GI.Gsk.Structs.Shadow as Gsk.Shadow
import qualified GI.Gsk.Structs.Transform as Gsk.Transform
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Layout as Pango.Layout
newtype Snapshot = Snapshot (SP.ManagedPtr Snapshot)
deriving (Snapshot -> Snapshot -> Bool
(Snapshot -> Snapshot -> Bool)
-> (Snapshot -> Snapshot -> Bool) -> Eq Snapshot
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Snapshot -> Snapshot -> Bool
$c/= :: Snapshot -> Snapshot -> Bool
== :: Snapshot -> Snapshot -> Bool
$c== :: Snapshot -> Snapshot -> Bool
Eq)
instance SP.ManagedPtrNewtype Snapshot where
toManagedPtr :: Snapshot -> ManagedPtr Snapshot
toManagedPtr (Snapshot ManagedPtr Snapshot
p) = ManagedPtr Snapshot
p
foreign import ccall "gtk_snapshot_get_type"
c_gtk_snapshot_get_type :: IO B.Types.GType
instance B.Types.TypedObject Snapshot where
glibType :: IO GType
glibType = IO GType
c_gtk_snapshot_get_type
instance B.Types.GObject Snapshot
class (SP.GObject o, O.IsDescendantOf Snapshot o) => IsSnapshot o
instance (SP.GObject o, O.IsDescendantOf Snapshot o) => IsSnapshot o
instance O.HasParentTypes Snapshot
type instance O.ParentTypes Snapshot = '[Gdk.Snapshot.Snapshot, GObject.Object.Object]
toSnapshot :: (MIO.MonadIO m, IsSnapshot o) => o -> m Snapshot
toSnapshot :: forall (m :: * -> *) o.
(MonadIO m, IsSnapshot o) =>
o -> m Snapshot
toSnapshot = IO Snapshot -> m Snapshot
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Snapshot -> m Snapshot)
-> (o -> IO Snapshot) -> o -> m Snapshot
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Snapshot -> Snapshot) -> o -> IO Snapshot
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Snapshot -> Snapshot
Snapshot
instance B.GValue.IsGValue (Maybe Snapshot) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_snapshot_get_type
gvalueSet_ :: Ptr GValue -> Maybe Snapshot -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Snapshot
P.Nothing = Ptr GValue -> Ptr Snapshot -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Snapshot
forall a. Ptr a
FP.nullPtr :: FP.Ptr Snapshot)
gvalueSet_ Ptr GValue
gv (P.Just Snapshot
obj) = Snapshot -> (Ptr Snapshot -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Snapshot
obj (Ptr GValue -> Ptr Snapshot -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Snapshot)
gvalueGet_ Ptr GValue
gv = do
Ptr Snapshot
ptr <- Ptr GValue -> IO (Ptr Snapshot)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Snapshot)
if Ptr Snapshot
ptr Ptr Snapshot -> Ptr Snapshot -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Snapshot
forall a. Ptr a
FP.nullPtr
then Snapshot -> Maybe Snapshot
forall a. a -> Maybe a
P.Just (Snapshot -> Maybe Snapshot) -> IO Snapshot -> IO (Maybe Snapshot)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Snapshot -> Snapshot) -> Ptr Snapshot -> IO Snapshot
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Snapshot -> Snapshot
Snapshot Ptr Snapshot
ptr
else Maybe Snapshot -> IO (Maybe Snapshot)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Snapshot
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveSnapshotMethod (t :: Symbol) (o :: *) :: * where
ResolveSnapshotMethod "appendBorder" o = SnapshotAppendBorderMethodInfo
ResolveSnapshotMethod "appendCairo" o = SnapshotAppendCairoMethodInfo
ResolveSnapshotMethod "appendColor" o = SnapshotAppendColorMethodInfo
ResolveSnapshotMethod "appendConicGradient" o = SnapshotAppendConicGradientMethodInfo
ResolveSnapshotMethod "appendInsetShadow" o = SnapshotAppendInsetShadowMethodInfo
ResolveSnapshotMethod "appendLayout" o = SnapshotAppendLayoutMethodInfo
ResolveSnapshotMethod "appendLinearGradient" o = SnapshotAppendLinearGradientMethodInfo
ResolveSnapshotMethod "appendNode" o = SnapshotAppendNodeMethodInfo
ResolveSnapshotMethod "appendOutsetShadow" o = SnapshotAppendOutsetShadowMethodInfo
ResolveSnapshotMethod "appendRadialGradient" o = SnapshotAppendRadialGradientMethodInfo
ResolveSnapshotMethod "appendRepeatingLinearGradient" o = SnapshotAppendRepeatingLinearGradientMethodInfo
ResolveSnapshotMethod "appendRepeatingRadialGradient" o = SnapshotAppendRepeatingRadialGradientMethodInfo
ResolveSnapshotMethod "appendTexture" o = SnapshotAppendTextureMethodInfo
ResolveSnapshotMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSnapshotMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSnapshotMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSnapshotMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSnapshotMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSnapshotMethod "glShaderPopTexture" o = SnapshotGlShaderPopTextureMethodInfo
ResolveSnapshotMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSnapshotMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSnapshotMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSnapshotMethod "perspective" o = SnapshotPerspectiveMethodInfo
ResolveSnapshotMethod "pop" o = SnapshotPopMethodInfo
ResolveSnapshotMethod "pushBlend" o = SnapshotPushBlendMethodInfo
ResolveSnapshotMethod "pushBlur" o = SnapshotPushBlurMethodInfo
ResolveSnapshotMethod "pushClip" o = SnapshotPushClipMethodInfo
ResolveSnapshotMethod "pushColorMatrix" o = SnapshotPushColorMatrixMethodInfo
ResolveSnapshotMethod "pushCrossFade" o = SnapshotPushCrossFadeMethodInfo
ResolveSnapshotMethod "pushGlShader" o = SnapshotPushGlShaderMethodInfo
ResolveSnapshotMethod "pushOpacity" o = SnapshotPushOpacityMethodInfo
ResolveSnapshotMethod "pushRepeat" o = SnapshotPushRepeatMethodInfo
ResolveSnapshotMethod "pushRoundedClip" o = SnapshotPushRoundedClipMethodInfo
ResolveSnapshotMethod "pushShadow" o = SnapshotPushShadowMethodInfo
ResolveSnapshotMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSnapshotMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSnapshotMethod "renderBackground" o = SnapshotRenderBackgroundMethodInfo
ResolveSnapshotMethod "renderFocus" o = SnapshotRenderFocusMethodInfo
ResolveSnapshotMethod "renderFrame" o = SnapshotRenderFrameMethodInfo
ResolveSnapshotMethod "renderInsertionCursor" o = SnapshotRenderInsertionCursorMethodInfo
ResolveSnapshotMethod "renderLayout" o = SnapshotRenderLayoutMethodInfo
ResolveSnapshotMethod "restore" o = SnapshotRestoreMethodInfo
ResolveSnapshotMethod "rotate" o = SnapshotRotateMethodInfo
ResolveSnapshotMethod "rotate3d" o = SnapshotRotate3dMethodInfo
ResolveSnapshotMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSnapshotMethod "save" o = SnapshotSaveMethodInfo
ResolveSnapshotMethod "scale" o = SnapshotScaleMethodInfo
ResolveSnapshotMethod "scale3d" o = SnapshotScale3dMethodInfo
ResolveSnapshotMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSnapshotMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSnapshotMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSnapshotMethod "toNode" o = SnapshotToNodeMethodInfo
ResolveSnapshotMethod "toPaintable" o = SnapshotToPaintableMethodInfo
ResolveSnapshotMethod "transform" o = SnapshotTransformMethodInfo
ResolveSnapshotMethod "transformMatrix" o = SnapshotTransformMatrixMethodInfo
ResolveSnapshotMethod "translate" o = SnapshotTranslateMethodInfo
ResolveSnapshotMethod "translate3d" o = SnapshotTranslate3dMethodInfo
ResolveSnapshotMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSnapshotMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSnapshotMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSnapshotMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSnapshotMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSnapshotMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSnapshotMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSnapshotMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSnapshotMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSnapshotMethod t Snapshot, O.OverloadedMethod info Snapshot p) => OL.IsLabel t (Snapshot -> 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 ~ ResolveSnapshotMethod t Snapshot, O.OverloadedMethod info Snapshot p, R.HasField t Snapshot p) => R.HasField t Snapshot p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveSnapshotMethod t Snapshot, O.OverloadedMethodInfo info Snapshot) => OL.IsLabel t (O.MethodProxy info Snapshot) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Snapshot
type instance O.AttributeList Snapshot = SnapshotAttributeList
type SnapshotAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Snapshot = SnapshotSignalList
type SnapshotSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_snapshot_new" gtk_snapshot_new ::
IO (Ptr Snapshot)
snapshotNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Snapshot
snapshotNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Snapshot
snapshotNew = IO Snapshot -> m Snapshot
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Snapshot -> m Snapshot) -> IO Snapshot -> m Snapshot
forall a b. (a -> b) -> a -> b
$ do
Ptr Snapshot
result <- IO (Ptr Snapshot)
gtk_snapshot_new
Text -> Ptr Snapshot -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"snapshotNew" Ptr Snapshot
result
Snapshot
result' <- ((ManagedPtr Snapshot -> Snapshot) -> Ptr Snapshot -> IO Snapshot
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Snapshot -> Snapshot
Snapshot) Ptr Snapshot
result
Snapshot -> IO Snapshot
forall (m :: * -> *) a. Monad m => a -> m a
return Snapshot
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_snapshot_append_border" gtk_snapshot_append_border ::
Ptr Snapshot ->
Ptr Gsk.RoundedRect.RoundedRect ->
Ptr CFloat ->
Ptr Gdk.RGBA.RGBA ->
IO ()
snapshotAppendBorder ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Gsk.RoundedRect.RoundedRect
-> [Float]
-> [Gdk.RGBA.RGBA]
-> m ()
snapshotAppendBorder :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> RoundedRect -> [Float] -> [RGBA] -> m ()
snapshotAppendBorder a
snapshot RoundedRect
outline [Float]
borderWidth [RGBA]
borderColor = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr RoundedRect
outline' <- RoundedRect -> IO (Ptr RoundedRect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RoundedRect
outline
Ptr CFloat
borderWidth' <- ((Float -> CFloat) -> [Float] -> IO (Ptr CFloat)
forall a b. Storable b => (a -> b) -> [a] -> IO (Ptr b)
packMapStorableArray Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac) [Float]
borderWidth
[Ptr RGBA]
borderColor' <- (RGBA -> IO (Ptr RGBA)) -> [RGBA] -> IO [Ptr RGBA]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [RGBA]
borderColor
Ptr RGBA
borderColor'' <- Int -> [Ptr RGBA] -> IO (Ptr RGBA)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
16 [Ptr RGBA]
borderColor'
Ptr Snapshot -> Ptr RoundedRect -> Ptr CFloat -> Ptr RGBA -> IO ()
gtk_snapshot_append_border Ptr Snapshot
snapshot' Ptr RoundedRect
outline' Ptr CFloat
borderWidth' Ptr RGBA
borderColor''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
RoundedRect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RoundedRect
outline
(RGBA -> IO ()) -> [RGBA] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [RGBA]
borderColor
Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
borderWidth'
Ptr RGBA -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr RGBA
borderColor''
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendBorderMethodInfo
instance (signature ~ (Gsk.RoundedRect.RoundedRect -> [Float] -> [Gdk.RGBA.RGBA] -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotAppendBorderMethodInfo a signature where
overloadedMethod = snapshotAppendBorder
instance O.OverloadedMethodInfo SnapshotAppendBorderMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendBorder",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendBorder"
}
#endif
foreign import ccall "gtk_snapshot_append_cairo" gtk_snapshot_append_cairo ::
Ptr Snapshot ->
Ptr Graphene.Rect.Rect ->
IO (Ptr Cairo.Context.Context)
snapshotAppendCairo ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Rect.Rect
-> m Cairo.Context.Context
snapshotAppendCairo :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Rect -> m Context
snapshotAppendCairo a
snapshot Rect
bounds = IO Context -> m Context
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Context -> m Context) -> IO Context -> m Context
forall a b. (a -> b) -> a -> b
$ do
Ptr Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Context
result <- Ptr Snapshot -> Ptr Rect -> IO (Ptr Context)
gtk_snapshot_append_cairo Ptr Snapshot
snapshot' Ptr Rect
bounds'
Text -> Ptr Context -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"snapshotAppendCairo" Ptr Context
result
Context
result' <- ((ManagedPtr Context -> Context) -> Ptr Context -> IO Context
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Context -> Context
Cairo.Context.Context) Ptr Context
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
Context -> IO Context
forall (m :: * -> *) a. Monad m => a -> m a
return Context
result'
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendCairoMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> m Cairo.Context.Context), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotAppendCairoMethodInfo a signature where
overloadedMethod = snapshotAppendCairo
instance O.OverloadedMethodInfo SnapshotAppendCairoMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendCairo",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendCairo"
}
#endif
foreign import ccall "gtk_snapshot_append_color" gtk_snapshot_append_color ::
Ptr Snapshot ->
Ptr Gdk.RGBA.RGBA ->
Ptr Graphene.Rect.Rect ->
IO ()
snapshotAppendColor ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Gdk.RGBA.RGBA
-> Graphene.Rect.Rect
-> m ()
snapshotAppendColor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> RGBA -> Rect -> m ()
snapshotAppendColor a
snapshot RGBA
color Rect
bounds = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr RGBA
color' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
color
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Snapshot -> Ptr RGBA -> Ptr Rect -> IO ()
gtk_snapshot_append_color Ptr Snapshot
snapshot' Ptr RGBA
color' Ptr Rect
bounds'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RGBA
color
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendColorMethodInfo
instance (signature ~ (Gdk.RGBA.RGBA -> Graphene.Rect.Rect -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotAppendColorMethodInfo a signature where
overloadedMethod = snapshotAppendColor
instance O.OverloadedMethodInfo SnapshotAppendColorMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendColor",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendColor"
}
#endif
foreign import ccall "gtk_snapshot_append_conic_gradient" gtk_snapshot_append_conic_gradient ::
Ptr Snapshot ->
Ptr Graphene.Rect.Rect ->
Ptr Graphene.Point.Point ->
CFloat ->
Ptr Gsk.ColorStop.ColorStop ->
Word64 ->
IO ()
snapshotAppendConicGradient ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Rect.Rect
-> Graphene.Point.Point
-> Float
-> [Gsk.ColorStop.ColorStop]
-> m ()
snapshotAppendConicGradient :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Rect -> Point -> Float -> [ColorStop] -> m ()
snapshotAppendConicGradient a
snapshot Rect
bounds Point
center Float
rotation [ColorStop]
stops = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let nStops :: Word64
nStops = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [ColorStop] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [ColorStop]
stops
Ptr Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Point
center' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
center
let rotation' :: CFloat
rotation' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
rotation
[Ptr ColorStop]
stops' <- (ColorStop -> IO (Ptr ColorStop))
-> [ColorStop] -> IO [Ptr ColorStop]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ColorStop -> IO (Ptr ColorStop)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [ColorStop]
stops
Ptr ColorStop
stops'' <- Int -> [Ptr ColorStop] -> IO (Ptr ColorStop)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
20 [Ptr ColorStop]
stops'
Ptr Snapshot
-> Ptr Rect
-> Ptr Point
-> CFloat
-> Ptr ColorStop
-> Word64
-> IO ()
gtk_snapshot_append_conic_gradient Ptr Snapshot
snapshot' Ptr Rect
bounds' Ptr Point
center' CFloat
rotation' Ptr ColorStop
stops'' Word64
nStops
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
center
(ColorStop -> IO ()) -> [ColorStop] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ColorStop -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [ColorStop]
stops
Ptr ColorStop -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr ColorStop
stops''
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendConicGradientMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> Graphene.Point.Point -> Float -> [Gsk.ColorStop.ColorStop] -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotAppendConicGradientMethodInfo a signature where
overloadedMethod = snapshotAppendConicGradient
instance O.OverloadedMethodInfo SnapshotAppendConicGradientMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendConicGradient",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendConicGradient"
}
#endif
foreign import ccall "gtk_snapshot_append_inset_shadow" gtk_snapshot_append_inset_shadow ::
Ptr Snapshot ->
Ptr Gsk.RoundedRect.RoundedRect ->
Ptr Gdk.RGBA.RGBA ->
CFloat ->
CFloat ->
CFloat ->
CFloat ->
IO ()
snapshotAppendInsetShadow ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Gsk.RoundedRect.RoundedRect
-> Gdk.RGBA.RGBA
-> Float
-> Float
-> Float
-> Float
-> m ()
snapshotAppendInsetShadow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> RoundedRect -> RGBA -> Float -> Float -> Float -> Float -> m ()
snapshotAppendInsetShadow a
snapshot RoundedRect
outline RGBA
color Float
dx Float
dy Float
spread Float
blurRadius = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr RoundedRect
outline' <- RoundedRect -> IO (Ptr RoundedRect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RoundedRect
outline
Ptr RGBA
color' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
color
let dx' :: CFloat
dx' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dx
let dy' :: CFloat
dy' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dy
let spread' :: CFloat
spread' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
spread
let blurRadius' :: CFloat
blurRadius' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
blurRadius
Ptr Snapshot
-> Ptr RoundedRect
-> Ptr RGBA
-> CFloat
-> CFloat
-> CFloat
-> CFloat
-> IO ()
gtk_snapshot_append_inset_shadow Ptr Snapshot
snapshot' Ptr RoundedRect
outline' Ptr RGBA
color' CFloat
dx' CFloat
dy' CFloat
spread' CFloat
blurRadius'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
RoundedRect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RoundedRect
outline
RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RGBA
color
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendInsetShadowMethodInfo
instance (signature ~ (Gsk.RoundedRect.RoundedRect -> Gdk.RGBA.RGBA -> Float -> Float -> Float -> Float -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotAppendInsetShadowMethodInfo a signature where
overloadedMethod = snapshotAppendInsetShadow
instance O.OverloadedMethodInfo SnapshotAppendInsetShadowMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendInsetShadow",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendInsetShadow"
}
#endif
foreign import ccall "gtk_snapshot_append_layout" gtk_snapshot_append_layout ::
Ptr Snapshot ->
Ptr Pango.Layout.Layout ->
Ptr Gdk.RGBA.RGBA ->
IO ()
snapshotAppendLayout ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a, Pango.Layout.IsLayout b) =>
a
-> b
-> Gdk.RGBA.RGBA
-> m ()
snapshotAppendLayout :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSnapshot a, IsLayout b) =>
a -> b -> RGBA -> m ()
snapshotAppendLayout a
snapshot b
layout RGBA
color = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Layout
layout' <- b -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
layout
Ptr RGBA
color' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
color
Ptr Snapshot -> Ptr Layout -> Ptr RGBA -> IO ()
gtk_snapshot_append_layout Ptr Snapshot
snapshot' Ptr Layout
layout' Ptr RGBA
color'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
layout
RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RGBA
color
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendLayoutMethodInfo
instance (signature ~ (b -> Gdk.RGBA.RGBA -> m ()), MonadIO m, IsSnapshot a, Pango.Layout.IsLayout b) => O.OverloadedMethod SnapshotAppendLayoutMethodInfo a signature where
overloadedMethod = snapshotAppendLayout
instance O.OverloadedMethodInfo SnapshotAppendLayoutMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendLayout",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendLayout"
}
#endif
foreign import ccall "gtk_snapshot_append_linear_gradient" gtk_snapshot_append_linear_gradient ::
Ptr Snapshot ->
Ptr Graphene.Rect.Rect ->
Ptr Graphene.Point.Point ->
Ptr Graphene.Point.Point ->
Ptr Gsk.ColorStop.ColorStop ->
Word64 ->
IO ()
snapshotAppendLinearGradient ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Rect.Rect
-> Graphene.Point.Point
-> Graphene.Point.Point
-> [Gsk.ColorStop.ColorStop]
-> m ()
snapshotAppendLinearGradient :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Rect -> Point -> Point -> [ColorStop] -> m ()
snapshotAppendLinearGradient a
snapshot Rect
bounds Point
startPoint Point
endPoint [ColorStop]
stops = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let nStops :: Word64
nStops = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [ColorStop] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [ColorStop]
stops
Ptr Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Point
startPoint' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
startPoint
Ptr Point
endPoint' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
endPoint
[Ptr ColorStop]
stops' <- (ColorStop -> IO (Ptr ColorStop))
-> [ColorStop] -> IO [Ptr ColorStop]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ColorStop -> IO (Ptr ColorStop)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [ColorStop]
stops
Ptr ColorStop
stops'' <- Int -> [Ptr ColorStop] -> IO (Ptr ColorStop)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
20 [Ptr ColorStop]
stops'
Ptr Snapshot
-> Ptr Rect
-> Ptr Point
-> Ptr Point
-> Ptr ColorStop
-> Word64
-> IO ()
gtk_snapshot_append_linear_gradient Ptr Snapshot
snapshot' Ptr Rect
bounds' Ptr Point
startPoint' Ptr Point
endPoint' Ptr ColorStop
stops'' Word64
nStops
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
startPoint
Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
endPoint
(ColorStop -> IO ()) -> [ColorStop] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ColorStop -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [ColorStop]
stops
Ptr ColorStop -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr ColorStop
stops''
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendLinearGradientMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> Graphene.Point.Point -> Graphene.Point.Point -> [Gsk.ColorStop.ColorStop] -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotAppendLinearGradientMethodInfo a signature where
overloadedMethod = snapshotAppendLinearGradient
instance O.OverloadedMethodInfo SnapshotAppendLinearGradientMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendLinearGradient",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendLinearGradient"
}
#endif
foreign import ccall "gtk_snapshot_append_node" gtk_snapshot_append_node ::
Ptr Snapshot ->
Ptr Gsk.RenderNode.RenderNode ->
IO ()
snapshotAppendNode ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a, Gsk.RenderNode.IsRenderNode b) =>
a
-> b
-> m ()
snapshotAppendNode :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSnapshot a, IsRenderNode b) =>
a -> b -> m ()
snapshotAppendNode a
snapshot b
node = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr RenderNode
node' <- b -> IO (Ptr RenderNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
node
Ptr Snapshot -> Ptr RenderNode -> IO ()
gtk_snapshot_append_node Ptr Snapshot
snapshot' Ptr RenderNode
node'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
node
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendNodeMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsSnapshot a, Gsk.RenderNode.IsRenderNode b) => O.OverloadedMethod SnapshotAppendNodeMethodInfo a signature where
overloadedMethod = snapshotAppendNode
instance O.OverloadedMethodInfo SnapshotAppendNodeMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendNode",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendNode"
}
#endif
foreign import ccall "gtk_snapshot_append_outset_shadow" gtk_snapshot_append_outset_shadow ::
Ptr Snapshot ->
Ptr Gsk.RoundedRect.RoundedRect ->
Ptr Gdk.RGBA.RGBA ->
CFloat ->
CFloat ->
CFloat ->
CFloat ->
IO ()
snapshotAppendOutsetShadow ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Gsk.RoundedRect.RoundedRect
-> Gdk.RGBA.RGBA
-> Float
-> Float
-> Float
-> Float
-> m ()
snapshotAppendOutsetShadow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> RoundedRect -> RGBA -> Float -> Float -> Float -> Float -> m ()
snapshotAppendOutsetShadow a
snapshot RoundedRect
outline RGBA
color Float
dx Float
dy Float
spread Float
blurRadius = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr RoundedRect
outline' <- RoundedRect -> IO (Ptr RoundedRect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RoundedRect
outline
Ptr RGBA
color' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
color
let dx' :: CFloat
dx' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dx
let dy' :: CFloat
dy' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dy
let spread' :: CFloat
spread' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
spread
let blurRadius' :: CFloat
blurRadius' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
blurRadius
Ptr Snapshot
-> Ptr RoundedRect
-> Ptr RGBA
-> CFloat
-> CFloat
-> CFloat
-> CFloat
-> IO ()
gtk_snapshot_append_outset_shadow Ptr Snapshot
snapshot' Ptr RoundedRect
outline' Ptr RGBA
color' CFloat
dx' CFloat
dy' CFloat
spread' CFloat
blurRadius'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
RoundedRect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RoundedRect
outline
RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RGBA
color
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendOutsetShadowMethodInfo
instance (signature ~ (Gsk.RoundedRect.RoundedRect -> Gdk.RGBA.RGBA -> Float -> Float -> Float -> Float -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotAppendOutsetShadowMethodInfo a signature where
overloadedMethod = snapshotAppendOutsetShadow
instance O.OverloadedMethodInfo SnapshotAppendOutsetShadowMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendOutsetShadow",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendOutsetShadow"
}
#endif
foreign import ccall "gtk_snapshot_append_radial_gradient" gtk_snapshot_append_radial_gradient ::
Ptr Snapshot ->
Ptr Graphene.Rect.Rect ->
Ptr Graphene.Point.Point ->
CFloat ->
CFloat ->
CFloat ->
CFloat ->
Ptr Gsk.ColorStop.ColorStop ->
Word64 ->
IO ()
snapshotAppendRadialGradient ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Rect.Rect
-> Graphene.Point.Point
-> Float
-> Float
-> Float
-> Float
-> [Gsk.ColorStop.ColorStop]
-> m ()
snapshotAppendRadialGradient :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Rect
-> Point
-> Float
-> Float
-> Float
-> Float
-> [ColorStop]
-> m ()
snapshotAppendRadialGradient a
snapshot Rect
bounds Point
center Float
hradius Float
vradius Float
start Float
end [ColorStop]
stops = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let nStops :: Word64
nStops = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [ColorStop] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [ColorStop]
stops
Ptr Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Point
center' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
center
let hradius' :: CFloat
hradius' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
hradius
let vradius' :: CFloat
vradius' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
vradius
let start' :: CFloat
start' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
start
let end' :: CFloat
end' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
end
[Ptr ColorStop]
stops' <- (ColorStop -> IO (Ptr ColorStop))
-> [ColorStop] -> IO [Ptr ColorStop]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ColorStop -> IO (Ptr ColorStop)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [ColorStop]
stops
Ptr ColorStop
stops'' <- Int -> [Ptr ColorStop] -> IO (Ptr ColorStop)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
20 [Ptr ColorStop]
stops'
Ptr Snapshot
-> Ptr Rect
-> Ptr Point
-> CFloat
-> CFloat
-> CFloat
-> CFloat
-> Ptr ColorStop
-> Word64
-> IO ()
gtk_snapshot_append_radial_gradient Ptr Snapshot
snapshot' Ptr Rect
bounds' Ptr Point
center' CFloat
hradius' CFloat
vradius' CFloat
start' CFloat
end' Ptr ColorStop
stops'' Word64
nStops
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
center
(ColorStop -> IO ()) -> [ColorStop] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ColorStop -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [ColorStop]
stops
Ptr ColorStop -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr ColorStop
stops''
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendRadialGradientMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> Graphene.Point.Point -> Float -> Float -> Float -> Float -> [Gsk.ColorStop.ColorStop] -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotAppendRadialGradientMethodInfo a signature where
overloadedMethod = snapshotAppendRadialGradient
instance O.OverloadedMethodInfo SnapshotAppendRadialGradientMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendRadialGradient",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendRadialGradient"
}
#endif
foreign import ccall "gtk_snapshot_append_repeating_linear_gradient" gtk_snapshot_append_repeating_linear_gradient ::
Ptr Snapshot ->
Ptr Graphene.Rect.Rect ->
Ptr Graphene.Point.Point ->
Ptr Graphene.Point.Point ->
Ptr Gsk.ColorStop.ColorStop ->
Word64 ->
IO ()
snapshotAppendRepeatingLinearGradient ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Rect.Rect
-> Graphene.Point.Point
-> Graphene.Point.Point
-> [Gsk.ColorStop.ColorStop]
-> m ()
snapshotAppendRepeatingLinearGradient :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Rect -> Point -> Point -> [ColorStop] -> m ()
snapshotAppendRepeatingLinearGradient a
snapshot Rect
bounds Point
startPoint Point
endPoint [ColorStop]
stops = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let nStops :: Word64
nStops = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [ColorStop] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [ColorStop]
stops
Ptr Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Point
startPoint' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
startPoint
Ptr Point
endPoint' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
endPoint
[Ptr ColorStop]
stops' <- (ColorStop -> IO (Ptr ColorStop))
-> [ColorStop] -> IO [Ptr ColorStop]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ColorStop -> IO (Ptr ColorStop)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [ColorStop]
stops
Ptr ColorStop
stops'' <- Int -> [Ptr ColorStop] -> IO (Ptr ColorStop)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
20 [Ptr ColorStop]
stops'
Ptr Snapshot
-> Ptr Rect
-> Ptr Point
-> Ptr Point
-> Ptr ColorStop
-> Word64
-> IO ()
gtk_snapshot_append_repeating_linear_gradient Ptr Snapshot
snapshot' Ptr Rect
bounds' Ptr Point
startPoint' Ptr Point
endPoint' Ptr ColorStop
stops'' Word64
nStops
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
startPoint
Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
endPoint
(ColorStop -> IO ()) -> [ColorStop] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ColorStop -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [ColorStop]
stops
Ptr ColorStop -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr ColorStop
stops''
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendRepeatingLinearGradientMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> Graphene.Point.Point -> Graphene.Point.Point -> [Gsk.ColorStop.ColorStop] -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotAppendRepeatingLinearGradientMethodInfo a signature where
overloadedMethod = snapshotAppendRepeatingLinearGradient
instance O.OverloadedMethodInfo SnapshotAppendRepeatingLinearGradientMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendRepeatingLinearGradient",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendRepeatingLinearGradient"
}
#endif
foreign import ccall "gtk_snapshot_append_repeating_radial_gradient" gtk_snapshot_append_repeating_radial_gradient ::
Ptr Snapshot ->
Ptr Graphene.Rect.Rect ->
Ptr Graphene.Point.Point ->
CFloat ->
CFloat ->
CFloat ->
CFloat ->
Ptr Gsk.ColorStop.ColorStop ->
Word64 ->
IO ()
snapshotAppendRepeatingRadialGradient ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Rect.Rect
-> Graphene.Point.Point
-> Float
-> Float
-> Float
-> Float
-> [Gsk.ColorStop.ColorStop]
-> m ()
snapshotAppendRepeatingRadialGradient :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Rect
-> Point
-> Float
-> Float
-> Float
-> Float
-> [ColorStop]
-> m ()
snapshotAppendRepeatingRadialGradient a
snapshot Rect
bounds Point
center Float
hradius Float
vradius Float
start Float
end [ColorStop]
stops = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let nStops :: Word64
nStops = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [ColorStop] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [ColorStop]
stops
Ptr Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Point
center' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
center
let hradius' :: CFloat
hradius' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
hradius
let vradius' :: CFloat
vradius' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
vradius
let start' :: CFloat
start' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
start
let end' :: CFloat
end' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
end
[Ptr ColorStop]
stops' <- (ColorStop -> IO (Ptr ColorStop))
-> [ColorStop] -> IO [Ptr ColorStop]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ColorStop -> IO (Ptr ColorStop)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [ColorStop]
stops
Ptr ColorStop
stops'' <- Int -> [Ptr ColorStop] -> IO (Ptr ColorStop)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
20 [Ptr ColorStop]
stops'
Ptr Snapshot
-> Ptr Rect
-> Ptr Point
-> CFloat
-> CFloat
-> CFloat
-> CFloat
-> Ptr ColorStop
-> Word64
-> IO ()
gtk_snapshot_append_repeating_radial_gradient Ptr Snapshot
snapshot' Ptr Rect
bounds' Ptr Point
center' CFloat
hradius' CFloat
vradius' CFloat
start' CFloat
end' Ptr ColorStop
stops'' Word64
nStops
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
center
(ColorStop -> IO ()) -> [ColorStop] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ColorStop -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [ColorStop]
stops
Ptr ColorStop -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr ColorStop
stops''
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendRepeatingRadialGradientMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> Graphene.Point.Point -> Float -> Float -> Float -> Float -> [Gsk.ColorStop.ColorStop] -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotAppendRepeatingRadialGradientMethodInfo a signature where
overloadedMethod = snapshotAppendRepeatingRadialGradient
instance O.OverloadedMethodInfo SnapshotAppendRepeatingRadialGradientMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendRepeatingRadialGradient",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendRepeatingRadialGradient"
}
#endif
foreign import ccall "gtk_snapshot_append_texture" gtk_snapshot_append_texture ::
Ptr Snapshot ->
Ptr Gdk.Texture.Texture ->
Ptr Graphene.Rect.Rect ->
IO ()
snapshotAppendTexture ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a, Gdk.Texture.IsTexture b) =>
a
-> b
-> Graphene.Rect.Rect
-> m ()
snapshotAppendTexture :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSnapshot a, IsTexture b) =>
a -> b -> Rect -> m ()
snapshotAppendTexture a
snapshot b
texture Rect
bounds = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Texture
texture' <- b -> IO (Ptr Texture)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
texture
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Snapshot -> Ptr Texture -> Ptr Rect -> IO ()
gtk_snapshot_append_texture Ptr Snapshot
snapshot' Ptr Texture
texture' Ptr Rect
bounds'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
texture
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotAppendTextureMethodInfo
instance (signature ~ (b -> Graphene.Rect.Rect -> m ()), MonadIO m, IsSnapshot a, Gdk.Texture.IsTexture b) => O.OverloadedMethod SnapshotAppendTextureMethodInfo a signature where
overloadedMethod = snapshotAppendTexture
instance O.OverloadedMethodInfo SnapshotAppendTextureMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotAppendTexture",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotAppendTexture"
}
#endif
foreign import ccall "gtk_snapshot_gl_shader_pop_texture" gtk_snapshot_gl_shader_pop_texture ::
Ptr Snapshot ->
IO ()
snapshotGlShaderPopTexture ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> m ()
snapshotGlShaderPopTexture :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> m ()
snapshotGlShaderPopTexture a
snapshot = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Snapshot -> IO ()
gtk_snapshot_gl_shader_pop_texture Ptr Snapshot
snapshot'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotGlShaderPopTextureMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotGlShaderPopTextureMethodInfo a signature where
overloadedMethod = snapshotGlShaderPopTexture
instance O.OverloadedMethodInfo SnapshotGlShaderPopTextureMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotGlShaderPopTexture",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotGlShaderPopTexture"
}
#endif
foreign import ccall "gtk_snapshot_perspective" gtk_snapshot_perspective ::
Ptr Snapshot ->
CFloat ->
IO ()
snapshotPerspective ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Float
-> m ()
snapshotPerspective :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Float -> m ()
snapshotPerspective a
snapshot Float
depth = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
let depth' :: CFloat
depth' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
depth
Ptr Snapshot -> CFloat -> IO ()
gtk_snapshot_perspective Ptr Snapshot
snapshot' CFloat
depth'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPerspectiveMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPerspectiveMethodInfo a signature where
overloadedMethod = snapshotPerspective
instance O.OverloadedMethodInfo SnapshotPerspectiveMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPerspective",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPerspective"
}
#endif
foreign import ccall "gtk_snapshot_pop" gtk_snapshot_pop ::
Ptr Snapshot ->
IO ()
snapshotPop ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> m ()
snapshotPop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> m ()
snapshotPop a
snapshot = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Snapshot -> IO ()
gtk_snapshot_pop Ptr Snapshot
snapshot'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPopMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPopMethodInfo a signature where
overloadedMethod = snapshotPop
instance O.OverloadedMethodInfo SnapshotPopMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPop",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPop"
}
#endif
foreign import ccall "gtk_snapshot_push_blend" gtk_snapshot_push_blend ::
Ptr Snapshot ->
CUInt ->
IO ()
snapshotPushBlend ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Gsk.Enums.BlendMode
-> m ()
snapshotPushBlend :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> BlendMode -> m ()
snapshotPushBlend a
snapshot BlendMode
blendMode = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
let blendMode' :: CUInt
blendMode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (BlendMode -> Int) -> BlendMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlendMode -> Int
forall a. Enum a => a -> Int
fromEnum) BlendMode
blendMode
Ptr Snapshot -> CUInt -> IO ()
gtk_snapshot_push_blend Ptr Snapshot
snapshot' CUInt
blendMode'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPushBlendMethodInfo
instance (signature ~ (Gsk.Enums.BlendMode -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPushBlendMethodInfo a signature where
overloadedMethod = snapshotPushBlend
instance O.OverloadedMethodInfo SnapshotPushBlendMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPushBlend",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPushBlend"
}
#endif
foreign import ccall "gtk_snapshot_push_blur" gtk_snapshot_push_blur ::
Ptr Snapshot ->
CDouble ->
IO ()
snapshotPushBlur ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Double
-> m ()
snapshotPushBlur :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Double -> m ()
snapshotPushBlur a
snapshot Double
radius = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
let radius' :: CDouble
radius' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
radius
Ptr Snapshot -> CDouble -> IO ()
gtk_snapshot_push_blur Ptr Snapshot
snapshot' CDouble
radius'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPushBlurMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPushBlurMethodInfo a signature where
overloadedMethod = snapshotPushBlur
instance O.OverloadedMethodInfo SnapshotPushBlurMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPushBlur",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPushBlur"
}
#endif
foreign import ccall "gtk_snapshot_push_clip" gtk_snapshot_push_clip ::
Ptr Snapshot ->
Ptr Graphene.Rect.Rect ->
IO ()
snapshotPushClip ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Rect.Rect
-> m ()
snapshotPushClip :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Rect -> m ()
snapshotPushClip a
snapshot Rect
bounds = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Snapshot -> Ptr Rect -> IO ()
gtk_snapshot_push_clip Ptr Snapshot
snapshot' Ptr Rect
bounds'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPushClipMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPushClipMethodInfo a signature where
overloadedMethod = snapshotPushClip
instance O.OverloadedMethodInfo SnapshotPushClipMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPushClip",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPushClip"
}
#endif
foreign import ccall "gtk_snapshot_push_color_matrix" gtk_snapshot_push_color_matrix ::
Ptr Snapshot ->
Ptr Graphene.Matrix.Matrix ->
Ptr Graphene.Vec4.Vec4 ->
IO ()
snapshotPushColorMatrix ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Matrix.Matrix
-> Graphene.Vec4.Vec4
-> m ()
snapshotPushColorMatrix :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Matrix -> Vec4 -> m ()
snapshotPushColorMatrix a
snapshot Matrix
colorMatrix Vec4
colorOffset = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Matrix
colorMatrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
colorMatrix
Ptr Vec4
colorOffset' <- Vec4 -> IO (Ptr Vec4)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec4
colorOffset
Ptr Snapshot -> Ptr Matrix -> Ptr Vec4 -> IO ()
gtk_snapshot_push_color_matrix Ptr Snapshot
snapshot' Ptr Matrix
colorMatrix' Ptr Vec4
colorOffset'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
colorMatrix
Vec4 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec4
colorOffset
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPushColorMatrixMethodInfo
instance (signature ~ (Graphene.Matrix.Matrix -> Graphene.Vec4.Vec4 -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPushColorMatrixMethodInfo a signature where
overloadedMethod = snapshotPushColorMatrix
instance O.OverloadedMethodInfo SnapshotPushColorMatrixMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPushColorMatrix",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPushColorMatrix"
}
#endif
foreign import ccall "gtk_snapshot_push_cross_fade" gtk_snapshot_push_cross_fade ::
Ptr Snapshot ->
CDouble ->
IO ()
snapshotPushCrossFade ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Double
-> m ()
snapshotPushCrossFade :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Double -> m ()
snapshotPushCrossFade a
snapshot Double
progress = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
let progress' :: CDouble
progress' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
progress
Ptr Snapshot -> CDouble -> IO ()
gtk_snapshot_push_cross_fade Ptr Snapshot
snapshot' CDouble
progress'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPushCrossFadeMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPushCrossFadeMethodInfo a signature where
overloadedMethod = snapshotPushCrossFade
instance O.OverloadedMethodInfo SnapshotPushCrossFadeMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPushCrossFade",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPushCrossFade"
}
#endif
foreign import ccall "gtk_snapshot_push_gl_shader" gtk_snapshot_push_gl_shader ::
Ptr Snapshot ->
Ptr Gsk.GLShader.GLShader ->
Ptr Graphene.Rect.Rect ->
Ptr GLib.Bytes.Bytes ->
IO ()
snapshotPushGlShader ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a, Gsk.GLShader.IsGLShader b) =>
a
-> b
-> Graphene.Rect.Rect
-> GLib.Bytes.Bytes
-> m ()
snapshotPushGlShader :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSnapshot a, IsGLShader b) =>
a -> b -> Rect -> Bytes -> m ()
snapshotPushGlShader a
snapshot b
shader Rect
bounds Bytes
takeArgs = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr GLShader
shader' <- b -> IO (Ptr GLShader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
shader
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Bytes
takeArgs' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Bytes
takeArgs
Ptr Snapshot -> Ptr GLShader -> Ptr Rect -> Ptr Bytes -> IO ()
gtk_snapshot_push_gl_shader Ptr Snapshot
snapshot' Ptr GLShader
shader' Ptr Rect
bounds' Ptr Bytes
takeArgs'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
shader
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
takeArgs
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPushGlShaderMethodInfo
instance (signature ~ (b -> Graphene.Rect.Rect -> GLib.Bytes.Bytes -> m ()), MonadIO m, IsSnapshot a, Gsk.GLShader.IsGLShader b) => O.OverloadedMethod SnapshotPushGlShaderMethodInfo a signature where
overloadedMethod = snapshotPushGlShader
instance O.OverloadedMethodInfo SnapshotPushGlShaderMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPushGlShader",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPushGlShader"
}
#endif
foreign import ccall "gtk_snapshot_push_opacity" gtk_snapshot_push_opacity ::
Ptr Snapshot ->
CDouble ->
IO ()
snapshotPushOpacity ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Double
-> m ()
snapshotPushOpacity :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Double -> m ()
snapshotPushOpacity a
snapshot Double
opacity = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
let opacity' :: CDouble
opacity' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
opacity
Ptr Snapshot -> CDouble -> IO ()
gtk_snapshot_push_opacity Ptr Snapshot
snapshot' CDouble
opacity'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPushOpacityMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPushOpacityMethodInfo a signature where
overloadedMethod = snapshotPushOpacity
instance O.OverloadedMethodInfo SnapshotPushOpacityMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPushOpacity",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPushOpacity"
}
#endif
foreign import ccall "gtk_snapshot_push_repeat" gtk_snapshot_push_repeat ::
Ptr Snapshot ->
Ptr Graphene.Rect.Rect ->
Ptr Graphene.Rect.Rect ->
IO ()
snapshotPushRepeat ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Rect.Rect
-> Maybe (Graphene.Rect.Rect)
-> m ()
snapshotPushRepeat :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Rect -> Maybe Rect -> m ()
snapshotPushRepeat a
snapshot Rect
bounds Maybe Rect
childBounds = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
Ptr Rect
maybeChildBounds <- case Maybe Rect
childBounds of
Maybe Rect
Nothing -> Ptr Rect -> IO (Ptr Rect)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Rect
forall a. Ptr a
nullPtr
Just Rect
jChildBounds -> do
Ptr Rect
jChildBounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
jChildBounds
Ptr Rect -> IO (Ptr Rect)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Rect
jChildBounds'
Ptr Snapshot -> Ptr Rect -> Ptr Rect -> IO ()
gtk_snapshot_push_repeat Ptr Snapshot
snapshot' Ptr Rect
bounds' Ptr Rect
maybeChildBounds
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
Maybe Rect -> (Rect -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Rect
childBounds Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPushRepeatMethodInfo
instance (signature ~ (Graphene.Rect.Rect -> Maybe (Graphene.Rect.Rect) -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPushRepeatMethodInfo a signature where
overloadedMethod = snapshotPushRepeat
instance O.OverloadedMethodInfo SnapshotPushRepeatMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPushRepeat",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPushRepeat"
}
#endif
foreign import ccall "gtk_snapshot_push_rounded_clip" gtk_snapshot_push_rounded_clip ::
Ptr Snapshot ->
Ptr Gsk.RoundedRect.RoundedRect ->
IO ()
snapshotPushRoundedClip ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Gsk.RoundedRect.RoundedRect
-> m ()
snapshotPushRoundedClip :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> RoundedRect -> m ()
snapshotPushRoundedClip a
snapshot RoundedRect
bounds = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr RoundedRect
bounds' <- RoundedRect -> IO (Ptr RoundedRect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RoundedRect
bounds
Ptr Snapshot -> Ptr RoundedRect -> IO ()
gtk_snapshot_push_rounded_clip Ptr Snapshot
snapshot' Ptr RoundedRect
bounds'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
RoundedRect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RoundedRect
bounds
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPushRoundedClipMethodInfo
instance (signature ~ (Gsk.RoundedRect.RoundedRect -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPushRoundedClipMethodInfo a signature where
overloadedMethod = snapshotPushRoundedClip
instance O.OverloadedMethodInfo SnapshotPushRoundedClipMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPushRoundedClip",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPushRoundedClip"
}
#endif
foreign import ccall "gtk_snapshot_push_shadow" gtk_snapshot_push_shadow ::
Ptr Snapshot ->
Ptr Gsk.Shadow.Shadow ->
Word64 ->
IO ()
snapshotPushShadow ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Gsk.Shadow.Shadow
-> Word64
-> m ()
snapshotPushShadow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Shadow -> Word64 -> m ()
snapshotPushShadow a
snapshot Shadow
shadow Word64
nShadows = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Shadow
shadow' <- Shadow -> IO (Ptr Shadow)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Shadow
shadow
Ptr Snapshot -> Ptr Shadow -> Word64 -> IO ()
gtk_snapshot_push_shadow Ptr Snapshot
snapshot' Ptr Shadow
shadow' Word64
nShadows
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Shadow -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Shadow
shadow
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotPushShadowMethodInfo
instance (signature ~ (Gsk.Shadow.Shadow -> Word64 -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotPushShadowMethodInfo a signature where
overloadedMethod = snapshotPushShadow
instance O.OverloadedMethodInfo SnapshotPushShadowMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotPushShadow",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotPushShadow"
}
#endif
foreign import ccall "gtk_snapshot_render_background" gtk_snapshot_render_background ::
Ptr Snapshot ->
Ptr Gtk.StyleContext.StyleContext ->
CDouble ->
CDouble ->
CDouble ->
CDouble ->
IO ()
snapshotRenderBackground ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a, Gtk.StyleContext.IsStyleContext b) =>
a
-> b
-> Double
-> Double
-> Double
-> Double
-> m ()
snapshotRenderBackground :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSnapshot a, IsStyleContext b) =>
a -> b -> Double -> Double -> Double -> Double -> m ()
snapshotRenderBackground a
snapshot b
context Double
x Double
y Double
width Double
height = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr StyleContext
context' <- b -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
context
let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
let width' :: CDouble
width' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
width
let height' :: CDouble
height' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
height
Ptr Snapshot
-> Ptr StyleContext
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> IO ()
gtk_snapshot_render_background Ptr Snapshot
snapshot' Ptr StyleContext
context' CDouble
x' CDouble
y' CDouble
width' CDouble
height'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
context
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotRenderBackgroundMethodInfo
instance (signature ~ (b -> Double -> Double -> Double -> Double -> m ()), MonadIO m, IsSnapshot a, Gtk.StyleContext.IsStyleContext b) => O.OverloadedMethod SnapshotRenderBackgroundMethodInfo a signature where
overloadedMethod = snapshotRenderBackground
instance O.OverloadedMethodInfo SnapshotRenderBackgroundMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotRenderBackground",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotRenderBackground"
}
#endif
foreign import ccall "gtk_snapshot_render_focus" gtk_snapshot_render_focus ::
Ptr Snapshot ->
Ptr Gtk.StyleContext.StyleContext ->
CDouble ->
CDouble ->
CDouble ->
CDouble ->
IO ()
snapshotRenderFocus ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a, Gtk.StyleContext.IsStyleContext b) =>
a
-> b
-> Double
-> Double
-> Double
-> Double
-> m ()
snapshotRenderFocus :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSnapshot a, IsStyleContext b) =>
a -> b -> Double -> Double -> Double -> Double -> m ()
snapshotRenderFocus a
snapshot b
context Double
x Double
y Double
width Double
height = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr StyleContext
context' <- b -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
context
let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
let width' :: CDouble
width' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
width
let height' :: CDouble
height' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
height
Ptr Snapshot
-> Ptr StyleContext
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> IO ()
gtk_snapshot_render_focus Ptr Snapshot
snapshot' Ptr StyleContext
context' CDouble
x' CDouble
y' CDouble
width' CDouble
height'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
context
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotRenderFocusMethodInfo
instance (signature ~ (b -> Double -> Double -> Double -> Double -> m ()), MonadIO m, IsSnapshot a, Gtk.StyleContext.IsStyleContext b) => O.OverloadedMethod SnapshotRenderFocusMethodInfo a signature where
overloadedMethod = snapshotRenderFocus
instance O.OverloadedMethodInfo SnapshotRenderFocusMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotRenderFocus",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotRenderFocus"
}
#endif
foreign import ccall "gtk_snapshot_render_frame" gtk_snapshot_render_frame ::
Ptr Snapshot ->
Ptr Gtk.StyleContext.StyleContext ->
CDouble ->
CDouble ->
CDouble ->
CDouble ->
IO ()
snapshotRenderFrame ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a, Gtk.StyleContext.IsStyleContext b) =>
a
-> b
-> Double
-> Double
-> Double
-> Double
-> m ()
snapshotRenderFrame :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSnapshot a, IsStyleContext b) =>
a -> b -> Double -> Double -> Double -> Double -> m ()
snapshotRenderFrame a
snapshot b
context Double
x Double
y Double
width Double
height = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr StyleContext
context' <- b -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
context
let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
let width' :: CDouble
width' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
width
let height' :: CDouble
height' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
height
Ptr Snapshot
-> Ptr StyleContext
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> IO ()
gtk_snapshot_render_frame Ptr Snapshot
snapshot' Ptr StyleContext
context' CDouble
x' CDouble
y' CDouble
width' CDouble
height'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
context
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotRenderFrameMethodInfo
instance (signature ~ (b -> Double -> Double -> Double -> Double -> m ()), MonadIO m, IsSnapshot a, Gtk.StyleContext.IsStyleContext b) => O.OverloadedMethod SnapshotRenderFrameMethodInfo a signature where
overloadedMethod = snapshotRenderFrame
instance O.OverloadedMethodInfo SnapshotRenderFrameMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotRenderFrame",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotRenderFrame"
}
#endif
foreign import ccall "gtk_snapshot_render_insertion_cursor" gtk_snapshot_render_insertion_cursor ::
Ptr Snapshot ->
Ptr Gtk.StyleContext.StyleContext ->
CDouble ->
CDouble ->
Ptr Pango.Layout.Layout ->
Int32 ->
CUInt ->
IO ()
snapshotRenderInsertionCursor ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a, Gtk.StyleContext.IsStyleContext b, Pango.Layout.IsLayout c) =>
a
-> b
-> Double
-> Double
-> c
-> Int32
-> Pango.Enums.Direction
-> m ()
snapshotRenderInsertionCursor :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsSnapshot a, IsStyleContext b,
IsLayout c) =>
a -> b -> Double -> Double -> c -> Int32 -> Direction -> m ()
snapshotRenderInsertionCursor a
snapshot b
context Double
x Double
y c
layout Int32
index Direction
direction = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr StyleContext
context' <- b -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
context
let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
Ptr Layout
layout' <- c -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
layout
let direction' :: CUInt
direction' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Direction -> Int) -> Direction -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Direction -> Int
forall a. Enum a => a -> Int
fromEnum) Direction
direction
Ptr Snapshot
-> Ptr StyleContext
-> CDouble
-> CDouble
-> Ptr Layout
-> Int32
-> CUInt
-> IO ()
gtk_snapshot_render_insertion_cursor Ptr Snapshot
snapshot' Ptr StyleContext
context' CDouble
x' CDouble
y' Ptr Layout
layout' Int32
index CUInt
direction'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
context
c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
layout
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotRenderInsertionCursorMethodInfo
instance (signature ~ (b -> Double -> Double -> c -> Int32 -> Pango.Enums.Direction -> m ()), MonadIO m, IsSnapshot a, Gtk.StyleContext.IsStyleContext b, Pango.Layout.IsLayout c) => O.OverloadedMethod SnapshotRenderInsertionCursorMethodInfo a signature where
overloadedMethod = snapshotRenderInsertionCursor
instance O.OverloadedMethodInfo SnapshotRenderInsertionCursorMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotRenderInsertionCursor",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotRenderInsertionCursor"
}
#endif
foreign import ccall "gtk_snapshot_render_layout" gtk_snapshot_render_layout ::
Ptr Snapshot ->
Ptr Gtk.StyleContext.StyleContext ->
CDouble ->
CDouble ->
Ptr Pango.Layout.Layout ->
IO ()
snapshotRenderLayout ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a, Gtk.StyleContext.IsStyleContext b, Pango.Layout.IsLayout c) =>
a
-> b
-> Double
-> Double
-> c
-> m ()
snapshotRenderLayout :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsSnapshot a, IsStyleContext b,
IsLayout c) =>
a -> b -> Double -> Double -> c -> m ()
snapshotRenderLayout a
snapshot b
context Double
x Double
y c
layout = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr StyleContext
context' <- b -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
context
let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
Ptr Layout
layout' <- c -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
layout
Ptr Snapshot
-> Ptr StyleContext -> CDouble -> CDouble -> Ptr Layout -> IO ()
gtk_snapshot_render_layout Ptr Snapshot
snapshot' Ptr StyleContext
context' CDouble
x' CDouble
y' Ptr Layout
layout'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
context
c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
layout
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotRenderLayoutMethodInfo
instance (signature ~ (b -> Double -> Double -> c -> m ()), MonadIO m, IsSnapshot a, Gtk.StyleContext.IsStyleContext b, Pango.Layout.IsLayout c) => O.OverloadedMethod SnapshotRenderLayoutMethodInfo a signature where
overloadedMethod = snapshotRenderLayout
instance O.OverloadedMethodInfo SnapshotRenderLayoutMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotRenderLayout",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotRenderLayout"
}
#endif
foreign import ccall "gtk_snapshot_restore" gtk_snapshot_restore ::
Ptr Snapshot ->
IO ()
snapshotRestore ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> m ()
snapshotRestore :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> m ()
snapshotRestore a
snapshot = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Snapshot -> IO ()
gtk_snapshot_restore Ptr Snapshot
snapshot'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotRestoreMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotRestoreMethodInfo a signature where
overloadedMethod = snapshotRestore
instance O.OverloadedMethodInfo SnapshotRestoreMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotRestore",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotRestore"
}
#endif
foreign import ccall "gtk_snapshot_rotate" gtk_snapshot_rotate ::
Ptr Snapshot ->
CFloat ->
IO ()
snapshotRotate ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Float
-> m ()
snapshotRotate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Float -> m ()
snapshotRotate a
snapshot Float
angle = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
let angle' :: CFloat
angle' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
angle
Ptr Snapshot -> CFloat -> IO ()
gtk_snapshot_rotate Ptr Snapshot
snapshot' CFloat
angle'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotRotateMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotRotateMethodInfo a signature where
overloadedMethod = snapshotRotate
instance O.OverloadedMethodInfo SnapshotRotateMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotRotate",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotRotate"
}
#endif
foreign import ccall "gtk_snapshot_rotate_3d" gtk_snapshot_rotate_3d ::
Ptr Snapshot ->
CFloat ->
Ptr Graphene.Vec3.Vec3 ->
IO ()
snapshotRotate3d ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Float
-> Graphene.Vec3.Vec3
-> m ()
snapshotRotate3d :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Float -> Vec3 -> m ()
snapshotRotate3d a
snapshot Float
angle Vec3
axis = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
let angle' :: CFloat
angle' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
angle
Ptr Vec3
axis' <- Vec3 -> IO (Ptr Vec3)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec3
axis
Ptr Snapshot -> CFloat -> Ptr Vec3 -> IO ()
gtk_snapshot_rotate_3d Ptr Snapshot
snapshot' CFloat
angle' Ptr Vec3
axis'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Vec3 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec3
axis
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotRotate3dMethodInfo
instance (signature ~ (Float -> Graphene.Vec3.Vec3 -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotRotate3dMethodInfo a signature where
overloadedMethod = snapshotRotate3d
instance O.OverloadedMethodInfo SnapshotRotate3dMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotRotate3d",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotRotate3d"
}
#endif
foreign import ccall "gtk_snapshot_save" gtk_snapshot_save ::
Ptr Snapshot ->
IO ()
snapshotSave ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> m ()
snapshotSave :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> m ()
snapshotSave a
snapshot = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Snapshot -> IO ()
gtk_snapshot_save Ptr Snapshot
snapshot'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotSaveMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotSaveMethodInfo a signature where
overloadedMethod = snapshotSave
instance O.OverloadedMethodInfo SnapshotSaveMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotSave",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotSave"
}
#endif
foreign import ccall "gtk_snapshot_scale" gtk_snapshot_scale ::
Ptr Snapshot ->
CFloat ->
CFloat ->
IO ()
snapshotScale ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Float
-> Float
-> m ()
snapshotScale :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Float -> Float -> m ()
snapshotScale a
snapshot Float
factorX Float
factorY = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
let factorX' :: CFloat
factorX' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factorX
let factorY' :: CFloat
factorY' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factorY
Ptr Snapshot -> CFloat -> CFloat -> IO ()
gtk_snapshot_scale Ptr Snapshot
snapshot' CFloat
factorX' CFloat
factorY'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotScaleMethodInfo
instance (signature ~ (Float -> Float -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotScaleMethodInfo a signature where
overloadedMethod = snapshotScale
instance O.OverloadedMethodInfo SnapshotScaleMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotScale",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotScale"
}
#endif
foreign import ccall "gtk_snapshot_scale_3d" gtk_snapshot_scale_3d ::
Ptr Snapshot ->
CFloat ->
CFloat ->
CFloat ->
IO ()
snapshotScale3d ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Float
-> Float
-> Float
-> m ()
snapshotScale3d :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Float -> Float -> Float -> m ()
snapshotScale3d a
snapshot Float
factorX Float
factorY Float
factorZ = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
let factorX' :: CFloat
factorX' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factorX
let factorY' :: CFloat
factorY' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factorY
let factorZ' :: CFloat
factorZ' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factorZ
Ptr Snapshot -> CFloat -> CFloat -> CFloat -> IO ()
gtk_snapshot_scale_3d Ptr Snapshot
snapshot' CFloat
factorX' CFloat
factorY' CFloat
factorZ'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotScale3dMethodInfo
instance (signature ~ (Float -> Float -> Float -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotScale3dMethodInfo a signature where
overloadedMethod = snapshotScale3d
instance O.OverloadedMethodInfo SnapshotScale3dMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotScale3d",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotScale3d"
}
#endif
foreign import ccall "gtk_snapshot_to_node" gtk_snapshot_to_node ::
Ptr Snapshot ->
IO (Ptr Gsk.RenderNode.RenderNode)
snapshotToNode ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> m Gsk.RenderNode.RenderNode
snapshotToNode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> m RenderNode
snapshotToNode a
snapshot = IO RenderNode -> m RenderNode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RenderNode -> m RenderNode) -> IO RenderNode -> m RenderNode
forall a b. (a -> b) -> a -> b
$ do
Ptr Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr RenderNode
result <- Ptr Snapshot -> IO (Ptr RenderNode)
gtk_snapshot_to_node Ptr Snapshot
snapshot'
Text -> Ptr RenderNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"snapshotToNode" Ptr RenderNode
result
RenderNode
result' <- ((ManagedPtr RenderNode -> RenderNode)
-> Ptr RenderNode -> IO RenderNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr RenderNode -> RenderNode
Gsk.RenderNode.RenderNode) Ptr RenderNode
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
RenderNode -> IO RenderNode
forall (m :: * -> *) a. Monad m => a -> m a
return RenderNode
result'
#if defined(ENABLE_OVERLOADING)
data SnapshotToNodeMethodInfo
instance (signature ~ (m Gsk.RenderNode.RenderNode), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotToNodeMethodInfo a signature where
overloadedMethod = snapshotToNode
instance O.OverloadedMethodInfo SnapshotToNodeMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotToNode",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotToNode"
}
#endif
foreign import ccall "gtk_snapshot_to_paintable" gtk_snapshot_to_paintable ::
Ptr Snapshot ->
Ptr Graphene.Size.Size ->
IO (Ptr Gdk.Paintable.Paintable)
snapshotToPaintable ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Maybe (Graphene.Size.Size)
-> m Gdk.Paintable.Paintable
snapshotToPaintable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Maybe Size -> m Paintable
snapshotToPaintable a
snapshot Maybe Size
size = IO Paintable -> m Paintable
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Paintable -> m Paintable) -> IO Paintable -> m Paintable
forall a b. (a -> b) -> a -> b
$ do
Ptr Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Size
maybeSize <- case Maybe Size
size of
Maybe Size
Nothing -> Ptr Size -> IO (Ptr Size)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Size
forall a. Ptr a
nullPtr
Just Size
jSize -> do
Ptr Size
jSize' <- Size -> IO (Ptr Size)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Size
jSize
Ptr Size -> IO (Ptr Size)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Size
jSize'
Ptr Paintable
result <- Ptr Snapshot -> Ptr Size -> IO (Ptr Paintable)
gtk_snapshot_to_paintable Ptr Snapshot
snapshot' Ptr Size
maybeSize
Text -> Ptr Paintable -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"snapshotToPaintable" Ptr Paintable
result
Paintable
result' <- ((ManagedPtr Paintable -> Paintable)
-> Ptr Paintable -> IO Paintable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Paintable -> Paintable
Gdk.Paintable.Paintable) Ptr Paintable
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Maybe Size -> (Size -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Size
size Size -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Paintable -> IO Paintable
forall (m :: * -> *) a. Monad m => a -> m a
return Paintable
result'
#if defined(ENABLE_OVERLOADING)
data SnapshotToPaintableMethodInfo
instance (signature ~ (Maybe (Graphene.Size.Size) -> m Gdk.Paintable.Paintable), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotToPaintableMethodInfo a signature where
overloadedMethod = snapshotToPaintable
instance O.OverloadedMethodInfo SnapshotToPaintableMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotToPaintable",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotToPaintable"
}
#endif
foreign import ccall "gtk_snapshot_transform" gtk_snapshot_transform ::
Ptr Snapshot ->
Ptr Gsk.Transform.Transform ->
IO ()
snapshotTransform ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Maybe (Gsk.Transform.Transform)
-> m ()
snapshotTransform :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Maybe Transform -> m ()
snapshotTransform a
snapshot Maybe Transform
transform = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Transform
maybeTransform <- case Maybe Transform
transform of
Maybe Transform
Nothing -> Ptr Transform -> IO (Ptr Transform)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Transform
forall a. Ptr a
nullPtr
Just Transform
jTransform -> do
Ptr Transform
jTransform' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
jTransform
Ptr Transform -> IO (Ptr Transform)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Transform
jTransform'
Ptr Snapshot -> Ptr Transform -> IO ()
gtk_snapshot_transform Ptr Snapshot
snapshot' Ptr Transform
maybeTransform
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Maybe Transform -> (Transform -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Transform
transform Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotTransformMethodInfo
instance (signature ~ (Maybe (Gsk.Transform.Transform) -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotTransformMethodInfo a signature where
overloadedMethod = snapshotTransform
instance O.OverloadedMethodInfo SnapshotTransformMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotTransform",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotTransform"
}
#endif
foreign import ccall "gtk_snapshot_transform_matrix" gtk_snapshot_transform_matrix ::
Ptr Snapshot ->
Ptr Graphene.Matrix.Matrix ->
IO ()
snapshotTransformMatrix ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Matrix.Matrix
-> m ()
snapshotTransformMatrix :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Matrix -> m ()
snapshotTransformMatrix a
snapshot Matrix
matrix = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
Ptr Snapshot -> Ptr Matrix -> IO ()
gtk_snapshot_transform_matrix Ptr Snapshot
snapshot' Ptr Matrix
matrix'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotTransformMatrixMethodInfo
instance (signature ~ (Graphene.Matrix.Matrix -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotTransformMatrixMethodInfo a signature where
overloadedMethod = snapshotTransformMatrix
instance O.OverloadedMethodInfo SnapshotTransformMatrixMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotTransformMatrix",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotTransformMatrix"
}
#endif
foreign import ccall "gtk_snapshot_translate" gtk_snapshot_translate ::
Ptr Snapshot ->
Ptr Graphene.Point.Point ->
IO ()
snapshotTranslate ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Point.Point
-> m ()
snapshotTranslate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Point -> m ()
snapshotTranslate a
snapshot Point
point = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Point
point' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
point
Ptr Snapshot -> Ptr Point -> IO ()
gtk_snapshot_translate Ptr Snapshot
snapshot' Ptr Point
point'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
point
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotTranslateMethodInfo
instance (signature ~ (Graphene.Point.Point -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotTranslateMethodInfo a signature where
overloadedMethod = snapshotTranslate
instance O.OverloadedMethodInfo SnapshotTranslateMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotTranslate",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotTranslate"
}
#endif
foreign import ccall "gtk_snapshot_translate_3d" gtk_snapshot_translate_3d ::
Ptr Snapshot ->
Ptr Graphene.Point3D.Point3D ->
IO ()
snapshotTranslate3d ::
(B.CallStack.HasCallStack, MonadIO m, IsSnapshot a) =>
a
-> Graphene.Point3D.Point3D
-> m ()
snapshotTranslate3d :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSnapshot a) =>
a -> Point3D -> m ()
snapshotTranslate3d a
snapshot Point3D
point = 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 Snapshot
snapshot' <- a -> IO (Ptr Snapshot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
snapshot
Ptr Point3D
point' <- Point3D -> IO (Ptr Point3D)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point3D
point
Ptr Snapshot -> Ptr Point3D -> IO ()
gtk_snapshot_translate_3d Ptr Snapshot
snapshot' Ptr Point3D
point'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
snapshot
Point3D -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point3D
point
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SnapshotTranslate3dMethodInfo
instance (signature ~ (Graphene.Point3D.Point3D -> m ()), MonadIO m, IsSnapshot a) => O.OverloadedMethod SnapshotTranslate3dMethodInfo a signature where
overloadedMethod = snapshotTranslate3d
instance O.OverloadedMethodInfo SnapshotTranslate3dMethodInfo a where
overloadedMethodInfo = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Objects.Snapshot.snapshotTranslate3d",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Snapshot.html#v:snapshotTranslate3d"
}
#endif