{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A render node that emits a debugging message when drawing its
-- child node.

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

module GI.Gsk.Objects.DebugNode
    ( 

-- * Exported types
    DebugNode(..)                           ,
    IsDebugNode                             ,
    toDebugNode                             ,


 -- * 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.DebugNode#g:method:getChild"), [getMessage]("GI.Gsk.Objects.DebugNode#g:method:getMessage"), [getNodeType]("GI.Gsk.Objects.RenderNode#g:method:getNodeType").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveDebugNodeMethod                  ,
#endif

-- ** getChild #method:getChild#

#if defined(ENABLE_OVERLOADING)
    DebugNodeGetChildMethodInfo             ,
#endif
    debugNodeGetChild                       ,


-- ** getMessage #method:getMessage#

#if defined(ENABLE_OVERLOADING)
    DebugNodeGetMessageMethodInfo           ,
#endif
    debugNodeGetMessage                     ,


-- ** new #method:new#

    debugNodeNew                            ,




    ) 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.Coerce as Coerce
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 {-# SOURCE #-} qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode

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

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

foreign import ccall "gsk_debug_node_get_type"
    c_gsk_debug_node_get_type :: IO B.Types.GType

instance B.Types.TypedObject DebugNode where
    glibType :: IO GType
glibType = IO GType
c_gsk_debug_node_get_type

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

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

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

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

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

#endif

instance (info ~ ResolveDebugNodeMethod t DebugNode, O.OverloadedMethodInfo info DebugNode) => OL.IsLabel t (O.MethodProxy info DebugNode) 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 DebugNode where
    boxedPtrCopy :: DebugNode -> IO DebugNode
boxedPtrCopy = DebugNode -> IO DebugNode
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: DebugNode -> IO ()
boxedPtrFree = \DebugNode
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


-- method DebugNode::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "RenderNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The child to add debug info for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "message"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The debug message" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "DebugNode" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_debug_node_new" gsk_debug_node_new :: 
    Ptr Gsk.RenderNode.RenderNode ->        -- child : TInterface (Name {namespace = "Gsk", name = "RenderNode"})
    CString ->                              -- message : TBasicType TUTF8
    IO (Ptr DebugNode)

-- | Creates a @GskRenderNode@ that will add debug information about
-- the given /@child@/.
-- 
-- Adding this node has no visual effect.
debugNodeNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gsk.RenderNode.IsRenderNode a) =>
    a
    -- ^ /@child@/: The child to add debug info for
    -> T.Text
    -- ^ /@message@/: The debug message
    -> m DebugNode
    -- ^ __Returns:__ A new @GskRenderNode@
debugNodeNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderNode a) =>
a -> Text -> m DebugNode
debugNodeNew a
child Text
message = IO DebugNode -> m DebugNode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DebugNode -> m DebugNode) -> IO DebugNode -> m DebugNode
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
    CString
message' <- Text -> IO CString
textToCString Text
message
    Ptr DebugNode
result <- Ptr RenderNode -> CString -> IO (Ptr DebugNode)
gsk_debug_node_new Ptr RenderNode
child' CString
message'
    Text -> Ptr DebugNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"debugNodeNew" Ptr DebugNode
result
    DebugNode
result' <- ((ManagedPtr DebugNode -> DebugNode)
-> Ptr DebugNode -> IO DebugNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr DebugNode -> DebugNode
DebugNode) Ptr DebugNode
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    DebugNode -> IO DebugNode
forall (m :: * -> *) a. Monad m => a -> m a
return DebugNode
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method DebugNode::get_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "node"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "DebugNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a debug `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_debug_node_get_child" gsk_debug_node_get_child :: 
    Ptr DebugNode ->                        -- node : TInterface (Name {namespace = "Gsk", name = "DebugNode"})
    IO (Ptr Gsk.RenderNode.RenderNode)

-- | Gets the child node that is getting drawn by the given /@node@/.
debugNodeGetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsDebugNode a) =>
    a
    -- ^ /@node@/: a debug @GskRenderNode@
    -> m Gsk.RenderNode.RenderNode
    -- ^ __Returns:__ the child @GskRenderNode@
debugNodeGetChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDebugNode a) =>
a -> m RenderNode
debugNodeGetChild 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 DebugNode
node' <- a -> IO (Ptr DebugNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr RenderNode
result <- Ptr DebugNode -> IO (Ptr RenderNode)
gsk_debug_node_get_child Ptr DebugNode
node'
    Text -> Ptr RenderNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"debugNodeGetChild" 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 DebugNodeGetChildMethodInfo
instance (signature ~ (m Gsk.RenderNode.RenderNode), MonadIO m, IsDebugNode a) => O.OverloadedMethod DebugNodeGetChildMethodInfo a signature where
    overloadedMethod = debugNodeGetChild

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


#endif

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

foreign import ccall "gsk_debug_node_get_message" gsk_debug_node_get_message :: 
    Ptr DebugNode ->                        -- node : TInterface (Name {namespace = "Gsk", name = "DebugNode"})
    IO CString

-- | Gets the debug message that was set on this node
debugNodeGetMessage ::
    (B.CallStack.HasCallStack, MonadIO m, IsDebugNode a) =>
    a
    -- ^ /@node@/: a debug @GskRenderNode@
    -> m T.Text
    -- ^ __Returns:__ The debug message
debugNodeGetMessage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDebugNode a) =>
a -> m Text
debugNodeGetMessage a
node = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DebugNode
node' <- a -> IO (Ptr DebugNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    CString
result <- Ptr DebugNode -> IO CString
gsk_debug_node_get_message Ptr DebugNode
node'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"debugNodeGetMessage" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DebugNodeGetMessageMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDebugNode a) => O.OverloadedMethod DebugNodeGetMessageMethodInfo a signature where
    overloadedMethod = debugNodeGetMessage

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


#endif