{-# language CPP #-}
-- | = Name
--
-- VK_EXT_blend_operation_advanced - device extension
--
-- == VK_EXT_blend_operation_advanced
--
-- [__Name String__]
--     @VK_EXT_blend_operation_advanced@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     149
--
-- [__Revision__]
--     2
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
-- [__Contact__]
--
--     -   Jeff Bolz
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_blend_operation_advanced] @jeffbolznv%0A<<Here describe the issue or question you have about the VK_EXT_blend_operation_advanced extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2017-06-12
--
-- [__Contributors__]
--
--     -   Jeff Bolz, NVIDIA
--
-- == Description
--
-- This extension adds a number of “advanced” blending operations that
-- /can/ be used to perform new color blending operations, many of which
-- are more complex than the standard blend modes provided by unextended
-- Vulkan. This extension requires different styles of usage, depending on
-- the level of hardware support and the enabled features:
--
-- -   If
--     'PhysicalDeviceBlendOperationAdvancedFeaturesEXT'::@advancedBlendCoherentOperations@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', the new blending
--     operations are supported, but a memory dependency /must/ separate
--     each advanced blend operation on a given sample.
--     'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT'
--     is used to synchronize reads using advanced blend operations.
--
-- -   If
--     'PhysicalDeviceBlendOperationAdvancedFeaturesEXT'::@advancedBlendCoherentOperations@
--     is 'Vulkan.Core10.FundamentalTypes.TRUE', advanced blend operations
--     obey primitive order just like basic blend operations.
--
-- In unextended Vulkan, the set of blending operations is limited, and
-- /can/ be expressed very simply. The
-- 'Vulkan.Core10.Enums.BlendOp.BLEND_OP_MIN' and
-- 'Vulkan.Core10.Enums.BlendOp.BLEND_OP_MAX' blend operations simply
-- compute component-wise minimums or maximums of source and destination
-- color components. The 'Vulkan.Core10.Enums.BlendOp.BLEND_OP_ADD',
-- 'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SUBTRACT', and
-- 'Vulkan.Core10.Enums.BlendOp.BLEND_OP_REVERSE_SUBTRACT' modes multiply
-- the source and destination colors by source and destination factors and
-- either add the two products together or subtract one from the other.
-- This limited set of operations supports many common blending operations
-- but precludes the use of more sophisticated transparency and blending
-- operations commonly available in many dedicated imaging APIs.
--
-- This extension provides a number of new “advanced” blending operations.
-- Unlike traditional blending operations using
-- 'Vulkan.Core10.Enums.BlendOp.BLEND_OP_ADD', these blending equations do
-- not use source and destination factors specified by
-- 'Vulkan.Core10.Enums.BlendFactor.BlendFactor'. Instead, each blend
-- operation specifies a complete equation based on the source and
-- destination colors. These new blend operations are used for both RGB and
-- alpha components; they /must/ not be used to perform separate RGB and
-- alpha blending (via different values of color and alpha
-- 'Vulkan.Core10.Enums.BlendOp.BlendOp').
--
-- These blending operations are performed using premultiplied colors,
-- where RGB colors /can/ be considered premultiplied or non-premultiplied
-- by alpha, according to the @srcPremultiplied@ and @dstPremultiplied@
-- members of 'PipelineColorBlendAdvancedStateCreateInfoEXT'. If a color is
-- considered non-premultiplied, the (R,G,B) color components are
-- multiplied by the alpha component prior to blending. For
-- non-premultiplied color components in the range [0,1], the corresponding
-- premultiplied color component would have values in the range [0 × A, 1 ×
-- A].
--
-- Many of these advanced blending equations are formulated where the
-- result of blending source and destination colors with partial coverage
-- have three separate contributions: from the portions covered by both the
-- source and the destination, from the portion covered only by the source,
-- and from the portion covered only by the destination. The blend
-- parameter 'PipelineColorBlendAdvancedStateCreateInfoEXT'::@blendOverlap@
-- /can/ be used to specify a correlation between source and destination
-- pixel coverage. If set to 'BLEND_OVERLAP_CONJOINT_EXT', the source and
-- destination are considered to have maximal overlap, as would be the case
-- if drawing two objects on top of each other. If set to
-- 'BLEND_OVERLAP_DISJOINT_EXT', the source and destination are considered
-- to have minimal overlap, as would be the case when rendering a complex
-- polygon tessellated into individual non-intersecting triangles. If set
-- to 'BLEND_OVERLAP_UNCORRELATED_EXT', the source and destination coverage
-- are assumed to have no spatial correlation within the pixel.
--
-- In addition to the coherency issues on implementations not supporting
-- @advancedBlendCoherentOperations@, this extension has several
-- limitations worth noting. First, the new blend operations have a limit
-- on the number of color attachments they /can/ be used with, as indicated
-- by
-- 'PhysicalDeviceBlendOperationAdvancedPropertiesEXT'::@advancedBlendMaxColorAttachments@.
-- Additionally, blending precision /may/ be limited to 16-bit
-- floating-point, which /may/ result in a loss of precision and dynamic
-- range for framebuffer formats with 32-bit floating-point components, and
-- in a loss of precision for formats with 12- and 16-bit signed or
-- unsigned normalized integer components.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceBlendOperationAdvancedFeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceBlendOperationAdvancedPropertiesEXT'
--
-- -   Extending
--     'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo':
--
--     -   'PipelineColorBlendAdvancedStateCreateInfoEXT'
--
-- == New Enums
--
-- -   'BlendOverlapEXT'
--
-- == New Enum Constants
--
-- -   'EXT_BLEND_OPERATION_ADVANCED_EXTENSION_NAME'
--
-- -   'EXT_BLEND_OPERATION_ADVANCED_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits':
--
--     -   'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.BlendOp.BlendOp':
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_BLUE_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_COLORBURN_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_COLORDODGE_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_CONTRAST_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DARKEN_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DIFFERENCE_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DST_ATOP_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DST_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DST_IN_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DST_OUT_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DST_OVER_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_EXCLUSION_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_GREEN_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_HARDLIGHT_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_HARDMIX_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_HSL_COLOR_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_HSL_HUE_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_HSL_LUMINOSITY_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_HSL_SATURATION_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_INVERT_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_INVERT_OVG_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_INVERT_RGB_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_LIGHTEN_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_LINEARBURN_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_LINEARDODGE_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_LINEARLIGHT_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_MINUS_CLAMPED_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_MINUS_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_MULTIPLY_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_OVERLAY_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_PINLIGHT_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_PLUS_CLAMPED_ALPHA_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_PLUS_CLAMPED_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_PLUS_DARKER_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_PLUS_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_RED_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SCREEN_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SOFTLIGHT_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SRC_ATOP_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SRC_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SRC_IN_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SRC_OUT_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SRC_OVER_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_VIVIDLIGHT_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_XOR_EXT'
--
--     -   'Vulkan.Core10.Enums.BlendOp.BLEND_OP_ZERO_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_PROPERTIES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_ADVANCED_STATE_CREATE_INFO_EXT'
--
-- == Issues
--
-- None.
--
-- == Version History
--
-- -   Revision 1, 2017-06-12 (Jeff Bolz)
--
--     -   Internal revisions
--
-- -   Revision 2, 2017-06-12 (Jeff Bolz)
--
--     -   Internal revisions
--
-- == See Also
--
-- 'BlendOverlapEXT', 'PhysicalDeviceBlendOperationAdvancedFeaturesEXT',
-- 'PhysicalDeviceBlendOperationAdvancedPropertiesEXT',
-- 'PipelineColorBlendAdvancedStateCreateInfoEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_blend_operation_advanced Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_EXT_blend_operation_advanced  ( PhysicalDeviceBlendOperationAdvancedFeaturesEXT(..)
                                                          , PhysicalDeviceBlendOperationAdvancedPropertiesEXT(..)
                                                          , PipelineColorBlendAdvancedStateCreateInfoEXT(..)
                                                          , BlendOverlapEXT( BLEND_OVERLAP_UNCORRELATED_EXT
                                                                           , BLEND_OVERLAP_DISJOINT_EXT
                                                                           , BLEND_OVERLAP_CONJOINT_EXT
                                                                           , ..
                                                                           )
                                                          , EXT_BLEND_OPERATION_ADVANCED_SPEC_VERSION
                                                          , pattern EXT_BLEND_OPERATION_ADVANCED_SPEC_VERSION
                                                          , EXT_BLEND_OPERATION_ADVANCED_EXTENSION_NAME
                                                          , pattern EXT_BLEND_OPERATION_ADVANCED_EXTENSION_NAME
                                                          ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showsPrec)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Data.Int (Int32)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Word (Word32)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_ADVANCED_STATE_CREATE_INFO_EXT))
-- | VkPhysicalDeviceBlendOperationAdvancedFeaturesEXT - Structure describing
-- advanced blending features that can be supported by an implementation
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceBlendOperationAdvancedFeaturesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceBlendOperationAdvancedFeaturesEXT' /can/ also
-- be used in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo'
-- to selectively enable these features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_blend_operation_advanced VK_EXT_blend_operation_advanced>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceBlendOperationAdvancedFeaturesEXT = PhysicalDeviceBlendOperationAdvancedFeaturesEXT
  { -- | #features-advancedBlendCoherentOperations#
    -- @advancedBlendCoherentOperations@ specifies whether blending using
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blend-advanced advanced blend operations>
    -- is guaranteed to execute atomically and in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing-primitive-order primitive order>.
    -- If this is 'Vulkan.Core10.FundamentalTypes.TRUE',
    -- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT'
    -- is treated the same as
    -- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_COLOR_ATTACHMENT_READ_BIT',
    -- and advanced blending needs no additional synchronization over basic
    -- blending. If this is 'Vulkan.Core10.FundamentalTypes.FALSE', then memory
    -- dependencies are required to guarantee order between two advanced
    -- blending operations that occur on the same sample.
    PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Bool
advancedBlendCoherentOperations :: Bool }
  deriving (Typeable, PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Bool
(PhysicalDeviceBlendOperationAdvancedFeaturesEXT
 -> PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Bool)
-> (PhysicalDeviceBlendOperationAdvancedFeaturesEXT
    -> PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Bool)
-> Eq PhysicalDeviceBlendOperationAdvancedFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Bool
$c/= :: PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Bool
== :: PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Bool
$c== :: PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceBlendOperationAdvancedFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceBlendOperationAdvancedFeaturesEXT

instance ToCStruct PhysicalDeviceBlendOperationAdvancedFeaturesEXT where
  withCStruct :: PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> (Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceBlendOperationAdvancedFeaturesEXT
x Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p -> Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p PhysicalDeviceBlendOperationAdvancedFeaturesEXT
x (Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> IO b
f Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p PhysicalDeviceBlendOperationAdvancedFeaturesEXT{Bool
advancedBlendCoherentOperations :: Bool
$sel:advancedBlendCoherentOperations:PhysicalDeviceBlendOperationAdvancedFeaturesEXT :: PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
advancedBlendCoherentOperations))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceBlendOperationAdvancedFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> IO PhysicalDeviceBlendOperationAdvancedFeaturesEXT
peekCStruct Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p = do
    Bool32
advancedBlendCoherentOperations <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> IO PhysicalDeviceBlendOperationAdvancedFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceBlendOperationAdvancedFeaturesEXT
 -> IO PhysicalDeviceBlendOperationAdvancedFeaturesEXT)
-> PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> IO PhysicalDeviceBlendOperationAdvancedFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceBlendOperationAdvancedFeaturesEXT
PhysicalDeviceBlendOperationAdvancedFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
advancedBlendCoherentOperations)

instance Storable PhysicalDeviceBlendOperationAdvancedFeaturesEXT where
  sizeOf :: PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Int
sizeOf ~PhysicalDeviceBlendOperationAdvancedFeaturesEXT
_ = Int
24
  alignment :: PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> Int
alignment ~PhysicalDeviceBlendOperationAdvancedFeaturesEXT
_ = Int
8
  peek :: Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> IO PhysicalDeviceBlendOperationAdvancedFeaturesEXT
peek = Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> IO PhysicalDeviceBlendOperationAdvancedFeaturesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> PhysicalDeviceBlendOperationAdvancedFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
poked = Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> PhysicalDeviceBlendOperationAdvancedFeaturesEXT
-> IO ()
-> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
ptr PhysicalDeviceBlendOperationAdvancedFeaturesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceBlendOperationAdvancedFeaturesEXT where
  zero :: PhysicalDeviceBlendOperationAdvancedFeaturesEXT
zero = Bool -> PhysicalDeviceBlendOperationAdvancedFeaturesEXT
PhysicalDeviceBlendOperationAdvancedFeaturesEXT
           Bool
forall a. Zero a => a
zero


-- | VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT - Structure
-- describing advanced blending limits that can be supported by an
-- implementation
--
-- = Description
--
-- If the 'PhysicalDeviceBlendOperationAdvancedPropertiesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_blend_operation_advanced VK_EXT_blend_operation_advanced>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceBlendOperationAdvancedPropertiesEXT = PhysicalDeviceBlendOperationAdvancedPropertiesEXT
  { -- | #limits-advancedBlendMaxColorAttachments#
    -- @advancedBlendMaxColorAttachments@ is one greater than the highest color
    -- attachment index that /can/ be used in a subpass, for a pipeline that
    -- uses an
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blend-advanced advanced blend operation>.
    PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Word32
advancedBlendMaxColorAttachments :: Word32
  , -- | #limits-advancedBlendIndependentBlend# @advancedBlendIndependentBlend@
    -- specifies whether advanced blend operations /can/ vary per-attachment.
    PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
advancedBlendIndependentBlend :: Bool
  , -- | #limits-advancedBlendNonPremultipliedSrcColor#
    -- @advancedBlendNonPremultipliedSrcColor@ specifies whether the source
    -- color /can/ be treated as non-premultiplied. If this is
    -- 'Vulkan.Core10.FundamentalTypes.FALSE', then
    -- 'PipelineColorBlendAdvancedStateCreateInfoEXT'::@srcPremultiplied@
    -- /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE'.
    PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
advancedBlendNonPremultipliedSrcColor :: Bool
  , -- | #limits-advancedBlendNonPremultipliedDstColor#
    -- @advancedBlendNonPremultipliedDstColor@ specifies whether the
    -- destination color /can/ be treated as non-premultiplied. If this is
    -- 'Vulkan.Core10.FundamentalTypes.FALSE', then
    -- 'PipelineColorBlendAdvancedStateCreateInfoEXT'::@dstPremultiplied@
    -- /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE'.
    PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
advancedBlendNonPremultipliedDstColor :: Bool
  , -- | #limits-advancedBlendCorrelatedOverlap# @advancedBlendCorrelatedOverlap@
    -- specifies whether the overlap mode /can/ be treated as correlated. If
    -- this is 'Vulkan.Core10.FundamentalTypes.FALSE', then
    -- 'PipelineColorBlendAdvancedStateCreateInfoEXT'::@blendOverlap@ /must/ be
    -- 'BLEND_OVERLAP_UNCORRELATED_EXT'.
    PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
advancedBlendCorrelatedOverlap :: Bool
  , -- | #limits-advancedBlendAllOperations# @advancedBlendAllOperations@
    -- specifies whether all advanced blend operation enums are supported. See
    -- the valid usage of
    -- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState'.
    PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
advancedBlendAllOperations :: Bool
  }
  deriving (Typeable, PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
(PhysicalDeviceBlendOperationAdvancedPropertiesEXT
 -> PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool)
-> (PhysicalDeviceBlendOperationAdvancedPropertiesEXT
    -> PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool)
-> Eq PhysicalDeviceBlendOperationAdvancedPropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
$c/= :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
== :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
$c== :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceBlendOperationAdvancedPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceBlendOperationAdvancedPropertiesEXT

instance ToCStruct PhysicalDeviceBlendOperationAdvancedPropertiesEXT where
  withCStruct :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> (Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceBlendOperationAdvancedPropertiesEXT
x Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p -> Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p PhysicalDeviceBlendOperationAdvancedPropertiesEXT
x (Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> IO b
f Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p PhysicalDeviceBlendOperationAdvancedPropertiesEXT{Bool
Word32
advancedBlendAllOperations :: Bool
advancedBlendCorrelatedOverlap :: Bool
advancedBlendNonPremultipliedDstColor :: Bool
advancedBlendNonPremultipliedSrcColor :: Bool
advancedBlendIndependentBlend :: Bool
advancedBlendMaxColorAttachments :: Word32
$sel:advancedBlendAllOperations:PhysicalDeviceBlendOperationAdvancedPropertiesEXT :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
$sel:advancedBlendCorrelatedOverlap:PhysicalDeviceBlendOperationAdvancedPropertiesEXT :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
$sel:advancedBlendNonPremultipliedDstColor:PhysicalDeviceBlendOperationAdvancedPropertiesEXT :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
$sel:advancedBlendNonPremultipliedSrcColor:PhysicalDeviceBlendOperationAdvancedPropertiesEXT :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
$sel:advancedBlendIndependentBlend:PhysicalDeviceBlendOperationAdvancedPropertiesEXT :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Bool
$sel:advancedBlendMaxColorAttachments:PhysicalDeviceBlendOperationAdvancedPropertiesEXT :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Word32
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
advancedBlendMaxColorAttachments)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
advancedBlendIndependentBlend))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
advancedBlendNonPremultipliedSrcColor))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
advancedBlendNonPremultipliedDstColor))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
advancedBlendCorrelatedOverlap))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
advancedBlendAllOperations))
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceBlendOperationAdvancedPropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> IO PhysicalDeviceBlendOperationAdvancedPropertiesEXT
peekCStruct Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p = do
    Word32
advancedBlendMaxColorAttachments <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Bool32
advancedBlendIndependentBlend <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    Bool32
advancedBlendNonPremultipliedSrcColor <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
    Bool32
advancedBlendNonPremultipliedDstColor <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
    Bool32
advancedBlendCorrelatedOverlap <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32))
    Bool32
advancedBlendAllOperations <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
p Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32))
    PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> IO PhysicalDeviceBlendOperationAdvancedPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceBlendOperationAdvancedPropertiesEXT
 -> IO PhysicalDeviceBlendOperationAdvancedPropertiesEXT)
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> IO PhysicalDeviceBlendOperationAdvancedPropertiesEXT
forall a b. (a -> b) -> a -> b
$ Word32
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT
PhysicalDeviceBlendOperationAdvancedPropertiesEXT
             Word32
advancedBlendMaxColorAttachments (Bool32 -> Bool
bool32ToBool Bool32
advancedBlendIndependentBlend) (Bool32 -> Bool
bool32ToBool Bool32
advancedBlendNonPremultipliedSrcColor) (Bool32 -> Bool
bool32ToBool Bool32
advancedBlendNonPremultipliedDstColor) (Bool32 -> Bool
bool32ToBool Bool32
advancedBlendCorrelatedOverlap) (Bool32 -> Bool
bool32ToBool Bool32
advancedBlendAllOperations)

instance Storable PhysicalDeviceBlendOperationAdvancedPropertiesEXT where
  sizeOf :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Int
sizeOf ~PhysicalDeviceBlendOperationAdvancedPropertiesEXT
_ = Int
40
  alignment :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> Int
alignment ~PhysicalDeviceBlendOperationAdvancedPropertiesEXT
_ = Int
8
  peek :: Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> IO PhysicalDeviceBlendOperationAdvancedPropertiesEXT
peek = Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> IO PhysicalDeviceBlendOperationAdvancedPropertiesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT -> IO ()
poke Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
poked = Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT
-> IO ()
-> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
ptr PhysicalDeviceBlendOperationAdvancedPropertiesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceBlendOperationAdvancedPropertiesEXT where
  zero :: PhysicalDeviceBlendOperationAdvancedPropertiesEXT
zero = Word32
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceBlendOperationAdvancedPropertiesEXT
PhysicalDeviceBlendOperationAdvancedPropertiesEXT
           Word32
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkPipelineColorBlendAdvancedStateCreateInfoEXT - Structure specifying
-- parameters that affect advanced blend operations
--
-- = Description
--
-- If this structure is not present, @srcPremultiplied@ and
-- @dstPremultiplied@ are both considered to be
-- 'Vulkan.Core10.FundamentalTypes.TRUE', and @blendOverlap@ is considered
-- to be 'BLEND_OVERLAP_UNCORRELATED_EXT'.
--
-- == Valid Usage
--
-- -   #VUID-VkPipelineColorBlendAdvancedStateCreateInfoEXT-srcPremultiplied-01424#
--     If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-advancedBlendNonPremultipliedSrcColor non-premultiplied source color>
--     property is not supported, @srcPremultiplied@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   #VUID-VkPipelineColorBlendAdvancedStateCreateInfoEXT-dstPremultiplied-01425#
--     If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-advancedBlendNonPremultipliedDstColor non-premultiplied destination color>
--     property is not supported, @dstPremultiplied@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   #VUID-VkPipelineColorBlendAdvancedStateCreateInfoEXT-blendOverlap-01426#
--     If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-advancedBlendCorrelatedOverlap correlated overlap>
--     property is not supported, @blendOverlap@ /must/ be
--     'BLEND_OVERLAP_UNCORRELATED_EXT'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkPipelineColorBlendAdvancedStateCreateInfoEXT-sType-sType#
--     @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_ADVANCED_STATE_CREATE_INFO_EXT'
--
-- -   #VUID-VkPipelineColorBlendAdvancedStateCreateInfoEXT-blendOverlap-parameter#
--     @blendOverlap@ /must/ be a valid 'BlendOverlapEXT' value
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_blend_operation_advanced VK_EXT_blend_operation_advanced>,
-- 'BlendOverlapEXT', 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineColorBlendAdvancedStateCreateInfoEXT = PipelineColorBlendAdvancedStateCreateInfoEXT
  { -- | @srcPremultiplied@ specifies whether the source color of the blend
    -- operation is treated as premultiplied.
    PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool
srcPremultiplied :: Bool
  , -- | @dstPremultiplied@ specifies whether the destination color of the blend
    -- operation is treated as premultiplied.
    PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool
dstPremultiplied :: Bool
  , -- | @blendOverlap@ is a 'BlendOverlapEXT' value specifying how the source
    -- and destination sample’s coverage is correlated.
    PipelineColorBlendAdvancedStateCreateInfoEXT -> BlendOverlapEXT
blendOverlap :: BlendOverlapEXT
  }
  deriving (Typeable, PipelineColorBlendAdvancedStateCreateInfoEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool
(PipelineColorBlendAdvancedStateCreateInfoEXT
 -> PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool)
-> (PipelineColorBlendAdvancedStateCreateInfoEXT
    -> PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool)
-> Eq PipelineColorBlendAdvancedStateCreateInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineColorBlendAdvancedStateCreateInfoEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool
$c/= :: PipelineColorBlendAdvancedStateCreateInfoEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool
== :: PipelineColorBlendAdvancedStateCreateInfoEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool
$c== :: PipelineColorBlendAdvancedStateCreateInfoEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineColorBlendAdvancedStateCreateInfoEXT)
#endif
deriving instance Show PipelineColorBlendAdvancedStateCreateInfoEXT

instance ToCStruct PipelineColorBlendAdvancedStateCreateInfoEXT where
  withCStruct :: PipelineColorBlendAdvancedStateCreateInfoEXT
-> (Ptr PipelineColorBlendAdvancedStateCreateInfoEXT -> IO b)
-> IO b
withCStruct PipelineColorBlendAdvancedStateCreateInfoEXT
x Ptr PipelineColorBlendAdvancedStateCreateInfoEXT -> IO b
f = Int
-> (Ptr PipelineColorBlendAdvancedStateCreateInfoEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT -> IO b)
 -> IO b)
-> (Ptr PipelineColorBlendAdvancedStateCreateInfoEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p -> Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p PipelineColorBlendAdvancedStateCreateInfoEXT
x (Ptr PipelineColorBlendAdvancedStateCreateInfoEXT -> IO b
f Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p)
  pokeCStruct :: Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p PipelineColorBlendAdvancedStateCreateInfoEXT{Bool
BlendOverlapEXT
blendOverlap :: BlendOverlapEXT
dstPremultiplied :: Bool
srcPremultiplied :: Bool
$sel:blendOverlap:PipelineColorBlendAdvancedStateCreateInfoEXT :: PipelineColorBlendAdvancedStateCreateInfoEXT -> BlendOverlapEXT
$sel:dstPremultiplied:PipelineColorBlendAdvancedStateCreateInfoEXT :: PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool
$sel:srcPremultiplied:PipelineColorBlendAdvancedStateCreateInfoEXT :: PipelineColorBlendAdvancedStateCreateInfoEXT -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_ADVANCED_STATE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
srcPremultiplied))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
dstPremultiplied))
    Ptr BlendOverlapEXT -> BlendOverlapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr BlendOverlapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BlendOverlapEXT)) (BlendOverlapEXT
blendOverlap)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PipelineColorBlendAdvancedStateCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_ADVANCED_STATE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr BlendOverlapEXT -> BlendOverlapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr BlendOverlapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BlendOverlapEXT)) (BlendOverlapEXT
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PipelineColorBlendAdvancedStateCreateInfoEXT where
  peekCStruct :: Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> IO PipelineColorBlendAdvancedStateCreateInfoEXT
peekCStruct Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p = do
    Bool32
srcPremultiplied <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    Bool32
dstPremultiplied <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    BlendOverlapEXT
blendOverlap <- Ptr BlendOverlapEXT -> IO BlendOverlapEXT
forall a. Storable a => Ptr a -> IO a
peek @BlendOverlapEXT ((Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
p Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> Int -> Ptr BlendOverlapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BlendOverlapEXT))
    PipelineColorBlendAdvancedStateCreateInfoEXT
-> IO PipelineColorBlendAdvancedStateCreateInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineColorBlendAdvancedStateCreateInfoEXT
 -> IO PipelineColorBlendAdvancedStateCreateInfoEXT)
-> PipelineColorBlendAdvancedStateCreateInfoEXT
-> IO PipelineColorBlendAdvancedStateCreateInfoEXT
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> BlendOverlapEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT
PipelineColorBlendAdvancedStateCreateInfoEXT
             (Bool32 -> Bool
bool32ToBool Bool32
srcPremultiplied) (Bool32 -> Bool
bool32ToBool Bool32
dstPremultiplied) BlendOverlapEXT
blendOverlap

instance Storable PipelineColorBlendAdvancedStateCreateInfoEXT where
  sizeOf :: PipelineColorBlendAdvancedStateCreateInfoEXT -> Int
sizeOf ~PipelineColorBlendAdvancedStateCreateInfoEXT
_ = Int
32
  alignment :: PipelineColorBlendAdvancedStateCreateInfoEXT -> Int
alignment ~PipelineColorBlendAdvancedStateCreateInfoEXT
_ = Int
8
  peek :: Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> IO PipelineColorBlendAdvancedStateCreateInfoEXT
peek = Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> IO PipelineColorBlendAdvancedStateCreateInfoEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT -> IO ()
poke Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
ptr PipelineColorBlendAdvancedStateCreateInfoEXT
poked = Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineColorBlendAdvancedStateCreateInfoEXT
ptr PipelineColorBlendAdvancedStateCreateInfoEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PipelineColorBlendAdvancedStateCreateInfoEXT where
  zero :: PipelineColorBlendAdvancedStateCreateInfoEXT
zero = Bool
-> Bool
-> BlendOverlapEXT
-> PipelineColorBlendAdvancedStateCreateInfoEXT
PipelineColorBlendAdvancedStateCreateInfoEXT
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           BlendOverlapEXT
forall a. Zero a => a
zero


-- | VkBlendOverlapEXT - Enumerant specifying the blend overlap parameter
--
-- = Description
--
-- \'
--
-- +----------------------------------+--------------------------------------------------------------------------------------+
-- | Overlap Mode                     | Weighting Equations                                                                  |
-- +==================================+======================================================================================+
-- | 'BLEND_OVERLAP_UNCORRELATED_EXT' | \[                                              \begin{aligned}                      |
-- |                                  |                                                 p_0(A_s,A_d) & = A_sA_d \\           |
-- |                                  |                                                 p_1(A_s,A_d) & = A_s(1-A_d) \\       |
-- |                                  |                                                 p_2(A_s,A_d) & = A_d(1-A_s) \\       |
-- |                                  |                                               \end{aligned}\]                        |
-- +----------------------------------+--------------------------------------------------------------------------------------+
-- | 'BLEND_OVERLAP_CONJOINT_EXT'     | \[                                              \begin{aligned}                      |
-- |                                  |                                                 p_0(A_s,A_d) & = min(A_s,A_d) \\     |
-- |                                  |                                                 p_1(A_s,A_d) & = max(A_s-A_d,0) \\   |
-- |                                  |                                                 p_2(A_s,A_d) & = max(A_d-A_s,0) \\   |
-- |                                  |                                               \end{aligned}\]                        |
-- +----------------------------------+--------------------------------------------------------------------------------------+
-- | 'BLEND_OVERLAP_DISJOINT_EXT'     | \[                                              \begin{aligned}                      |
-- |                                  |                                                 p_0(A_s,A_d) & = max(A_s+A_d-1,0) \\ |
-- |                                  |                                                 p_1(A_s,A_d) & = min(A_s,1-A_d) \\   |
-- |                                  |                                                 p_2(A_s,A_d) & = min(A_d,1-A_s) \\   |
-- |                                  |                                               \end{aligned}\]                        |
-- +----------------------------------+--------------------------------------------------------------------------------------+
--
-- Advanced Blend Overlap Modes
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_blend_operation_advanced VK_EXT_blend_operation_advanced>,
-- 'PipelineColorBlendAdvancedStateCreateInfoEXT'
newtype BlendOverlapEXT = BlendOverlapEXT Int32
  deriving newtype (BlendOverlapEXT -> BlendOverlapEXT -> Bool
(BlendOverlapEXT -> BlendOverlapEXT -> Bool)
-> (BlendOverlapEXT -> BlendOverlapEXT -> Bool)
-> Eq BlendOverlapEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
$c/= :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
== :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
$c== :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
Eq, Eq BlendOverlapEXT
Eq BlendOverlapEXT
-> (BlendOverlapEXT -> BlendOverlapEXT -> Ordering)
-> (BlendOverlapEXT -> BlendOverlapEXT -> Bool)
-> (BlendOverlapEXT -> BlendOverlapEXT -> Bool)
-> (BlendOverlapEXT -> BlendOverlapEXT -> Bool)
-> (BlendOverlapEXT -> BlendOverlapEXT -> Bool)
-> (BlendOverlapEXT -> BlendOverlapEXT -> BlendOverlapEXT)
-> (BlendOverlapEXT -> BlendOverlapEXT -> BlendOverlapEXT)
-> Ord BlendOverlapEXT
BlendOverlapEXT -> BlendOverlapEXT -> Bool
BlendOverlapEXT -> BlendOverlapEXT -> Ordering
BlendOverlapEXT -> BlendOverlapEXT -> BlendOverlapEXT
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BlendOverlapEXT -> BlendOverlapEXT -> BlendOverlapEXT
$cmin :: BlendOverlapEXT -> BlendOverlapEXT -> BlendOverlapEXT
max :: BlendOverlapEXT -> BlendOverlapEXT -> BlendOverlapEXT
$cmax :: BlendOverlapEXT -> BlendOverlapEXT -> BlendOverlapEXT
>= :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
$c>= :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
> :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
$c> :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
<= :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
$c<= :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
< :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
$c< :: BlendOverlapEXT -> BlendOverlapEXT -> Bool
compare :: BlendOverlapEXT -> BlendOverlapEXT -> Ordering
$ccompare :: BlendOverlapEXT -> BlendOverlapEXT -> Ordering
$cp1Ord :: Eq BlendOverlapEXT
Ord, Ptr b -> Int -> IO BlendOverlapEXT
Ptr b -> Int -> BlendOverlapEXT -> IO ()
Ptr BlendOverlapEXT -> IO BlendOverlapEXT
Ptr BlendOverlapEXT -> Int -> IO BlendOverlapEXT
Ptr BlendOverlapEXT -> Int -> BlendOverlapEXT -> IO ()
Ptr BlendOverlapEXT -> BlendOverlapEXT -> IO ()
BlendOverlapEXT -> Int
(BlendOverlapEXT -> Int)
-> (BlendOverlapEXT -> Int)
-> (Ptr BlendOverlapEXT -> Int -> IO BlendOverlapEXT)
-> (Ptr BlendOverlapEXT -> Int -> BlendOverlapEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO BlendOverlapEXT)
-> (forall b. Ptr b -> Int -> BlendOverlapEXT -> IO ())
-> (Ptr BlendOverlapEXT -> IO BlendOverlapEXT)
-> (Ptr BlendOverlapEXT -> BlendOverlapEXT -> IO ())
-> Storable BlendOverlapEXT
forall b. Ptr b -> Int -> IO BlendOverlapEXT
forall b. Ptr b -> Int -> BlendOverlapEXT -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr BlendOverlapEXT -> BlendOverlapEXT -> IO ()
$cpoke :: Ptr BlendOverlapEXT -> BlendOverlapEXT -> IO ()
peek :: Ptr BlendOverlapEXT -> IO BlendOverlapEXT
$cpeek :: Ptr BlendOverlapEXT -> IO BlendOverlapEXT
pokeByteOff :: Ptr b -> Int -> BlendOverlapEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> BlendOverlapEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO BlendOverlapEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO BlendOverlapEXT
pokeElemOff :: Ptr BlendOverlapEXT -> Int -> BlendOverlapEXT -> IO ()
$cpokeElemOff :: Ptr BlendOverlapEXT -> Int -> BlendOverlapEXT -> IO ()
peekElemOff :: Ptr BlendOverlapEXT -> Int -> IO BlendOverlapEXT
$cpeekElemOff :: Ptr BlendOverlapEXT -> Int -> IO BlendOverlapEXT
alignment :: BlendOverlapEXT -> Int
$calignment :: BlendOverlapEXT -> Int
sizeOf :: BlendOverlapEXT -> Int
$csizeOf :: BlendOverlapEXT -> Int
Storable, BlendOverlapEXT
BlendOverlapEXT -> Zero BlendOverlapEXT
forall a. a -> Zero a
zero :: BlendOverlapEXT
$czero :: BlendOverlapEXT
Zero)

-- | 'BLEND_OVERLAP_UNCORRELATED_EXT' specifies that there is no correlation
-- between the source and destination coverage.
pattern $bBLEND_OVERLAP_UNCORRELATED_EXT :: BlendOverlapEXT
$mBLEND_OVERLAP_UNCORRELATED_EXT :: forall r. BlendOverlapEXT -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OVERLAP_UNCORRELATED_EXT = BlendOverlapEXT 0
-- | 'BLEND_OVERLAP_DISJOINT_EXT' specifies that the source and destination
-- coverage are considered to have minimal overlap.
pattern $bBLEND_OVERLAP_DISJOINT_EXT :: BlendOverlapEXT
$mBLEND_OVERLAP_DISJOINT_EXT :: forall r. BlendOverlapEXT -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OVERLAP_DISJOINT_EXT     = BlendOverlapEXT 1
-- | 'BLEND_OVERLAP_CONJOINT_EXT' specifies that the source and destination
-- coverage are considered to have maximal overlap.
pattern $bBLEND_OVERLAP_CONJOINT_EXT :: BlendOverlapEXT
$mBLEND_OVERLAP_CONJOINT_EXT :: forall r. BlendOverlapEXT -> (Void# -> r) -> (Void# -> r) -> r
BLEND_OVERLAP_CONJOINT_EXT     = BlendOverlapEXT 2
{-# complete BLEND_OVERLAP_UNCORRELATED_EXT,
             BLEND_OVERLAP_DISJOINT_EXT,
             BLEND_OVERLAP_CONJOINT_EXT :: BlendOverlapEXT #-}

conNameBlendOverlapEXT :: String
conNameBlendOverlapEXT :: String
conNameBlendOverlapEXT = String
"BlendOverlapEXT"

enumPrefixBlendOverlapEXT :: String
enumPrefixBlendOverlapEXT :: String
enumPrefixBlendOverlapEXT = String
"BLEND_OVERLAP_"

showTableBlendOverlapEXT :: [(BlendOverlapEXT, String)]
showTableBlendOverlapEXT :: [(BlendOverlapEXT, String)]
showTableBlendOverlapEXT =
  [ (BlendOverlapEXT
BLEND_OVERLAP_UNCORRELATED_EXT, String
"UNCORRELATED_EXT")
  , (BlendOverlapEXT
BLEND_OVERLAP_DISJOINT_EXT    , String
"DISJOINT_EXT")
  , (BlendOverlapEXT
BLEND_OVERLAP_CONJOINT_EXT    , String
"CONJOINT_EXT")
  ]

instance Show BlendOverlapEXT where
  showsPrec :: Int -> BlendOverlapEXT -> ShowS
showsPrec = String
-> [(BlendOverlapEXT, String)]
-> String
-> (BlendOverlapEXT -> Int32)
-> (Int32 -> ShowS)
-> Int
-> BlendOverlapEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixBlendOverlapEXT
                            [(BlendOverlapEXT, String)]
showTableBlendOverlapEXT
                            String
conNameBlendOverlapEXT
                            (\(BlendOverlapEXT Int32
x) -> Int32
x)
                            (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read BlendOverlapEXT where
  readPrec :: ReadPrec BlendOverlapEXT
readPrec = String
-> [(BlendOverlapEXT, String)]
-> String
-> (Int32 -> BlendOverlapEXT)
-> ReadPrec BlendOverlapEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixBlendOverlapEXT [(BlendOverlapEXT, String)]
showTableBlendOverlapEXT String
conNameBlendOverlapEXT Int32 -> BlendOverlapEXT
BlendOverlapEXT


type EXT_BLEND_OPERATION_ADVANCED_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_EXT_BLEND_OPERATION_ADVANCED_SPEC_VERSION"
pattern EXT_BLEND_OPERATION_ADVANCED_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_BLEND_OPERATION_ADVANCED_SPEC_VERSION :: a
$mEXT_BLEND_OPERATION_ADVANCED_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_BLEND_OPERATION_ADVANCED_SPEC_VERSION = 2


type EXT_BLEND_OPERATION_ADVANCED_EXTENSION_NAME = "VK_EXT_blend_operation_advanced"

-- No documentation found for TopLevel "VK_EXT_BLEND_OPERATION_ADVANCED_EXTENSION_NAME"
pattern EXT_BLEND_OPERATION_ADVANCED_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_BLEND_OPERATION_ADVANCED_EXTENSION_NAME :: a
$mEXT_BLEND_OPERATION_ADVANCED_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_BLEND_OPERATION_ADVANCED_EXTENSION_NAME = "VK_EXT_blend_operation_advanced"