{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gsk.Objects.StrokeNode
(
StrokeNode(..) ,
IsStrokeNode ,
toStrokeNode ,
#if defined(ENABLE_OVERLOADING)
ResolveStrokeNodeMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
StrokeNodeGetChildMethodInfo ,
#endif
strokeNodeGetChild ,
#if defined(ENABLE_OVERLOADING)
StrokeNodeGetPathMethodInfo ,
#endif
strokeNodeGetPath ,
#if defined(ENABLE_OVERLOADING)
StrokeNodeGetStrokeMethodInfo ,
#endif
strokeNodeGetStroke ,
strokeNodeNew ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Gsk.Callbacks as Gsk.Callbacks
import {-# SOURCE #-} qualified GI.Gsk.Enums as Gsk.Enums
import {-# SOURCE #-} qualified GI.Gsk.Flags as Gsk.Flags
import {-# SOURCE #-} qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import {-# SOURCE #-} qualified GI.Gsk.Structs.Path as Gsk.Path
import {-# SOURCE #-} qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
#else
import {-# SOURCE #-} qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import {-# SOURCE #-} qualified GI.Gsk.Structs.Path as Gsk.Path
import {-# SOURCE #-} qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
#endif
newtype StrokeNode = StrokeNode (SP.ManagedPtr StrokeNode)
deriving (StrokeNode -> StrokeNode -> Bool
(StrokeNode -> StrokeNode -> Bool)
-> (StrokeNode -> StrokeNode -> Bool) -> Eq StrokeNode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StrokeNode -> StrokeNode -> Bool
== :: StrokeNode -> StrokeNode -> Bool
$c/= :: StrokeNode -> StrokeNode -> Bool
/= :: StrokeNode -> StrokeNode -> Bool
Eq)
instance SP.ManagedPtrNewtype StrokeNode where
toManagedPtr :: StrokeNode -> ManagedPtr StrokeNode
toManagedPtr (StrokeNode ManagedPtr StrokeNode
p) = ManagedPtr StrokeNode
p
foreign import ccall "gsk_stroke_node_get_type"
c_gsk_stroke_node_get_type :: IO B.Types.GType
instance B.Types.TypedObject StrokeNode where
glibType :: IO GType
glibType = IO GType
c_gsk_stroke_node_get_type
class (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf StrokeNode o) => IsStrokeNode o
instance (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf StrokeNode o) => IsStrokeNode o
instance O.HasParentTypes StrokeNode
type instance O.ParentTypes StrokeNode = '[Gsk.RenderNode.RenderNode]
toStrokeNode :: (MIO.MonadIO m, IsStrokeNode o) => o -> m StrokeNode
toStrokeNode :: forall (m :: * -> *) o.
(MonadIO m, IsStrokeNode o) =>
o -> m StrokeNode
toStrokeNode = IO StrokeNode -> m StrokeNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO StrokeNode -> m StrokeNode)
-> (o -> IO StrokeNode) -> o -> m StrokeNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr StrokeNode -> StrokeNode) -> o -> IO StrokeNode
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr StrokeNode -> StrokeNode
StrokeNode
#if defined(ENABLE_OVERLOADING)
type family ResolveStrokeNodeMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveStrokeNodeMethod "draw" o = Gsk.RenderNode.RenderNodeDrawMethodInfo
ResolveStrokeNodeMethod "ref" o = Gsk.RenderNode.RenderNodeRefMethodInfo
ResolveStrokeNodeMethod "serialize" o = Gsk.RenderNode.RenderNodeSerializeMethodInfo
ResolveStrokeNodeMethod "unref" o = Gsk.RenderNode.RenderNodeUnrefMethodInfo
ResolveStrokeNodeMethod "writeToFile" o = Gsk.RenderNode.RenderNodeWriteToFileMethodInfo
ResolveStrokeNodeMethod "getBounds" o = Gsk.RenderNode.RenderNodeGetBoundsMethodInfo
ResolveStrokeNodeMethod "getChild" o = StrokeNodeGetChildMethodInfo
ResolveStrokeNodeMethod "getNodeType" o = Gsk.RenderNode.RenderNodeGetNodeTypeMethodInfo
ResolveStrokeNodeMethod "getPath" o = StrokeNodeGetPathMethodInfo
ResolveStrokeNodeMethod "getStroke" o = StrokeNodeGetStrokeMethodInfo
ResolveStrokeNodeMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveStrokeNodeMethod t StrokeNode, O.OverloadedMethod info StrokeNode p) => OL.IsLabel t (StrokeNode -> 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 ~ ResolveStrokeNodeMethod t StrokeNode, O.OverloadedMethod info StrokeNode p, R.HasField t StrokeNode p) => R.HasField t StrokeNode p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveStrokeNodeMethod t StrokeNode, O.OverloadedMethodInfo info StrokeNode) => OL.IsLabel t (O.MethodProxy info StrokeNode) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
instance BoxedPtr StrokeNode where
boxedPtrCopy :: StrokeNode -> IO StrokeNode
boxedPtrCopy = StrokeNode -> IO StrokeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
boxedPtrFree :: StrokeNode -> IO ()
boxedPtrFree = \StrokeNode
_x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
foreign import ccall "gsk_stroke_node_new" gsk_stroke_node_new ::
Ptr Gsk.RenderNode.RenderNode ->
Ptr Gsk.Path.Path ->
Ptr Gsk.Stroke.Stroke ->
IO (Ptr StrokeNode)
strokeNodeNew ::
(B.CallStack.HasCallStack, MonadIO m, Gsk.RenderNode.IsRenderNode a) =>
a
-> Gsk.Path.Path
-> Gsk.Stroke.Stroke
-> m StrokeNode
strokeNodeNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderNode a) =>
a -> Path -> Stroke -> m StrokeNode
strokeNodeNew a
child Path
path Stroke
stroke = IO StrokeNode -> m StrokeNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StrokeNode -> m StrokeNode) -> IO StrokeNode -> m StrokeNode
forall a b. (a -> b) -> a -> b
$ do
Ptr RenderNode
child' <- a -> IO (Ptr RenderNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
Ptr Path
path' <- Path -> IO (Ptr Path)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Path
path
Ptr Stroke
stroke' <- Stroke -> IO (Ptr Stroke)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Stroke
stroke
Ptr StrokeNode
result <- Ptr RenderNode -> Ptr Path -> Ptr Stroke -> IO (Ptr StrokeNode)
gsk_stroke_node_new Ptr RenderNode
child' Ptr Path
path' Ptr Stroke
stroke'
Text -> Ptr StrokeNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"strokeNodeNew" Ptr StrokeNode
result
StrokeNode
result' <- ((ManagedPtr StrokeNode -> StrokeNode)
-> Ptr StrokeNode -> IO StrokeNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr StrokeNode -> StrokeNode
StrokeNode) Ptr StrokeNode
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
path
Stroke -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Stroke
stroke
StrokeNode -> IO StrokeNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return StrokeNode
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gsk_stroke_node_get_child" gsk_stroke_node_get_child ::
Ptr StrokeNode ->
IO (Ptr Gsk.RenderNode.RenderNode)
strokeNodeGetChild ::
(B.CallStack.HasCallStack, MonadIO m, IsStrokeNode a) =>
a
-> m Gsk.RenderNode.RenderNode
strokeNodeGetChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStrokeNode a) =>
a -> m RenderNode
strokeNodeGetChild a
node = IO RenderNode -> m RenderNode
forall a. IO a -> m a
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 StrokeNode
node' <- a -> IO (Ptr StrokeNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
Ptr RenderNode
result <- Ptr StrokeNode -> IO (Ptr RenderNode)
gsk_stroke_node_get_child Ptr StrokeNode
node'
Text -> Ptr RenderNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"strokeNodeGetChild" Ptr RenderNode
result
RenderNode
result' <- ((ManagedPtr RenderNode -> RenderNode)
-> Ptr RenderNode -> IO RenderNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr RenderNode -> RenderNode
Gsk.RenderNode.RenderNode) Ptr RenderNode
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
RenderNode -> IO RenderNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RenderNode
result'
#if defined(ENABLE_OVERLOADING)
data StrokeNodeGetChildMethodInfo
instance (signature ~ (m Gsk.RenderNode.RenderNode), MonadIO m, IsStrokeNode a) => O.OverloadedMethod StrokeNodeGetChildMethodInfo a signature where
overloadedMethod = strokeNodeGetChild
instance O.OverloadedMethodInfo StrokeNodeGetChildMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Objects.StrokeNode.strokeNodeGetChild",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Objects-StrokeNode.html#v:strokeNodeGetChild"
})
#endif
foreign import ccall "gsk_stroke_node_get_path" gsk_stroke_node_get_path ::
Ptr StrokeNode ->
IO (Ptr Gsk.Path.Path)
strokeNodeGetPath ::
(B.CallStack.HasCallStack, MonadIO m, IsStrokeNode a) =>
a
-> m Gsk.Path.Path
strokeNodeGetPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStrokeNode a) =>
a -> m Path
strokeNodeGetPath a
node = IO Path -> m Path
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Path -> m Path) -> IO Path -> m Path
forall a b. (a -> b) -> a -> b
$ do
Ptr StrokeNode
node' <- a -> IO (Ptr StrokeNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
Ptr Path
result <- Ptr StrokeNode -> IO (Ptr Path)
gsk_stroke_node_get_path Ptr StrokeNode
node'
Text -> Ptr Path -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"strokeNodeGetPath" Ptr Path
result
Path
result' <- ((ManagedPtr Path -> Path) -> Ptr Path -> IO Path
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Path -> Path
Gsk.Path.Path) Ptr Path
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
Path -> IO Path
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Path
result'
#if defined(ENABLE_OVERLOADING)
data StrokeNodeGetPathMethodInfo
instance (signature ~ (m Gsk.Path.Path), MonadIO m, IsStrokeNode a) => O.OverloadedMethod StrokeNodeGetPathMethodInfo a signature where
overloadedMethod = strokeNodeGetPath
instance O.OverloadedMethodInfo StrokeNodeGetPathMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Objects.StrokeNode.strokeNodeGetPath",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Objects-StrokeNode.html#v:strokeNodeGetPath"
})
#endif
foreign import ccall "gsk_stroke_node_get_stroke" gsk_stroke_node_get_stroke ::
Ptr StrokeNode ->
IO (Ptr Gsk.Stroke.Stroke)
strokeNodeGetStroke ::
(B.CallStack.HasCallStack, MonadIO m, IsStrokeNode a) =>
a
-> m Gsk.Stroke.Stroke
strokeNodeGetStroke :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStrokeNode a) =>
a -> m Stroke
strokeNodeGetStroke a
node = IO Stroke -> m Stroke
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Stroke -> m Stroke) -> IO Stroke -> m Stroke
forall a b. (a -> b) -> a -> b
$ do
Ptr StrokeNode
node' <- a -> IO (Ptr StrokeNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
Ptr Stroke
result <- Ptr StrokeNode -> IO (Ptr Stroke)
gsk_stroke_node_get_stroke Ptr StrokeNode
node'
Text -> Ptr Stroke -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"strokeNodeGetStroke" Ptr Stroke
result
Stroke
result' <- ((ManagedPtr Stroke -> Stroke) -> Ptr Stroke -> IO Stroke
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Stroke -> Stroke
Gsk.Stroke.Stroke) Ptr Stroke
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
Stroke -> IO Stroke
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Stroke
result'
#if defined(ENABLE_OVERLOADING)
data StrokeNodeGetStrokeMethodInfo
instance (signature ~ (m Gsk.Stroke.Stroke), MonadIO m, IsStrokeNode a) => O.OverloadedMethod StrokeNodeGetStrokeMethodInfo a signature where
overloadedMethod = strokeNodeGetStroke
instance O.OverloadedMethodInfo StrokeNodeGetStrokeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gsk.Objects.StrokeNode.strokeNodeGetStroke",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Objects-StrokeNode.html#v:strokeNodeGetStroke"
})
#endif