{-# 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.ColorMatrixNode
    ( 

-- * Exported types
    ColorMatrixNode(..)                     ,
    IsColorMatrixNode                       ,
    toColorMatrixNode                       ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveColorMatrixNodeMethod            ,
#endif


-- ** getChild #method:getChild#

#if defined(ENABLE_OVERLOADING)
    ColorMatrixNodeGetChildMethodInfo       ,
#endif
    colorMatrixNodeGetChild                 ,


-- ** new #method:new#

    colorMatrixNodeNew                      ,


-- ** peekColorMatrix #method:peekColorMatrix#

#if defined(ENABLE_OVERLOADING)
    ColorMatrixNodePeekColorMatrixMethodInfo,
#endif
    colorMatrixNodePeekColorMatrix          ,


-- ** peekColorOffset #method:peekColorOffset#

#if defined(ENABLE_OVERLOADING)
    ColorMatrixNodePeekColorOffsetMethodInfo,
#endif
    colorMatrixNodePeekColorOffset          ,




    ) 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 qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4
import {-# SOURCE #-} qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode

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

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

foreign import ccall "gsk_color_matrix_node_get_type"
    c_gsk_color_matrix_node_get_type :: IO B.Types.GType

instance B.Types.TypedObject ColorMatrixNode where
    glibType :: IO GType
glibType = IO GType
c_gsk_color_matrix_node_get_type

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveColorMatrixNodeMethod (t :: Symbol) (o :: *) :: * where
    ResolveColorMatrixNodeMethod "draw" o = Gsk.RenderNode.RenderNodeDrawMethodInfo
    ResolveColorMatrixNodeMethod "peekColorMatrix" o = ColorMatrixNodePeekColorMatrixMethodInfo
    ResolveColorMatrixNodeMethod "peekColorOffset" o = ColorMatrixNodePeekColorOffsetMethodInfo
    ResolveColorMatrixNodeMethod "ref" o = Gsk.RenderNode.RenderNodeRefMethodInfo
    ResolveColorMatrixNodeMethod "serialize" o = Gsk.RenderNode.RenderNodeSerializeMethodInfo
    ResolveColorMatrixNodeMethod "unref" o = Gsk.RenderNode.RenderNodeUnrefMethodInfo
    ResolveColorMatrixNodeMethod "writeToFile" o = Gsk.RenderNode.RenderNodeWriteToFileMethodInfo
    ResolveColorMatrixNodeMethod "getBounds" o = Gsk.RenderNode.RenderNodeGetBoundsMethodInfo
    ResolveColorMatrixNodeMethod "getChild" o = ColorMatrixNodeGetChildMethodInfo
    ResolveColorMatrixNodeMethod "getNodeType" o = Gsk.RenderNode.RenderNodeGetNodeTypeMethodInfo
    ResolveColorMatrixNodeMethod l o = O.MethodResolutionFailed l o

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


-- method ColorMatrixNode::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 = "color_matrix"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The matrix to apply"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color_offset"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Vec4" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Values to add to the color"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gsk" , name = "ColorMatrixNode" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_color_matrix_node_new" gsk_color_matrix_node_new :: 
    Ptr Gsk.RenderNode.RenderNode ->        -- child : TInterface (Name {namespace = "Gsk", name = "RenderNode"})
    Ptr Graphene.Matrix.Matrix ->           -- color_matrix : TInterface (Name {namespace = "Graphene", name = "Matrix"})
    Ptr Graphene.Vec4.Vec4 ->               -- color_offset : TInterface (Name {namespace = "Graphene", name = "Vec4"})
    IO (Ptr ColorMatrixNode)

-- | Creates a t'GI.Gsk.Objects.RenderNode.RenderNode' that will drawn the /@child@/ with reduced
-- /@colorMatrix@/.
-- 
-- In particular, the node will transform the operation
-- 
-- 
-- === /plain code/
-- >
-- >  pixel = color_matrix * pixel + color_offset
-- 
-- 
-- for every pixel.
colorMatrixNodeNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gsk.RenderNode.IsRenderNode a) =>
    a
    -- ^ /@child@/: The node to draw
    -> Graphene.Matrix.Matrix
    -- ^ /@colorMatrix@/: The matrix to apply
    -> Graphene.Vec4.Vec4
    -- ^ /@colorOffset@/: Values to add to the color
    -> m ColorMatrixNode
    -- ^ __Returns:__ A new t'GI.Gsk.Objects.RenderNode.RenderNode'
colorMatrixNodeNew :: a -> Matrix -> Vec4 -> m ColorMatrixNode
colorMatrixNodeNew a
child Matrix
colorMatrix Vec4
colorOffset = IO ColorMatrixNode -> m ColorMatrixNode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ColorMatrixNode -> m ColorMatrixNode)
-> IO ColorMatrixNode -> m ColorMatrixNode
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 Matrix
colorMatrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
colorMatrix
    Ptr Vec4
colorOffset' <- Vec4 -> IO (Ptr Vec4)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Vec4
colorOffset
    Ptr ColorMatrixNode
result <- Ptr RenderNode
-> Ptr Matrix -> Ptr Vec4 -> IO (Ptr ColorMatrixNode)
gsk_color_matrix_node_new Ptr RenderNode
child' Ptr Matrix
colorMatrix' Ptr Vec4
colorOffset'
    Text -> Ptr ColorMatrixNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"colorMatrixNodeNew" Ptr ColorMatrixNode
result
    ColorMatrixNode
result' <- ((ManagedPtr ColorMatrixNode -> ColorMatrixNode)
-> Ptr ColorMatrixNode -> IO ColorMatrixNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ColorMatrixNode -> ColorMatrixNode
ColorMatrixNode) Ptr ColorMatrixNode
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
colorMatrix
    Vec4 -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Vec4
colorOffset
    ColorMatrixNode -> IO ColorMatrixNode
forall (m :: * -> *) a. Monad m => a -> m a
return ColorMatrixNode
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

-- | Gets the child node that is getting its colors modified by the given /@node@/.
colorMatrixNodeGetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsColorMatrixNode a) =>
    a
    -- ^ /@node@/: a color matrix t'GI.Gsk.Objects.RenderNode.RenderNode'
    -> m Gsk.RenderNode.RenderNode
    -- ^ __Returns:__ The child that is getting its colors modified
colorMatrixNodeGetChild :: a -> m RenderNode
colorMatrixNodeGetChild 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 ColorMatrixNode
node' <- a -> IO (Ptr ColorMatrixNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr RenderNode
result <- Ptr ColorMatrixNode -> IO (Ptr RenderNode)
gsk_color_matrix_node_get_child Ptr ColorMatrixNode
node'
    Text -> Ptr RenderNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"colorMatrixNodeGetChild" 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 ColorMatrixNodeGetChildMethodInfo
instance (signature ~ (m Gsk.RenderNode.RenderNode), MonadIO m, IsColorMatrixNode a) => O.MethodInfo ColorMatrixNodeGetChildMethodInfo a signature where
    overloadedMethod = colorMatrixNodeGetChild

#endif

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

foreign import ccall "gsk_color_matrix_node_peek_color_matrix" gsk_color_matrix_node_peek_color_matrix :: 
    Ptr ColorMatrixNode ->                  -- node : TInterface (Name {namespace = "Gsk", name = "ColorMatrixNode"})
    IO (Ptr Graphene.Matrix.Matrix)

-- | Retrieves the color matrix used by the /@node@/.
colorMatrixNodePeekColorMatrix ::
    (B.CallStack.HasCallStack, MonadIO m, IsColorMatrixNode a) =>
    a
    -- ^ /@node@/: a color matrix t'GI.Gsk.Objects.RenderNode.RenderNode'
    -> m Graphene.Matrix.Matrix
    -- ^ __Returns:__ a 4x4 color matrix
colorMatrixNodePeekColorMatrix :: a -> m Matrix
colorMatrixNodePeekColorMatrix a
node = IO Matrix -> m Matrix
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Matrix -> m Matrix) -> IO Matrix -> m Matrix
forall a b. (a -> b) -> a -> b
$ do
    Ptr ColorMatrixNode
node' <- a -> IO (Ptr ColorMatrixNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr Matrix
result <- Ptr ColorMatrixNode -> IO (Ptr Matrix)
gsk_color_matrix_node_peek_color_matrix Ptr ColorMatrixNode
node'
    Text -> Ptr Matrix -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"colorMatrixNodePeekColorMatrix" Ptr Matrix
result
    Matrix
result' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Graphene.Matrix.Matrix) Ptr Matrix
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    Matrix -> IO Matrix
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result'

#if defined(ENABLE_OVERLOADING)
data ColorMatrixNodePeekColorMatrixMethodInfo
instance (signature ~ (m Graphene.Matrix.Matrix), MonadIO m, IsColorMatrixNode a) => O.MethodInfo ColorMatrixNodePeekColorMatrixMethodInfo a signature where
    overloadedMethod = colorMatrixNodePeekColorMatrix

#endif

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

foreign import ccall "gsk_color_matrix_node_peek_color_offset" gsk_color_matrix_node_peek_color_offset :: 
    Ptr ColorMatrixNode ->                  -- node : TInterface (Name {namespace = "Gsk", name = "ColorMatrixNode"})
    IO (Ptr Graphene.Vec4.Vec4)

-- | Retrieves the color offset used by the /@node@/.
colorMatrixNodePeekColorOffset ::
    (B.CallStack.HasCallStack, MonadIO m, IsColorMatrixNode a) =>
    a
    -- ^ /@node@/: a color matrix t'GI.Gsk.Objects.RenderNode.RenderNode'
    -> m Graphene.Vec4.Vec4
    -- ^ __Returns:__ a color vector
colorMatrixNodePeekColorOffset :: a -> m Vec4
colorMatrixNodePeekColorOffset a
node = IO Vec4 -> m Vec4
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vec4 -> m Vec4) -> IO Vec4 -> m Vec4
forall a b. (a -> b) -> a -> b
$ do
    Ptr ColorMatrixNode
node' <- a -> IO (Ptr ColorMatrixNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr Vec4
result <- Ptr ColorMatrixNode -> IO (Ptr Vec4)
gsk_color_matrix_node_peek_color_offset Ptr ColorMatrixNode
node'
    Text -> Ptr Vec4 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"colorMatrixNodePeekColorOffset" Ptr Vec4
result
    Vec4
result' <- ((ManagedPtr Vec4 -> Vec4) -> Ptr Vec4 -> IO Vec4
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Vec4 -> Vec4
Graphene.Vec4.Vec4) Ptr Vec4
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    Vec4 -> IO Vec4
forall (m :: * -> *) a. Monad m => a -> m a
return Vec4
result'

#if defined(ENABLE_OVERLOADING)
data ColorMatrixNodePeekColorOffsetMethodInfo
instance (signature ~ (m Graphene.Vec4.Vec4), MonadIO m, IsColorMatrixNode a) => O.MethodInfo ColorMatrixNodePeekColorOffsetMethodInfo a signature where
    overloadedMethod = colorMatrixNodePeekColorOffset

#endif