{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A render node controlling the opacity of its single child node.

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

module GI.Gsk.Objects.OpacityNode
    ( 

-- * Exported types
    OpacityNode(..)                         ,
    IsOpacityNode                           ,
    toOpacityNode                           ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveOpacityNodeMethod                ,
#endif

-- ** getChild #method:getChild#

#if defined(ENABLE_OVERLOADING)
    OpacityNodeGetChildMethodInfo           ,
#endif
    opacityNodeGetChild                     ,


-- ** getOpacity #method:getOpacity#

#if defined(ENABLE_OVERLOADING)
    OpacityNodeGetOpacityMethodInfo         ,
#endif
    opacityNodeGetOpacity                   ,


-- ** new #method:new#

    opacityNodeNew                          ,




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

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

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

foreign import ccall "gsk_opacity_node_get_type"
    c_gsk_opacity_node_get_type :: IO B.Types.GType

instance B.Types.TypedObject OpacityNode where
    glibType :: IO GType
glibType = IO GType
c_gsk_opacity_node_get_type

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

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

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

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

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

#endif

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


-- method OpacityNode::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 = "opacity"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The opacity to apply"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "OpacityNode" })
-- throws : False
-- Skip return : False

foreign import ccall "gsk_opacity_node_new" gsk_opacity_node_new :: 
    Ptr Gsk.RenderNode.RenderNode ->        -- child : TInterface (Name {namespace = "Gsk", name = "RenderNode"})
    CFloat ->                               -- opacity : TBasicType TFloat
    IO (Ptr OpacityNode)

-- | Creates a @GskRenderNode@ that will drawn the /@child@/ with reduced
-- /@opacity@/.
opacityNodeNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gsk.RenderNode.IsRenderNode a) =>
    a
    -- ^ /@child@/: The node to draw
    -> Float
    -- ^ /@opacity@/: The opacity to apply
    -> m OpacityNode
    -- ^ __Returns:__ A new @GskRenderNode@
opacityNodeNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderNode a) =>
a -> Float -> m OpacityNode
opacityNodeNew a
child Float
opacity = IO OpacityNode -> m OpacityNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OpacityNode -> m OpacityNode)
-> IO OpacityNode -> m OpacityNode
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
    let opacity' :: CFloat
opacity' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
opacity
    Ptr OpacityNode
result <- Ptr RenderNode -> CFloat -> IO (Ptr OpacityNode)
gsk_opacity_node_new Ptr RenderNode
child' CFloat
opacity'
    Text -> Ptr OpacityNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"opacityNodeNew" Ptr OpacityNode
result
    OpacityNode
result' <- ((ManagedPtr OpacityNode -> OpacityNode)
-> Ptr OpacityNode -> IO OpacityNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr OpacityNode -> OpacityNode
OpacityNode) Ptr OpacityNode
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    OpacityNode -> IO OpacityNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return OpacityNode
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

-- | Gets the child node that is getting opacityed by the given /@node@/.
opacityNodeGetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsOpacityNode a) =>
    a
    -- ^ /@node@/: a @GskRenderNode@ for an opacity
    -> m Gsk.RenderNode.RenderNode
    -- ^ __Returns:__ The child that is getting opacityed
opacityNodeGetChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsOpacityNode a) =>
a -> m RenderNode
opacityNodeGetChild a
node = IO RenderNode -> m RenderNode
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RenderNode -> m RenderNode) -> IO RenderNode -> m RenderNode
forall a b. (a -> b) -> a -> b
$ do
    Ptr OpacityNode
node' <- a -> IO (Ptr OpacityNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    Ptr RenderNode
result <- Ptr OpacityNode -> IO (Ptr RenderNode)
gsk_opacity_node_get_child Ptr OpacityNode
node'
    Text -> Ptr RenderNode -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"opacityNodeGetChild" Ptr RenderNode
result
    RenderNode
result' <- ((ManagedPtr RenderNode -> RenderNode)
-> Ptr RenderNode -> IO RenderNode
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr RenderNode -> RenderNode
Gsk.RenderNode.RenderNode) Ptr RenderNode
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
node
    RenderNode -> IO RenderNode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RenderNode
result'

#if defined(ENABLE_OVERLOADING)
data OpacityNodeGetChildMethodInfo
instance (signature ~ (m Gsk.RenderNode.RenderNode), MonadIO m, IsOpacityNode a) => O.OverloadedMethod OpacityNodeGetChildMethodInfo a signature where
    overloadedMethod = opacityNodeGetChild

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


#endif

-- method OpacityNode::get_opacity
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "node"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "OpacityNode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GskRenderNode` for an opacity"
--                 , 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_opacity_node_get_opacity" gsk_opacity_node_get_opacity :: 
    Ptr OpacityNode ->                      -- node : TInterface (Name {namespace = "Gsk", name = "OpacityNode"})
    IO CFloat

-- | Gets the transparency factor for an opacity node.
opacityNodeGetOpacity ::
    (B.CallStack.HasCallStack, MonadIO m, IsOpacityNode a) =>
    a
    -- ^ /@node@/: a @GskRenderNode@ for an opacity
    -> m Float
    -- ^ __Returns:__ the opacity factor
opacityNodeGetOpacity :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsOpacityNode a) =>
a -> m Float
opacityNodeGetOpacity 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 OpacityNode
node' <- a -> IO (Ptr OpacityNode)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
node
    CFloat
result <- Ptr OpacityNode -> IO CFloat
gsk_opacity_node_get_opacity Ptr OpacityNode
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 OpacityNodeGetOpacityMethodInfo
instance (signature ~ (m Float), MonadIO m, IsOpacityNode a) => O.OverloadedMethod OpacityNodeGetOpacityMethodInfo a signature where
    overloadedMethod = opacityNodeGetOpacity

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


#endif