{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A render node filling the area given by [struct/@gsk@/.Path]
-- and t'GI.Gsk.Enums.FillRule' with the child node.
-- 
-- /Since: 4.14/

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gsk.Objects.FillNode
    ( 

-- * Exported types
    FillNode(..)                            ,
    IsFillNode                              ,
    toFillNode                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [draw]("GI.Gsk.Objects.RenderNode#g:method:draw"), [ref]("GI.Gsk.Objects.RenderNode#g:method:ref"), [serialize]("GI.Gsk.Objects.RenderNode#g:method:serialize"), [unref]("GI.Gsk.Objects.RenderNode#g:method:unref"), [writeToFile]("GI.Gsk.Objects.RenderNode#g:method:writeToFile").
-- 
-- ==== Getters
-- [getBounds]("GI.Gsk.Objects.RenderNode#g:method:getBounds"), [getChild]("GI.Gsk.Objects.FillNode#g:method:getChild"), [getFillRule]("GI.Gsk.Objects.FillNode#g:method:getFillRule"), [getNodeType]("GI.Gsk.Objects.RenderNode#g:method:getNodeType"), [getPath]("GI.Gsk.Objects.FillNode#g:method:getPath").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveFillNodeMethod                   ,
#endif

-- ** getChild #method:getChild#

#if defined(ENABLE_OVERLOADING)
    FillNodeGetChildMethodInfo              ,
#endif
    fillNodeGetChild                        ,


-- ** getFillRule #method:getFillRule#

#if defined(ENABLE_OVERLOADING)
    FillNodeGetFillRuleMethodInfo           ,
#endif
    fillNodeGetFillRule                     ,


-- ** getPath #method:getPath#

#if defined(ENABLE_OVERLOADING)
    FillNodeGetPathMethodInfo               ,
#endif
    fillNodeGetPath                         ,


-- ** new #method:new#

    fillNodeNew                             ,




    ) 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

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#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.Enums as Gsk.Enums
import {-# SOURCE #-} qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import {-# SOURCE #-} qualified GI.Gsk.Structs.Path as Gsk.Path

#endif

-- | Memory-managed wrapper type.
newtype FillNode = FillNode (SP.ManagedPtr FillNode)
    deriving (FillNode -> FillNode -> Bool
(FillNode -> FillNode -> Bool)
-> (FillNode -> FillNode -> Bool) -> Eq FillNode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FillNode -> FillNode -> Bool
== :: FillNode -> FillNode -> Bool
$c/= :: FillNode -> FillNode -> Bool
/= :: FillNode -> FillNode -> Bool
Eq)

instance SP.ManagedPtrNewtype FillNode where
    toManagedPtr :: FillNode -> ManagedPtr FillNode
toManagedPtr (FillNode ManagedPtr FillNode
p) = ManagedPtr FillNode
p

foreign import ccall "gsk_fill_node_get_type"
    c_gsk_fill_node_get_type :: IO B.Types.GType

instance B.Types.TypedObject FillNode where
    glibType :: IO GType
glibType = IO GType
c_gsk_fill_node_get_type

-- | Type class for types which can be safely cast to `FillNode`, for instance with `toFillNode`.
class (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf FillNode o) => IsFillNode o
instance (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf FillNode o) => IsFillNode o

instance O.HasParentTypes FillNode
type instance O.ParentTypes FillNode = '[Gsk.RenderNode.RenderNode]

-- | Cast to `FillNode`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toFillNode :: (MIO.MonadIO m, IsFillNode o) => o -> m FillNode
toFillNode :: forall (m :: * -> *) o.
(MonadIO m, IsFillNode o) =>
o -> m FillNode
toFillNode = IO FillNode -> m FillNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO FillNode -> m FillNode)
-> (o -> IO FillNode) -> o -> m FillNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr FillNode -> FillNode) -> o -> IO FillNode
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr FillNode -> FillNode
FillNode

--- XXX Missing getter and/or setter, so no GValue instance could be generated.
#if defined(ENABLE_OVERLOADING)
type family ResolveFillNodeMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveFillNodeMethod "draw" o = Gsk.RenderNode.RenderNodeDrawMethodInfo
    ResolveFillNodeMethod "ref" o = Gsk.RenderNode.RenderNodeRefMethodInfo
    ResolveFillNodeMethod "serialize" o = Gsk.RenderNode.RenderNodeSerializeMethodInfo
    ResolveFillNodeMethod "unref" o = Gsk.RenderNode.RenderNodeUnrefMethodInfo
    ResolveFillNodeMethod "writeToFile" o = Gsk.RenderNode.RenderNodeWriteToFileMethodInfo
    ResolveFillNodeMethod "getBounds" o = Gsk.RenderNode.RenderNodeGetBoundsMethodInfo
    ResolveFillNodeMethod "getChild" o = FillNodeGetChildMethodInfo
    ResolveFillNodeMethod "getFillRule" o = FillNodeGetFillRuleMethodInfo
    ResolveFillNodeMethod "getNodeType" o = Gsk.RenderNode.RenderNodeGetNodeTypeMethodInfo
    ResolveFillNodeMethod "getPath" o = FillNodeGetPathMethodInfo
    ResolveFillNodeMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveFillNodeMethod t FillNode, O.OverloadedMethod info FillNode p) => OL.IsLabel t (FillNode -> 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 ~ ResolveFillNodeMethod t FillNode, O.OverloadedMethod info FillNode p, R.HasField t FillNode p) => R.HasField t FillNode p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveFillNodeMethod t FillNode, O.OverloadedMethodInfo info FillNode) => OL.IsLabel t (O.MethodProxy info FillNode) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr FillNode where
    boxedPtrCopy :: FillNode -> IO FillNode
boxedPtrCopy = FillNode -> IO FillNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: FillNode -> IO ()
boxedPtrFree = \FillNode
_x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()


-- method FillNode::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "RenderNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The node to fill the area with"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TInterface Name { namespace = "Gsk" , name = "Path" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The path describing the area to fill"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fill_rule"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "FillRule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The fill rule to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "FillNode" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_fill_node_new" gsk_fill_node_new :: 
    Ptr Gsk.RenderNode.RenderNode ->        -- child : TInterface (Name {namespace = "Gsk", name = "RenderNode"})
    Ptr Gsk.Path.Path ->                    -- path : TInterface (Name {namespace = "Gsk", name = "Path"})
    CUInt ->                                -- fill_rule : TInterface (Name {namespace = "Gsk", name = "FillRule"})
    IO (Ptr FillNode)

-- | Creates a @GskRenderNode@ that will fill the /@child@/ in the area
-- given by /@path@/ and /@fillRule@/.
-- 
-- /Since: 4.14/
fillNodeNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gsk.RenderNode.IsRenderNode a) =>
    a
    -- ^ /@child@/: The node to fill the area with
    -> Gsk.Path.Path
    -- ^ /@path@/: The path describing the area to fill
    -> Gsk.Enums.FillRule
    -- ^ /@fillRule@/: The fill rule to use
    -> m FillNode
    -- ^ __Returns:__ A new @GskRenderNode@
fillNodeNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderNode a) =>
a -> Path -> FillRule -> m FillNode
fillNodeNew a
child Path
path FillRule
fillRule = IO FillNode -> m FillNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FillNode -> m FillNode) -> IO FillNode -> m FillNode
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
    let fillRule' :: CUInt
fillRule' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (FillRule -> Int) -> FillRule -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FillRule -> Int
forall a. Enum a => a -> Int
fromEnum) FillRule
fillRule
    Ptr FillNode
result <- Ptr RenderNode -> Ptr Path -> CUInt -> IO (Ptr FillNode)
gsk_fill_node_new Ptr RenderNode
child' Ptr Path
path' CUInt
fillRule'
    Text -> Ptr FillNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fillNodeNew" Ptr FillNode
result
    FillNode
result' <- ((ManagedPtr FillNode -> FillNode) -> Ptr FillNode -> IO FillNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr FillNode -> FillNode
FillNode) Ptr FillNode
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    Path -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Path
path
    FillNode -> IO FillNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FillNode
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method FillNode::get_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "node"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "FillNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a fill `GskRenderNode`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "RenderNode" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_fill_node_get_child" gsk_fill_node_get_child :: 
    Ptr FillNode ->                         -- node : TInterface (Name {namespace = "Gsk", name = "FillNode"})
    IO (Ptr Gsk.RenderNode.RenderNode)

-- | Gets the child node that is getting drawn by the given /@node@/.
-- 
-- /Since: 4.14/
fillNodeGetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsFillNode a) =>
    a
    -- ^ /@node@/: a fill @GskRenderNode@
    -> m Gsk.RenderNode.RenderNode
    -- ^ __Returns:__ The child that is getting drawn
fillNodeGetChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFillNode a) =>
a -> m RenderNode
fillNodeGetChild 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 FillNode
node' <- a -> IO (Ptr FillNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr RenderNode
result <- Ptr FillNode -> IO (Ptr RenderNode)
gsk_fill_node_get_child Ptr FillNode
node'
    Text -> Ptr RenderNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fillNodeGetChild" 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 FillNodeGetChildMethodInfo
instance (signature ~ (m Gsk.RenderNode.RenderNode), MonadIO m, IsFillNode a) => O.OverloadedMethod FillNodeGetChildMethodInfo a signature where
    overloadedMethod = fillNodeGetChild

instance O.OverloadedMethodInfo FillNodeGetChildMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gsk.Objects.FillNode.fillNodeGetChild",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Objects-FillNode.html#v:fillNodeGetChild"
        })


#endif

-- method FillNode::get_fill_rule
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "node"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "FillNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a fill `GskRenderNode`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "FillRule" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_fill_node_get_fill_rule" gsk_fill_node_get_fill_rule :: 
    Ptr FillNode ->                         -- node : TInterface (Name {namespace = "Gsk", name = "FillNode"})
    IO CUInt

-- | Retrieves the fill rule used to determine how the path is filled.
-- 
-- /Since: 4.14/
fillNodeGetFillRule ::
    (B.CallStack.HasCallStack, MonadIO m, IsFillNode a) =>
    a
    -- ^ /@node@/: a fill @GskRenderNode@
    -> m Gsk.Enums.FillRule
    -- ^ __Returns:__ a @GskFillRule@
fillNodeGetFillRule :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFillNode a) =>
a -> m FillRule
fillNodeGetFillRule a
node = IO FillRule -> m FillRule
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FillRule -> m FillRule) -> IO FillRule -> m FillRule
forall a b. (a -> b) -> a -> b
$ do
    Ptr FillNode
node' <- a -> IO (Ptr FillNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    CUInt
result <- Ptr FillNode -> IO CUInt
gsk_fill_node_get_fill_rule Ptr FillNode
node'
    let result' :: FillRule
result' = (Int -> FillRule
forall a. Enum a => Int -> a
toEnum (Int -> FillRule) -> (CUInt -> Int) -> CUInt -> FillRule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    FillRule -> IO FillRule
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FillRule
result'

#if defined(ENABLE_OVERLOADING)
data FillNodeGetFillRuleMethodInfo
instance (signature ~ (m Gsk.Enums.FillRule), MonadIO m, IsFillNode a) => O.OverloadedMethod FillNodeGetFillRuleMethodInfo a signature where
    overloadedMethod = fillNodeGetFillRule

instance O.OverloadedMethodInfo FillNodeGetFillRuleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gsk.Objects.FillNode.fillNodeGetFillRule",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Objects-FillNode.html#v:fillNodeGetFillRule"
        })


#endif

-- method FillNode::get_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "node"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "FillNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a fill `GskRenderNode`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Path" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_fill_node_get_path" gsk_fill_node_get_path :: 
    Ptr FillNode ->                         -- node : TInterface (Name {namespace = "Gsk", name = "FillNode"})
    IO (Ptr Gsk.Path.Path)

-- | Retrieves the path used to describe the area filled with the contents of
-- the /@node@/.
-- 
-- /Since: 4.14/
fillNodeGetPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsFillNode a) =>
    a
    -- ^ /@node@/: a fill @GskRenderNode@
    -> m Gsk.Path.Path
    -- ^ __Returns:__ a @GskPath@
fillNodeGetPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFillNode a) =>
a -> m Path
fillNodeGetPath 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 FillNode
node' <- a -> IO (Ptr FillNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr Path
result <- Ptr FillNode -> IO (Ptr Path)
gsk_fill_node_get_path Ptr FillNode
node'
    Text -> Ptr Path -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fillNodeGetPath" 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 FillNodeGetPathMethodInfo
instance (signature ~ (m Gsk.Path.Path), MonadIO m, IsFillNode a) => O.OverloadedMethod FillNodeGetPathMethodInfo a signature where
    overloadedMethod = fillNodeGetPath

instance O.OverloadedMethodInfo FillNodeGetPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gsk.Objects.FillNode.fillNodeGetPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Objects-FillNode.html#v:fillNodeGetPath"
        })


#endif