{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Gsk.Objects.ShadowNode
    ( 

-- * Exported types
    ShadowNode(..)                          ,
    IsShadowNode                            ,
    toShadowNode                            ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveShadowNodeMethod                 ,
#endif


-- ** getChild #method:getChild#

#if defined(ENABLE_OVERLOADING)
    ShadowNodeGetChildMethodInfo            ,
#endif
    shadowNodeGetChild                      ,


-- ** getNShadows #method:getNShadows#

#if defined(ENABLE_OVERLOADING)
    ShadowNodeGetNShadowsMethodInfo         ,
#endif
    shadowNodeGetNShadows                   ,


-- ** new #method:new#

    shadowNodeNew                           ,


-- ** peekShadow #method:peekShadow#

#if defined(ENABLE_OVERLOADING)
    ShadowNodePeekShadowMethodInfo          ,
#endif
    shadowNodePeekShadow                    ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import {-# SOURCE #-} qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import {-# SOURCE #-} qualified GI.Gsk.Structs.Shadow as Gsk.Shadow

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

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

foreign import ccall "gsk_shadow_node_get_type"
    c_gsk_shadow_node_get_type :: IO B.Types.GType

instance B.Types.TypedObject ShadowNode where
    glibType :: IO GType
glibType = IO GType
c_gsk_shadow_node_get_type

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveShadowNodeMethod (t :: Symbol) (o :: *) :: * where
    ResolveShadowNodeMethod "draw" o = Gsk.RenderNode.RenderNodeDrawMethodInfo
    ResolveShadowNodeMethod "peekShadow" o = ShadowNodePeekShadowMethodInfo
    ResolveShadowNodeMethod "ref" o = Gsk.RenderNode.RenderNodeRefMethodInfo
    ResolveShadowNodeMethod "serialize" o = Gsk.RenderNode.RenderNodeSerializeMethodInfo
    ResolveShadowNodeMethod "unref" o = Gsk.RenderNode.RenderNodeUnrefMethodInfo
    ResolveShadowNodeMethod "writeToFile" o = Gsk.RenderNode.RenderNodeWriteToFileMethodInfo
    ResolveShadowNodeMethod "getBounds" o = Gsk.RenderNode.RenderNodeGetBoundsMethodInfo
    ResolveShadowNodeMethod "getChild" o = ShadowNodeGetChildMethodInfo
    ResolveShadowNodeMethod "getNShadows" o = ShadowNodeGetNShadowsMethodInfo
    ResolveShadowNodeMethod "getNodeType" o = Gsk.RenderNode.RenderNodeGetNodeTypeMethodInfo
    ResolveShadowNodeMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveShadowNodeMethod t ShadowNode, O.MethodInfo info ShadowNode p) => OL.IsLabel t (ShadowNode -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

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


-- method ShadowNode::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 draw" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "shadows"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 2
--                 (TInterface Name { namespace = "Gsk" , name = "Shadow" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The shadows to apply"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_shadows"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of entries in the @shadows array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_shadows"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of entries in the @shadows array"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "ShadowNode" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_shadow_node_new" gsk_shadow_node_new :: 
    Ptr Gsk.RenderNode.RenderNode ->        -- child : TInterface (Name {namespace = "Gsk", name = "RenderNode"})
    Ptr Gsk.Shadow.Shadow ->                -- shadows : TCArray False (-1) 2 (TInterface (Name {namespace = "Gsk", name = "Shadow"}))
    Word64 ->                               -- n_shadows : TBasicType TUInt64
    IO (Ptr ShadowNode)

-- | Creates a t'GI.Gsk.Objects.RenderNode.RenderNode' that will draw a /@child@/ with the given
-- /@shadows@/ below it.
shadowNodeNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gsk.RenderNode.IsRenderNode a) =>
    a
    -- ^ /@child@/: The node to draw
    -> [Gsk.Shadow.Shadow]
    -- ^ /@shadows@/: The shadows to apply
    -> m ShadowNode
    -- ^ __Returns:__ A new t'GI.Gsk.Objects.RenderNode.RenderNode'
shadowNodeNew :: a -> [Shadow] -> m ShadowNode
shadowNodeNew a
child [Shadow]
shadows = IO ShadowNode -> m ShadowNode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ShadowNode -> m ShadowNode) -> IO ShadowNode -> m ShadowNode
forall a b. (a -> b) -> a -> b
$ do
    let nShadows :: Word64
nShadows = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [Shadow] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Shadow]
shadows
    Ptr RenderNode
child' <- a -> IO (Ptr RenderNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    [Ptr Shadow]
shadows' <- (Shadow -> IO (Ptr Shadow)) -> [Shadow] -> IO [Ptr Shadow]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Shadow -> IO (Ptr Shadow)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [Shadow]
shadows
    Ptr Shadow
shadows'' <- Int -> [Ptr Shadow] -> IO (Ptr Shadow)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
28 [Ptr Shadow]
shadows'
    Ptr ShadowNode
result <- Ptr RenderNode -> Ptr Shadow -> Word64 -> IO (Ptr ShadowNode)
gsk_shadow_node_new Ptr RenderNode
child' Ptr Shadow
shadows'' Word64
nShadows
    Text -> Ptr ShadowNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"shadowNodeNew" Ptr ShadowNode
result
    ShadowNode
result' <- ((ManagedPtr ShadowNode -> ShadowNode)
-> Ptr ShadowNode -> IO ShadowNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ShadowNode -> ShadowNode
ShadowNode) Ptr ShadowNode
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    (Shadow -> IO ()) -> [Shadow] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Shadow -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [Shadow]
shadows
    Ptr Shadow -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Shadow
shadows''
    ShadowNode -> IO ShadowNode
forall (m :: * -> *) a. Monad m => a -> m a
return ShadowNode
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Retrieves the child t'GI.Gsk.Objects.RenderNode.RenderNode' of the shadow /@node@/.
shadowNodeGetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsShadowNode a) =>
    a
    -- ^ /@node@/: a shadow t'GI.Gsk.Objects.RenderNode.RenderNode'
    -> m Gsk.RenderNode.RenderNode
    -- ^ __Returns:__ the child render node
shadowNodeGetChild :: a -> m RenderNode
shadowNodeGetChild a
node = 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 ShadowNode
node' <- a -> IO (Ptr ShadowNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr RenderNode
result <- Ptr ShadowNode -> IO (Ptr RenderNode)
gsk_shadow_node_get_child Ptr ShadowNode
node'
    Text -> Ptr RenderNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"shadowNodeGetChild" 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 (m :: * -> *) a. Monad m => a -> m a
return RenderNode
result'

#if defined(ENABLE_OVERLOADING)
data ShadowNodeGetChildMethodInfo
instance (signature ~ (m Gsk.RenderNode.RenderNode), MonadIO m, IsShadowNode a) => O.MethodInfo ShadowNodeGetChildMethodInfo a signature where
    overloadedMethod = shadowNodeGetChild

#endif

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

foreign import ccall "gsk_shadow_node_get_n_shadows" gsk_shadow_node_get_n_shadows :: 
    Ptr ShadowNode ->                       -- node : TInterface (Name {namespace = "Gsk", name = "ShadowNode"})
    IO Word64

-- | Retrieves the number of shadows in the /@node@/.
shadowNodeGetNShadows ::
    (B.CallStack.HasCallStack, MonadIO m, IsShadowNode a) =>
    a
    -- ^ /@node@/: a shadow t'GI.Gsk.Objects.RenderNode.RenderNode'
    -> m Word64
    -- ^ __Returns:__ the number of shadows.
shadowNodeGetNShadows :: a -> m Word64
shadowNodeGetNShadows a
node = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShadowNode
node' <- a -> IO (Ptr ShadowNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Word64
result <- Ptr ShadowNode -> IO Word64
gsk_shadow_node_get_n_shadows Ptr ShadowNode
node'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data ShadowNodeGetNShadowsMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsShadowNode a) => O.MethodInfo ShadowNodeGetNShadowsMethodInfo a signature where
    overloadedMethod = shadowNodeGetNShadows

#endif

-- method ShadowNode::peek_shadow
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "node"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "ShadowNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a shadow #GskRenderNode"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "i"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the given index" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Shadow" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_shadow_node_peek_shadow" gsk_shadow_node_peek_shadow :: 
    Ptr ShadowNode ->                       -- node : TInterface (Name {namespace = "Gsk", name = "ShadowNode"})
    Word64 ->                               -- i : TBasicType TUInt64
    IO (Ptr Gsk.Shadow.Shadow)

-- | Retrieves the shadow data at the given index /@i@/.
shadowNodePeekShadow ::
    (B.CallStack.HasCallStack, MonadIO m, IsShadowNode a) =>
    a
    -- ^ /@node@/: a shadow t'GI.Gsk.Objects.RenderNode.RenderNode'
    -> Word64
    -- ^ /@i@/: the given index
    -> m Gsk.Shadow.Shadow
    -- ^ __Returns:__ the shadow data
shadowNodePeekShadow :: a -> Word64 -> m Shadow
shadowNodePeekShadow a
node Word64
i = IO Shadow -> m Shadow
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Shadow -> m Shadow) -> IO Shadow -> m Shadow
forall a b. (a -> b) -> a -> b
$ do
    Ptr ShadowNode
node' <- a -> IO (Ptr ShadowNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr Shadow
result <- Ptr ShadowNode -> Word64 -> IO (Ptr Shadow)
gsk_shadow_node_peek_shadow Ptr ShadowNode
node' Word64
i
    Text -> Ptr Shadow -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"shadowNodePeekShadow" Ptr Shadow
result
    Shadow
result' <- ((ManagedPtr Shadow -> Shadow) -> Ptr Shadow -> IO Shadow
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Shadow -> Shadow
Gsk.Shadow.Shadow) Ptr Shadow
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    Shadow -> IO Shadow
forall (m :: * -> *) a. Monad m => a -> m a
return Shadow
result'

#if defined(ENABLE_OVERLOADING)
data ShadowNodePeekShadowMethodInfo
instance (signature ~ (Word64 -> m Gsk.Shadow.Shadow), MonadIO m, IsShadowNode a) => O.MethodInfo ShadowNodePeekShadowMethodInfo a signature where
    overloadedMethod = shadowNodePeekShadow

#endif