{-# language CPP #-}
-- | = Name
--
-- VK_EXT_color_write_enable - device extension
--
-- == VK_EXT_color_write_enable
--
-- [__Name String__]
--     @VK_EXT_color_write_enable@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     382
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_KHR_get_physical_device_properties2@ to be enabled
--         for any device-level functionality
--
-- [__Contact__]
--
--     -   Sharif Elcott
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_color_write_enable] @selcott%0A*Here describe the issue or question you have about the VK_EXT_color_write_enable extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2020-02-25
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Sharif Elcott, Google
--
--     -   Tobias Hector, AMD
--
--     -   Piers Daniell, NVIDIA
--
-- == Description
--
-- This extension allows for selectively enabling and disabling writes to
-- output color attachments via a pipeline dynamic state.
--
-- The intended use cases for this new state are mostly identical to those
-- of colorWriteMask, such as selectively disabling writes to avoid
-- feedback loops between subpasses or bandwidth savings for unused
-- outputs. By making the state dynamic, one additional benefit is the
-- ability to reduce pipeline counts and pipeline switching via shaders
-- that write a superset of the desired data of which subsets are selected
-- dynamically. The reason for a new state, colorWriteEnable, rather than
-- making colorWriteMask dynamic is that, on many implementations, the more
-- flexible per-component semantics of the colorWriteMask state cannot be
-- made dynamic in a performant manner.
--
-- == New Commands
--
-- -   'cmdSetColorWriteEnableEXT'
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceColorWriteEnableFeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo':
--
--     -   'PipelineColorWriteCreateInfoEXT'
--
-- == New Enum Constants
--
-- -   'EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME'
--
-- -   'EXT_COLOR_WRITE_ENABLE_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.DynamicState.DynamicState':
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_COLOR_WRITE_ENABLE_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_COLOR_WRITE_CREATE_INFO_EXT'
--
-- == Version History
--
-- -   Revision 1, 2020-01-25 (Sharif Elcott)
--
--     -   Internal revisions
--
-- == See Also
--
-- 'PhysicalDeviceColorWriteEnableFeaturesEXT',
-- 'PipelineColorWriteCreateInfoEXT', 'cmdSetColorWriteEnableEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_color_write_enable 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_color_write_enable  ( cmdSetColorWriteEnableEXT
                                                    , PhysicalDeviceColorWriteEnableFeaturesEXT(..)
                                                    , PipelineColorWriteCreateInfoEXT(..)
                                                    , EXT_COLOR_WRITE_ENABLE_SPEC_VERSION
                                                    , pattern EXT_COLOR_WRITE_ENABLE_SPEC_VERSION
                                                    , EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME
                                                    , pattern EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME
                                                    ) where

import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
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 GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (Bool32(..))
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetColorWriteEnableEXT))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_COLOR_WRITE_ENABLE_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_COLOR_WRITE_CREATE_INFO_EXT))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdSetColorWriteEnableEXT
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr Bool32 -> IO ()

-- | vkCmdSetColorWriteEnableEXT - Enable or disable writes to a color
-- attachment dynamically for a command buffer
--
-- = Description
--
-- This command sets the color write enables for subsequent drawing
-- commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'PipelineColorWriteCreateInfoEXT'::@pColorWriteEnables@ values used to
-- create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetColorWriteEnableEXT-None-04803# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetColorWriteEnableEXT-attachmentCount-06656#
--     @attachmentCount@ /must/ be less than or equal to the
--     @maxColorAttachments@ member of
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetColorWriteEnableEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetColorWriteEnableEXT-pColorWriteEnables-parameter#
--     @pColorWriteEnables@ /must/ be a valid pointer to an array of
--     @attachmentCount@ 'Vulkan.Core10.FundamentalTypes.Bool32' values
--
-- -   #VUID-vkCmdSetColorWriteEnableEXT-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdSetColorWriteEnableEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetColorWriteEnableEXT-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- -   #VUID-vkCmdSetColorWriteEnableEXT-attachmentCount-arraylength#
--     @attachmentCount@ /must/ be greater than @0@
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Outside                                                                                                                     | Graphics                                                                                                              | State                                                                                                                                  |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             |                                                                                                                       |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_color_write_enable VK_EXT_color_write_enable>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetColorWriteEnableEXT :: forall io
                           . (MonadIO io)
                          => -- | @commandBuffer@ is the command buffer into which the command will be
                             -- recorded.
                             CommandBuffer
                          -> -- | @pColorWriteEnables@ is a pointer to an array of per target attachment
                             -- boolean values specifying whether color writes are enabled for the given
                             -- attachment.
                             ("colorWriteEnables" ::: Vector Bool)
                          -> io ()
cmdSetColorWriteEnableEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> ("colorWriteEnables" ::: Vector Bool) -> io ()
cmdSetColorWriteEnableEXT CommandBuffer
commandBuffer
                            "colorWriteEnables" ::: Vector Bool
colorWriteEnables = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetColorWriteEnableEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("attachmentCount" ::: Word32)
   -> ("pColorWriteEnables" ::: Ptr Bool32)
   -> IO ())
vkCmdSetColorWriteEnableEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("attachmentCount" ::: Word32)
      -> ("pColorWriteEnables" ::: Ptr Bool32)
      -> IO ())
pVkCmdSetColorWriteEnableEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("attachmentCount" ::: Word32)
   -> ("pColorWriteEnables" ::: Ptr Bool32)
   -> IO ())
vkCmdSetColorWriteEnableEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("attachmentCount" ::: Word32)
   -> ("pColorWriteEnables" ::: Ptr Bool32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("attachmentCount" ::: Word32)
      -> ("pColorWriteEnables" ::: Ptr Bool32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("attachmentCount" ::: Word32)
   -> ("pColorWriteEnables" ::: Ptr Bool32)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCmdSetColorWriteEnableEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetColorWriteEnableEXT' :: Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ()
vkCmdSetColorWriteEnableEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("attachmentCount" ::: Word32)
   -> ("pColorWriteEnables" ::: Ptr Bool32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ()
mkVkCmdSetColorWriteEnableEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("attachmentCount" ::: Word32)
   -> ("pColorWriteEnables" ::: Ptr Bool32)
   -> IO ())
vkCmdSetColorWriteEnableEXTPtr
  "pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables <- ((("pColorWriteEnables" ::: Ptr Bool32) -> IO ()) -> IO ())
-> ContT () IO ("pColorWriteEnables" ::: Ptr Bool32)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pColorWriteEnables" ::: Ptr Bool32) -> IO ()) -> IO ())
 -> ContT () IO ("pColorWriteEnables" ::: Ptr Bool32))
-> ((("pColorWriteEnables" ::: Ptr Bool32) -> IO ()) -> IO ())
-> ContT () IO ("pColorWriteEnables" ::: Ptr Bool32)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Bool32 ((("colorWriteEnables" ::: Vector Bool) -> Int
forall a. Vector a -> Int
Data.Vector.length ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Bool -> IO ())
-> ("colorWriteEnables" ::: Vector Bool) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Bool
e -> ("pColorWriteEnables" ::: Ptr Bool32) -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables ("pColorWriteEnables" ::: Ptr Bool32)
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32) (Bool -> Bool32
boolToBool32 (Bool
e))) ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetColorWriteEnableEXT" (Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ()
vkCmdSetColorWriteEnableEXT'
                                                           (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                           ((Int -> "attachmentCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("colorWriteEnables" ::: Vector Bool) -> Int
forall a. Vector a -> Int
Data.Vector.length (("colorWriteEnables" ::: Vector Bool) -> Int)
-> ("colorWriteEnables" ::: Vector Bool) -> Int
forall a b. (a -> b) -> a -> b
$ ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) :: Word32))
                                                           ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables))
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkPhysicalDeviceColorWriteEnableFeaturesEXT - Structure describing
-- whether writes to color attachments can be enabled and disabled
-- dynamically
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceColorWriteEnableFeaturesEXT' 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. 'PhysicalDeviceColorWriteEnableFeaturesEXT' /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_color_write_enable VK_EXT_color_write_enable>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceColorWriteEnableFeaturesEXT = PhysicalDeviceColorWriteEnableFeaturesEXT
  { -- | #features-colorWriteEnable# @colorWriteEnable@ indicates that the
    -- implementation supports the dynamic state
    -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_ENABLE_EXT'.
    PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
colorWriteEnable :: Bool }
  deriving (Typeable, PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
(PhysicalDeviceColorWriteEnableFeaturesEXT
 -> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool)
-> (PhysicalDeviceColorWriteEnableFeaturesEXT
    -> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool)
-> Eq PhysicalDeviceColorWriteEnableFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
$c/= :: PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
== :: PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
$c== :: PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceColorWriteEnableFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceColorWriteEnableFeaturesEXT

instance ToCStruct PhysicalDeviceColorWriteEnableFeaturesEXT where
  withCStruct :: forall b.
PhysicalDeviceColorWriteEnableFeaturesEXT
-> (Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceColorWriteEnableFeaturesEXT
x Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p -> Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p PhysicalDeviceColorWriteEnableFeaturesEXT
x (Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b
f Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p PhysicalDeviceColorWriteEnableFeaturesEXT{Bool
colorWriteEnable :: Bool
$sel:colorWriteEnable:PhysicalDeviceColorWriteEnableFeaturesEXT :: PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COLOR_WRITE_ENABLE_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pColorWriteEnables" ::: Ptr Bool32) -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
colorWriteEnable))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COLOR_WRITE_ENABLE_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pColorWriteEnables" ::: Ptr Bool32) -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> "pColorWriteEnables" ::: 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 PhysicalDeviceColorWriteEnableFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> IO PhysicalDeviceColorWriteEnableFeaturesEXT
peekCStruct Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p = do
    Bool32
colorWriteEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    PhysicalDeviceColorWriteEnableFeaturesEXT
-> IO PhysicalDeviceColorWriteEnableFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceColorWriteEnableFeaturesEXT
 -> IO PhysicalDeviceColorWriteEnableFeaturesEXT)
-> PhysicalDeviceColorWriteEnableFeaturesEXT
-> IO PhysicalDeviceColorWriteEnableFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceColorWriteEnableFeaturesEXT
PhysicalDeviceColorWriteEnableFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
colorWriteEnable)

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

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


-- | VkPipelineColorWriteCreateInfoEXT - Structure specifying color write
-- state of a newly created pipeline
--
-- = Description
--
-- When this structure is included in the @pNext@ chain of
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo', it defines
-- per-attachment color write state. If this structure is not included in
-- the @pNext@ chain, it is equivalent to specifying this structure with
-- @attachmentCount@ equal to the @attachmentCount@ member of
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo', and
-- @pColorWriteEnables@ pointing to an array of as many
-- 'Vulkan.Core10.FundamentalTypes.TRUE' values.
--
-- If the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable>
-- feature is not enabled on the device, all
-- 'Vulkan.Core10.FundamentalTypes.Bool32' elements in the
-- @pColorWriteEnables@ array /must/ be
-- 'Vulkan.Core10.FundamentalTypes.TRUE'.
--
-- Color Write Enable interacts with the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#framebuffer-color-write-mask Color Write Mask>
-- as follows:
--
-- -   If @colorWriteEnable@ is 'Vulkan.Core10.FundamentalTypes.TRUE',
--     writes to the attachment are determined by the @colorWriteMask@.
--
-- -   If @colorWriteEnable@ is 'Vulkan.Core10.FundamentalTypes.FALSE', the
--     @colorWriteMask@ is ignored and writes to all components of the
--     attachment are disabled. This is equivalent to specifying a
--     @colorWriteMask@ of 0.
--
-- == Valid Usage
--
-- -   #VUID-VkPipelineColorWriteCreateInfoEXT-pAttachments-04801# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-colorWriteEnable colorWriteEnable>
--     feature is not enabled, all elements of @pColorWriteEnables@ /must/
--     be 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   #VUID-VkPipelineColorWriteCreateInfoEXT-attachmentCount-04802#
--     @attachmentCount@ /must/ be equal to the @attachmentCount@ member of
--     the 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo'
--     structure specified during pipeline creation
--
-- -   #VUID-VkPipelineColorWriteCreateInfoEXT-attachmentCount-06655#
--     @attachmentCount@ /must/ be less than or equal to the
--     @maxColorAttachments@ member of
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkPipelineColorWriteCreateInfoEXT-sType-sType# @sType@ /must/
--     be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_COLOR_WRITE_CREATE_INFO_EXT'
--
-- -   #VUID-VkPipelineColorWriteCreateInfoEXT-pColorWriteEnables-parameter#
--     If @attachmentCount@ is not @0@, @pColorWriteEnables@ /must/ be a
--     valid pointer to an array of @attachmentCount@
--     'Vulkan.Core10.FundamentalTypes.Bool32' values
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_color_write_enable VK_EXT_color_write_enable>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineColorWriteCreateInfoEXT = PipelineColorWriteCreateInfoEXT
  { -- | @pColorWriteEnables@ is a pointer to an array of per target attachment
    -- boolean values specifying whether color writes are enabled for the given
    -- attachment.
    PipelineColorWriteCreateInfoEXT
-> "colorWriteEnables" ::: Vector Bool
colorWriteEnables :: Vector Bool }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineColorWriteCreateInfoEXT)
#endif
deriving instance Show PipelineColorWriteCreateInfoEXT

instance ToCStruct PipelineColorWriteCreateInfoEXT where
  withCStruct :: forall b.
PipelineColorWriteCreateInfoEXT
-> (Ptr PipelineColorWriteCreateInfoEXT -> IO b) -> IO b
withCStruct PipelineColorWriteCreateInfoEXT
x Ptr PipelineColorWriteCreateInfoEXT -> IO b
f = Int -> (Ptr PipelineColorWriteCreateInfoEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PipelineColorWriteCreateInfoEXT -> IO b) -> IO b)
-> (Ptr PipelineColorWriteCreateInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PipelineColorWriteCreateInfoEXT
p -> Ptr PipelineColorWriteCreateInfoEXT
-> PipelineColorWriteCreateInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineColorWriteCreateInfoEXT
p PipelineColorWriteCreateInfoEXT
x (Ptr PipelineColorWriteCreateInfoEXT -> IO b
f Ptr PipelineColorWriteCreateInfoEXT
p)
  pokeCStruct :: forall b.
Ptr PipelineColorWriteCreateInfoEXT
-> PipelineColorWriteCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr PipelineColorWriteCreateInfoEXT
p PipelineColorWriteCreateInfoEXT{"colorWriteEnables" ::: Vector Bool
colorWriteEnables :: "colorWriteEnables" ::: Vector Bool
$sel:colorWriteEnables:PipelineColorWriteCreateInfoEXT :: PipelineColorWriteCreateInfoEXT
-> "colorWriteEnables" ::: Vector Bool
..} IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COLOR_WRITE_CREATE_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("attachmentCount" ::: Word32)
-> ("attachmentCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT
-> Int -> Ptr ("attachmentCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((Int -> "attachmentCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("colorWriteEnables" ::: Vector Bool) -> Int
forall a. Vector a -> Int
Data.Vector.length (("colorWriteEnables" ::: Vector Bool) -> Int)
-> ("colorWriteEnables" ::: Vector Bool) -> Int
forall a b. (a -> b) -> a -> b
$ ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) :: Word32))
    "pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables' <- ((("pColorWriteEnables" ::: Ptr Bool32) -> IO b) -> IO b)
-> ContT b IO ("pColorWriteEnables" ::: Ptr Bool32)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pColorWriteEnables" ::: Ptr Bool32) -> IO b) -> IO b)
 -> ContT b IO ("pColorWriteEnables" ::: Ptr Bool32))
-> ((("pColorWriteEnables" ::: Ptr Bool32) -> IO b) -> IO b)
-> ContT b IO ("pColorWriteEnables" ::: Ptr Bool32)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Bool32 ((("colorWriteEnables" ::: Vector Bool) -> Int
forall a. Vector a -> Int
Data.Vector.length ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Bool -> IO ())
-> ("colorWriteEnables" ::: Vector Bool) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Bool
e -> ("pColorWriteEnables" ::: Ptr Bool32) -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables' ("pColorWriteEnables" ::: Ptr Bool32)
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32) (Bool -> Bool32
boolToBool32 (Bool
e))) ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pColorWriteEnables" ::: Ptr Bool32)
-> ("pColorWriteEnables" ::: Ptr Bool32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT
-> Int -> Ptr ("pColorWriteEnables" ::: Ptr Bool32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Bool32))) ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr PipelineColorWriteCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr PipelineColorWriteCreateInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COLOR_WRITE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct PipelineColorWriteCreateInfoEXT where
  peekCStruct :: Ptr PipelineColorWriteCreateInfoEXT
-> IO PipelineColorWriteCreateInfoEXT
peekCStruct Ptr PipelineColorWriteCreateInfoEXT
p = do
    "attachmentCount" ::: Word32
attachmentCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT
-> Int -> Ptr ("attachmentCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    "pColorWriteEnables" ::: Ptr Bool32
pColorWriteEnables <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Bool32) ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT
-> Int -> Ptr ("pColorWriteEnables" ::: Ptr Bool32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Bool32)))
    "colorWriteEnables" ::: Vector Bool
pColorWriteEnables' <- Int -> (Int -> IO Bool) -> IO ("colorWriteEnables" ::: Vector Bool)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("attachmentCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "attachmentCount" ::: Word32
attachmentCount) (\Int
i -> do
      Bool32
pColorWriteEnablesElem <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pColorWriteEnables" ::: Ptr Bool32
pColorWriteEnables ("pColorWriteEnables" ::: Ptr Bool32)
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32))
      Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Bool32 -> Bool
bool32ToBool Bool32
pColorWriteEnablesElem)
    PipelineColorWriteCreateInfoEXT
-> IO PipelineColorWriteCreateInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineColorWriteCreateInfoEXT
 -> IO PipelineColorWriteCreateInfoEXT)
-> PipelineColorWriteCreateInfoEXT
-> IO PipelineColorWriteCreateInfoEXT
forall a b. (a -> b) -> a -> b
$ ("colorWriteEnables" ::: Vector Bool)
-> PipelineColorWriteCreateInfoEXT
PipelineColorWriteCreateInfoEXT
             "colorWriteEnables" ::: Vector Bool
pColorWriteEnables'

instance Zero PipelineColorWriteCreateInfoEXT where
  zero :: PipelineColorWriteCreateInfoEXT
zero = ("colorWriteEnables" ::: Vector Bool)
-> PipelineColorWriteCreateInfoEXT
PipelineColorWriteCreateInfoEXT
           "colorWriteEnables" ::: Vector Bool
forall a. Monoid a => a
mempty


type EXT_COLOR_WRITE_ENABLE_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_COLOR_WRITE_ENABLE_SPEC_VERSION"
pattern EXT_COLOR_WRITE_ENABLE_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_COLOR_WRITE_ENABLE_SPEC_VERSION :: forall a. Integral a => a
$mEXT_COLOR_WRITE_ENABLE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_COLOR_WRITE_ENABLE_SPEC_VERSION = 1


type EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME = "VK_EXT_color_write_enable"

-- No documentation found for TopLevel "VK_EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME"
pattern EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_COLOR_WRITE_ENABLE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_COLOR_WRITE_ENABLE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME = "VK_EXT_color_write_enable"