{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gsk.Objects.BlendNode
    ( 
    BlendNode(..)                           ,
    IsBlendNode                             ,
    toBlendNode                             ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveBlendNodeMethod                  ,
#endif
#if defined(ENABLE_OVERLOADING)
    BlendNodeGetBlendModeMethodInfo         ,
#endif
    blendNodeGetBlendMode                   ,
#if defined(ENABLE_OVERLOADING)
    BlendNodeGetBottomChildMethodInfo       ,
#endif
    blendNodeGetBottomChild                 ,
#if defined(ENABLE_OVERLOADING)
    BlendNodeGetTopChildMethodInfo          ,
#endif
    blendNodeGetTopChild                    ,
    blendNodeNew                            ,
    ) 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.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.Objects.RenderNode as Gsk.RenderNode
#else
import {-# SOURCE #-} qualified GI.Gsk.Enums as Gsk.Enums
import {-# SOURCE #-} qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
#endif
newtype BlendNode = BlendNode (SP.ManagedPtr BlendNode)
    deriving (BlendNode -> BlendNode -> Bool
(BlendNode -> BlendNode -> Bool)
-> (BlendNode -> BlendNode -> Bool) -> Eq BlendNode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BlendNode -> BlendNode -> Bool
== :: BlendNode -> BlendNode -> Bool
$c/= :: BlendNode -> BlendNode -> Bool
/= :: BlendNode -> BlendNode -> Bool
Eq)
instance SP.ManagedPtrNewtype BlendNode where
    toManagedPtr :: BlendNode -> ManagedPtr BlendNode
toManagedPtr (BlendNode ManagedPtr BlendNode
p) = ManagedPtr BlendNode
p
foreign import ccall "gsk_blend_node_get_type"
    c_gsk_blend_node_get_type :: IO B.Types.GType
instance B.Types.TypedObject BlendNode where
    glibType :: IO GType
glibType = IO GType
c_gsk_blend_node_get_type
class (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf BlendNode o) => IsBlendNode o
instance (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf BlendNode o) => IsBlendNode o
instance O.HasParentTypes BlendNode
type instance O.ParentTypes BlendNode = '[Gsk.RenderNode.RenderNode]
toBlendNode :: (MIO.MonadIO m, IsBlendNode o) => o -> m BlendNode
toBlendNode :: forall (m :: * -> *) o.
(MonadIO m, IsBlendNode o) =>
o -> m BlendNode
toBlendNode = IO BlendNode -> m BlendNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO BlendNode -> m BlendNode)
-> (o -> IO BlendNode) -> o -> m BlendNode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr BlendNode -> BlendNode) -> o -> IO BlendNode
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr BlendNode -> BlendNode
BlendNode
#if defined(ENABLE_OVERLOADING)
type family ResolveBlendNodeMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveBlendNodeMethod "draw" o = Gsk.RenderNode.RenderNodeDrawMethodInfo
    ResolveBlendNodeMethod "ref" o = Gsk.RenderNode.RenderNodeRefMethodInfo
    ResolveBlendNodeMethod "serialize" o = Gsk.RenderNode.RenderNodeSerializeMethodInfo
    ResolveBlendNodeMethod "unref" o = Gsk.RenderNode.RenderNodeUnrefMethodInfo
    ResolveBlendNodeMethod "writeToFile" o = Gsk.RenderNode.RenderNodeWriteToFileMethodInfo
    ResolveBlendNodeMethod "getBlendMode" o = BlendNodeGetBlendModeMethodInfo
    ResolveBlendNodeMethod "getBottomChild" o = BlendNodeGetBottomChildMethodInfo
    ResolveBlendNodeMethod "getBounds" o = Gsk.RenderNode.RenderNodeGetBoundsMethodInfo
    ResolveBlendNodeMethod "getNodeType" o = Gsk.RenderNode.RenderNodeGetNodeTypeMethodInfo
    ResolveBlendNodeMethod "getTopChild" o = BlendNodeGetTopChildMethodInfo
    ResolveBlendNodeMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveBlendNodeMethod t BlendNode, O.OverloadedMethod info BlendNode p) => OL.IsLabel t (BlendNode -> 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 ~ ResolveBlendNodeMethod t BlendNode, O.OverloadedMethod info BlendNode p, R.HasField t BlendNode p) => R.HasField t BlendNode p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveBlendNodeMethod t BlendNode, O.OverloadedMethodInfo info BlendNode) => OL.IsLabel t (O.MethodProxy info BlendNode) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
instance BoxedPtr BlendNode where
    boxedPtrCopy :: BlendNode -> IO BlendNode
boxedPtrCopy = BlendNode -> IO BlendNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: BlendNode -> IO ()
boxedPtrFree = \BlendNode
_x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
foreign import ccall "gsk_blend_node_new" gsk_blend_node_new :: 
    Ptr Gsk.RenderNode.RenderNode ->        
    Ptr Gsk.RenderNode.RenderNode ->        
    CUInt ->                                
    IO (Ptr BlendNode)
blendNodeNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gsk.RenderNode.IsRenderNode a, Gsk.RenderNode.IsRenderNode b) =>
    a
    
    -> b
    
    -> Gsk.Enums.BlendMode
    
    -> m BlendNode
    
blendNodeNew :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRenderNode a, IsRenderNode b) =>
a -> b -> BlendMode -> m BlendNode
blendNodeNew a
bottom b
top BlendMode
blendMode = IO BlendNode -> m BlendNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BlendNode -> m BlendNode) -> IO BlendNode -> m BlendNode
forall a b. (a -> b) -> a -> b
$ do
    Ptr RenderNode
bottom' <- a -> IO (Ptr RenderNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
bottom
    Ptr RenderNode
top' <- b -> IO (Ptr RenderNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
top
    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 BlendNode
result <- Ptr RenderNode -> Ptr RenderNode -> CUInt -> IO (Ptr BlendNode)
gsk_blend_node_new Ptr RenderNode
bottom' Ptr RenderNode
top' CUInt
blendMode'
    Text -> Ptr BlendNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"blendNodeNew" Ptr BlendNode
result
    BlendNode
result' <- ((ManagedPtr BlendNode -> BlendNode)
-> Ptr BlendNode -> IO BlendNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr BlendNode -> BlendNode
BlendNode) Ptr BlendNode
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
bottom
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
top
    BlendNode -> IO BlendNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BlendNode
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gsk_blend_node_get_blend_mode" gsk_blend_node_get_blend_mode :: 
    Ptr BlendNode ->                        
    IO CUInt
blendNodeGetBlendMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsBlendNode a) =>
    a
    
    -> m Gsk.Enums.BlendMode
    
blendNodeGetBlendMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBlendNode a) =>
a -> m BlendMode
blendNodeGetBlendMode a
node = IO BlendMode -> m BlendMode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BlendMode -> m BlendMode) -> IO BlendMode -> m BlendMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr BlendNode
node' <- a -> IO (Ptr BlendNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    CUInt
result <- Ptr BlendNode -> IO CUInt
gsk_blend_node_get_blend_mode Ptr BlendNode
node'
    let result' :: BlendMode
result' = (Int -> BlendMode
forall a. Enum a => Int -> a
toEnum (Int -> BlendMode) -> (CUInt -> Int) -> CUInt -> BlendMode
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
    BlendMode -> IO BlendMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BlendMode
result'
#if defined(ENABLE_OVERLOADING)
data BlendNodeGetBlendModeMethodInfo
instance (signature ~ (m Gsk.Enums.BlendMode), MonadIO m, IsBlendNode a) => O.OverloadedMethod BlendNodeGetBlendModeMethodInfo a signature where
    overloadedMethod = blendNodeGetBlendMode
instance O.OverloadedMethodInfo BlendNodeGetBlendModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gsk.Objects.BlendNode.blendNodeGetBlendMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Objects-BlendNode.html#v:blendNodeGetBlendMode"
        })
#endif
foreign import ccall "gsk_blend_node_get_bottom_child" gsk_blend_node_get_bottom_child :: 
    Ptr BlendNode ->                        
    IO (Ptr Gsk.RenderNode.RenderNode)
blendNodeGetBottomChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsBlendNode a) =>
    a
    
    -> m Gsk.RenderNode.RenderNode
    
blendNodeGetBottomChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBlendNode a) =>
a -> m RenderNode
blendNodeGetBottomChild 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 BlendNode
node' <- a -> IO (Ptr BlendNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr RenderNode
result <- Ptr BlendNode -> IO (Ptr RenderNode)
gsk_blend_node_get_bottom_child Ptr BlendNode
node'
    Text -> Ptr RenderNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"blendNodeGetBottomChild" 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 BlendNodeGetBottomChildMethodInfo
instance (signature ~ (m Gsk.RenderNode.RenderNode), MonadIO m, IsBlendNode a) => O.OverloadedMethod BlendNodeGetBottomChildMethodInfo a signature where
    overloadedMethod = blendNodeGetBottomChild
instance O.OverloadedMethodInfo BlendNodeGetBottomChildMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gsk.Objects.BlendNode.blendNodeGetBottomChild",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Objects-BlendNode.html#v:blendNodeGetBottomChild"
        })
#endif
foreign import ccall "gsk_blend_node_get_top_child" gsk_blend_node_get_top_child :: 
    Ptr BlendNode ->                        
    IO (Ptr Gsk.RenderNode.RenderNode)
blendNodeGetTopChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsBlendNode a) =>
    a
    
    -> m Gsk.RenderNode.RenderNode
    
blendNodeGetTopChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBlendNode a) =>
a -> m RenderNode
blendNodeGetTopChild 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 BlendNode
node' <- a -> IO (Ptr BlendNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr RenderNode
result <- Ptr BlendNode -> IO (Ptr RenderNode)
gsk_blend_node_get_top_child Ptr BlendNode
node'
    Text -> Ptr RenderNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"blendNodeGetTopChild" 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 BlendNodeGetTopChildMethodInfo
instance (signature ~ (m Gsk.RenderNode.RenderNode), MonadIO m, IsBlendNode a) => O.OverloadedMethod BlendNodeGetTopChildMethodInfo a signature where
    overloadedMethod = blendNodeGetTopChild
instance O.OverloadedMethodInfo BlendNodeGetTopChildMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gsk.Objects.BlendNode.blendNodeGetTopChild",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gsk-4.0.8/docs/GI-Gsk-Objects-BlendNode.html#v:blendNodeGetTopChild"
        })
#endif