{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A render node for a conic gradient.

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

module GI.Gsk.Objects.ConicGradientNode
    ( 

-- * Exported types
    ConicGradientNode(..)                   ,
    IsConicGradientNode                     ,
    toConicGradientNode                     ,


 -- * 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
-- [getAngle]("GI.Gsk.Objects.ConicGradientNode#g:method:getAngle"), [getBounds]("GI.Gsk.Objects.RenderNode#g:method:getBounds"), [getCenter]("GI.Gsk.Objects.ConicGradientNode#g:method:getCenter"), [getColorStops]("GI.Gsk.Objects.ConicGradientNode#g:method:getColorStops"), [getNColorStops]("GI.Gsk.Objects.ConicGradientNode#g:method:getNColorStops"), [getNodeType]("GI.Gsk.Objects.RenderNode#g:method:getNodeType"), [getRotation]("GI.Gsk.Objects.ConicGradientNode#g:method:getRotation").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveConicGradientNodeMethod          ,
#endif

-- ** getAngle #method:getAngle#

#if defined(ENABLE_OVERLOADING)
    ConicGradientNodeGetAngleMethodInfo     ,
#endif
    conicGradientNodeGetAngle               ,


-- ** getCenter #method:getCenter#

#if defined(ENABLE_OVERLOADING)
    ConicGradientNodeGetCenterMethodInfo    ,
#endif
    conicGradientNodeGetCenter              ,


-- ** getColorStops #method:getColorStops#

#if defined(ENABLE_OVERLOADING)
    ConicGradientNodeGetColorStopsMethodInfo,
#endif
    conicGradientNodeGetColorStops          ,


-- ** getNColorStops #method:getNColorStops#

#if defined(ENABLE_OVERLOADING)
    ConicGradientNodeGetNColorStopsMethodInfo,
#endif
    conicGradientNodeGetNColorStops         ,


-- ** getRotation #method:getRotation#

#if defined(ENABLE_OVERLOADING)
    ConicGradientNodeGetRotationMethodInfo  ,
#endif
    conicGradientNodeGetRotation            ,


-- ** new #method:new#

    conicGradientNodeNew                    ,




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

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

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

foreign import ccall "gsk_conic_gradient_node_get_type"
    c_gsk_conic_gradient_node_get_type :: IO B.Types.GType

instance B.Types.TypedObject ConicGradientNode where
    glibType :: IO GType
glibType = IO GType
c_gsk_conic_gradient_node_get_type

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

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

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

--- XXX Missing getter and/or setter, so no GValue instance could be generated.
#if defined(ENABLE_OVERLOADING)
type family ResolveConicGradientNodeMethod (t :: Symbol) (o :: *) :: * where
    ResolveConicGradientNodeMethod "draw" o = Gsk.RenderNode.RenderNodeDrawMethodInfo
    ResolveConicGradientNodeMethod "ref" o = Gsk.RenderNode.RenderNodeRefMethodInfo
    ResolveConicGradientNodeMethod "serialize" o = Gsk.RenderNode.RenderNodeSerializeMethodInfo
    ResolveConicGradientNodeMethod "unref" o = Gsk.RenderNode.RenderNodeUnrefMethodInfo
    ResolveConicGradientNodeMethod "writeToFile" o = Gsk.RenderNode.RenderNodeWriteToFileMethodInfo
    ResolveConicGradientNodeMethod "getAngle" o = ConicGradientNodeGetAngleMethodInfo
    ResolveConicGradientNodeMethod "getBounds" o = Gsk.RenderNode.RenderNodeGetBoundsMethodInfo
    ResolveConicGradientNodeMethod "getCenter" o = ConicGradientNodeGetCenterMethodInfo
    ResolveConicGradientNodeMethod "getColorStops" o = ConicGradientNodeGetColorStopsMethodInfo
    ResolveConicGradientNodeMethod "getNColorStops" o = ConicGradientNodeGetNColorStopsMethodInfo
    ResolveConicGradientNodeMethod "getNodeType" o = Gsk.RenderNode.RenderNodeGetNodeTypeMethodInfo
    ResolveConicGradientNodeMethod "getRotation" o = ConicGradientNodeGetRotationMethodInfo
    ResolveConicGradientNodeMethod l o = O.MethodResolutionFailed l o

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

#endif

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


-- method ConicGradientNode::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "bounds"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the bounds of the node"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "center"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the center of the gradient"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rotation"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the rotation of the gradient in degrees"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color_stops"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 4
--                 (TInterface Name { namespace = "Gsk" , name = "ColorStop" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a pointer to an array of\n  `GskColorStop` defining the gradient. The offsets of all color stops\n  must be increasing. The first stop's offset must be >= 0 and the last\n  stop's offset must be <= 1."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_color_stops"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of elements in @color_stops"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_color_stops"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of elements in @color_stops"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gsk" , name = "ConicGradientNode" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_conic_gradient_node_new" gsk_conic_gradient_node_new :: 
    Ptr Graphene.Rect.Rect ->               -- bounds : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Point.Point ->             -- center : TInterface (Name {namespace = "Graphene", name = "Point"})
    CFloat ->                               -- rotation : TBasicType TFloat
    Ptr Gsk.ColorStop.ColorStop ->          -- color_stops : TCArray False (-1) 4 (TInterface (Name {namespace = "Gsk", name = "ColorStop"}))
    Word64 ->                               -- n_color_stops : TBasicType TUInt64
    IO (Ptr ConicGradientNode)

-- | Creates a @GskRenderNode@ that draws a conic gradient.
-- 
-- The conic gradient
-- starts around /@center@/ in the direction of /@rotation@/. A rotation of 0 means
-- that the gradient points up. Color stops are then added clockwise.
conicGradientNodeNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Graphene.Rect.Rect
    -- ^ /@bounds@/: the bounds of the node
    -> Graphene.Point.Point
    -- ^ /@center@/: the center of the gradient
    -> Float
    -- ^ /@rotation@/: the rotation of the gradient in degrees
    -> [Gsk.ColorStop.ColorStop]
    -- ^ /@colorStops@/: a pointer to an array of
    --   @GskColorStop@ defining the gradient. The offsets of all color stops
    --   must be increasing. The first stop\'s offset must be >= 0 and the last
    --   stop\'s offset must be \<= 1.
    -> m ConicGradientNode
    -- ^ __Returns:__ A new @GskRenderNode@
conicGradientNodeNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rect -> Point -> Float -> [ColorStop] -> m ConicGradientNode
conicGradientNodeNew Rect
bounds Point
center Float
rotation [ColorStop]
colorStops = IO ConicGradientNode -> m ConicGradientNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ConicGradientNode -> m ConicGradientNode)
-> IO ConicGradientNode -> m ConicGradientNode
forall a b. (a -> b) -> a -> b
$ do
    let nColorStops :: Word64
nColorStops = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [ColorStop] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [ColorStop]
colorStops
    Ptr Rect
bounds' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
bounds
    Ptr Point
center' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
center
    let rotation' :: CFloat
rotation' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
rotation
    [Ptr ColorStop]
colorStops' <- (ColorStop -> IO (Ptr ColorStop))
-> [ColorStop] -> IO [Ptr ColorStop]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ColorStop -> IO (Ptr ColorStop)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [ColorStop]
colorStops
    Ptr ColorStop
colorStops'' <- Int -> [Ptr ColorStop] -> IO (Ptr ColorStop)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
20 [Ptr ColorStop]
colorStops'
    Ptr ConicGradientNode
result <- Ptr Rect
-> Ptr Point
-> CFloat
-> Ptr ColorStop
-> Word64
-> IO (Ptr ConicGradientNode)
gsk_conic_gradient_node_new Ptr Rect
bounds' Ptr Point
center' CFloat
rotation' Ptr ColorStop
colorStops'' Word64
nColorStops
    Text -> Ptr ConicGradientNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"conicGradientNodeNew" Ptr ConicGradientNode
result
    ConicGradientNode
result' <- ((ManagedPtr ConicGradientNode -> ConicGradientNode)
-> Ptr ConicGradientNode -> IO ConicGradientNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ConicGradientNode -> ConicGradientNode
ConicGradientNode) Ptr ConicGradientNode
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
bounds
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
center
    (ColorStop -> IO ()) -> [ColorStop] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ColorStop -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [ColorStop]
colorStops
    Ptr ColorStop -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr ColorStop
colorStops''
    ConicGradientNode -> IO ConicGradientNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ConicGradientNode
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gsk_conic_gradient_node_get_angle" gsk_conic_gradient_node_get_angle :: 
    Ptr ConicGradientNode ->                -- node : TInterface (Name {namespace = "Gsk", name = "ConicGradientNode"})
    IO CFloat

-- | Retrieves the angle for the gradient in radians, normalized in [0, 2 * PI].
-- 
-- The angle is starting at the top and going clockwise, as expressed
-- in the css specification:
-- 
--     angle = 90 - 'GI.Gsk.Objects.ConicGradientNode.conicGradientNodeGetRotation'
-- 
-- /Since: 4.2/
conicGradientNodeGetAngle ::
    (B.CallStack.HasCallStack, MonadIO m, IsConicGradientNode a) =>
    a
    -- ^ /@node@/: a @GskRenderNode@ for a conic gradient
    -> m Float
    -- ^ __Returns:__ the angle for the gradient
conicGradientNodeGetAngle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConicGradientNode a) =>
a -> m Float
conicGradientNodeGetAngle a
node = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr ConicGradientNode
node' <- a -> IO (Ptr ConicGradientNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    CFloat
result <- Ptr ConicGradientNode -> IO CFloat
gsk_conic_gradient_node_get_angle Ptr ConicGradientNode
node'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data ConicGradientNodeGetAngleMethodInfo
instance (signature ~ (m Float), MonadIO m, IsConicGradientNode a) => O.OverloadedMethod ConicGradientNodeGetAngleMethodInfo a signature where
    overloadedMethod = conicGradientNodeGetAngle

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


#endif

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

foreign import ccall "gsk_conic_gradient_node_get_center" gsk_conic_gradient_node_get_center :: 
    Ptr ConicGradientNode ->                -- node : TInterface (Name {namespace = "Gsk", name = "ConicGradientNode"})
    IO (Ptr Graphene.Point.Point)

-- | Retrieves the center pointer for the gradient.
conicGradientNodeGetCenter ::
    (B.CallStack.HasCallStack, MonadIO m, IsConicGradientNode a) =>
    a
    -- ^ /@node@/: a @GskRenderNode@ for a conic gradient
    -> m Graphene.Point.Point
    -- ^ __Returns:__ the center point for the gradient
conicGradientNodeGetCenter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConicGradientNode a) =>
a -> m Point
conicGradientNodeGetCenter a
node = IO Point -> m Point
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr ConicGradientNode
node' <- a -> IO (Ptr ConicGradientNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr Point
result <- Ptr ConicGradientNode -> IO (Ptr Point)
gsk_conic_gradient_node_get_center Ptr ConicGradientNode
node'
    Text -> Ptr Point -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"conicGradientNodeGetCenter" Ptr Point
result
    Point
result' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Point -> Point
Graphene.Point.Point) Ptr Point
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    Point -> IO Point
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Point
result'

#if defined(ENABLE_OVERLOADING)
data ConicGradientNodeGetCenterMethodInfo
instance (signature ~ (m Graphene.Point.Point), MonadIO m, IsConicGradientNode a) => O.OverloadedMethod ConicGradientNodeGetCenterMethodInfo a signature where
    overloadedMethod = conicGradientNodeGetCenter

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


#endif

-- method ConicGradientNode::get_color_stops
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "node"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "ConicGradientNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GskRenderNode` for a conic gradient"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_stops"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number of color stops in the returned array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_stops"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "the number of color stops in the returned array"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just
--               (TCArray
--                  False
--                  (-1)
--                  1
--                  (TInterface Name { namespace = "Gsk" , name = "ColorStop" }))
-- throws : False
-- Skip return : False

foreign import ccall "gsk_conic_gradient_node_get_color_stops" gsk_conic_gradient_node_get_color_stops :: 
    Ptr ConicGradientNode ->                -- node : TInterface (Name {namespace = "Gsk", name = "ConicGradientNode"})
    Ptr Word64 ->                           -- n_stops : TBasicType TUInt64
    IO (Ptr Gsk.ColorStop.ColorStop)

-- | Retrieves the color stops in the gradient.
conicGradientNodeGetColorStops ::
    (B.CallStack.HasCallStack, MonadIO m, IsConicGradientNode a) =>
    a
    -- ^ /@node@/: a @GskRenderNode@ for a conic gradient
    -> m [Gsk.ColorStop.ColorStop]
    -- ^ __Returns:__ the color stops in the gradient
conicGradientNodeGetColorStops :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConicGradientNode a) =>
a -> m [ColorStop]
conicGradientNodeGetColorStops a
node = IO [ColorStop] -> m [ColorStop]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ColorStop] -> m [ColorStop])
-> IO [ColorStop] -> m [ColorStop]
forall a b. (a -> b) -> a -> b
$ do
    Ptr ConicGradientNode
node' <- a -> IO (Ptr ConicGradientNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr Word64
nStops <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr ColorStop
result <- Ptr ConicGradientNode -> Ptr Word64 -> IO (Ptr ColorStop)
gsk_conic_gradient_node_get_color_stops Ptr ConicGradientNode
node' Ptr Word64
nStops
    Word64
nStops' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
nStops
    Text -> Ptr ColorStop -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"conicGradientNodeGetColorStops" Ptr ColorStop
result
    [Ptr ColorStop]
result' <- (Int -> Word64 -> Ptr ColorStop -> IO [Ptr ColorStop]
forall a b. Integral a => Int -> a -> Ptr b -> IO [Ptr b]
unpackBlockArrayWithLength Int
20 Word64
nStops') Ptr ColorStop
result
    [ColorStop]
result'' <- (Ptr ColorStop -> IO ColorStop)
-> [Ptr ColorStop] -> IO [ColorStop]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr ColorStop -> ColorStop)
-> Ptr ColorStop -> IO ColorStop
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr ColorStop -> ColorStop
Gsk.ColorStop.ColorStop) [Ptr ColorStop]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
nStops
    [ColorStop] -> IO [ColorStop]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ColorStop]
result''

#if defined(ENABLE_OVERLOADING)
data ConicGradientNodeGetColorStopsMethodInfo
instance (signature ~ (m [Gsk.ColorStop.ColorStop]), MonadIO m, IsConicGradientNode a) => O.OverloadedMethod ConicGradientNodeGetColorStopsMethodInfo a signature where
    overloadedMethod = conicGradientNodeGetColorStops

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


#endif

-- method ConicGradientNode::get_n_color_stops
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "node"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "ConicGradientNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GskRenderNode` for a conic gradient"
--                 , 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_conic_gradient_node_get_n_color_stops" gsk_conic_gradient_node_get_n_color_stops :: 
    Ptr ConicGradientNode ->                -- node : TInterface (Name {namespace = "Gsk", name = "ConicGradientNode"})
    IO Word64

-- | Retrieves the number of color stops in the gradient.
conicGradientNodeGetNColorStops ::
    (B.CallStack.HasCallStack, MonadIO m, IsConicGradientNode a) =>
    a
    -- ^ /@node@/: a @GskRenderNode@ for a conic gradient
    -> m Word64
    -- ^ __Returns:__ the number of color stops
conicGradientNodeGetNColorStops :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConicGradientNode a) =>
a -> m Word64
conicGradientNodeGetNColorStops a
node = IO Word64 -> m Word64
forall a. IO a -> m a
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 ConicGradientNode
node' <- a -> IO (Ptr ConicGradientNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Word64
result <- Ptr ConicGradientNode -> IO Word64
gsk_conic_gradient_node_get_n_color_stops Ptr ConicGradientNode
node'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    Word64 -> IO Word64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data ConicGradientNodeGetNColorStopsMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsConicGradientNode a) => O.OverloadedMethod ConicGradientNodeGetNColorStopsMethodInfo a signature where
    overloadedMethod = conicGradientNodeGetNColorStops

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


#endif

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

foreign import ccall "gsk_conic_gradient_node_get_rotation" gsk_conic_gradient_node_get_rotation :: 
    Ptr ConicGradientNode ->                -- node : TInterface (Name {namespace = "Gsk", name = "ConicGradientNode"})
    IO CFloat

-- | Retrieves the rotation for the gradient in degrees.
conicGradientNodeGetRotation ::
    (B.CallStack.HasCallStack, MonadIO m, IsConicGradientNode a) =>
    a
    -- ^ /@node@/: a @GskRenderNode@ for a conic gradient
    -> m Float
    -- ^ __Returns:__ the rotation for the gradient
conicGradientNodeGetRotation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConicGradientNode a) =>
a -> m Float
conicGradientNodeGetRotation a
node = IO Float -> m Float
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr ConicGradientNode
node' <- a -> IO (Ptr ConicGradientNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    CFloat
result <- Ptr ConicGradientNode -> IO CFloat
gsk_conic_gradient_node_get_rotation Ptr ConicGradientNode
node'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    Float -> IO Float
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data ConicGradientNodeGetRotationMethodInfo
instance (signature ~ (m Float), MonadIO m, IsConicGradientNode a) => O.OverloadedMethod ConicGradientNodeGetRotationMethodInfo a signature where
    overloadedMethod = conicGradientNodeGetRotation

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


#endif