{-# language CPP #-}
-- | = Name
--
-- VK_EXT_conditional_rendering - device extension
--
-- == VK_EXT_conditional_rendering
--
-- [__Name String__]
--     @VK_EXT_conditional_rendering@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     82
--
-- [__Revision__]
--     2
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
-- [__Contact__]
--
--     -   Vikram Kushwaha
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_conditional_rendering] @vkushwaha%0A<<Here describe the issue or question you have about the VK_EXT_conditional_rendering extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2018-05-21
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Vikram Kushwaha, NVIDIA
--
--     -   Daniel Rakos, AMD
--
--     -   Jesse Hall, Google
--
--     -   Jeff Bolz, NVIDIA
--
--     -   Piers Daniell, NVIDIA
--
--     -   Stuart Smith, Imagination Technologies
--
-- == Description
--
-- This extension allows the execution of one or more rendering commands to
-- be conditional on a value in buffer memory. This may help an application
-- reduce the latency by conditionally discarding rendering commands
-- without application intervention. The conditional rendering commands are
-- limited to draws, compute dispatches and clearing attachments within a
-- conditional rendering block.
--
-- == New Commands
--
-- -   'cmdBeginConditionalRenderingEXT'
--
-- -   'cmdEndConditionalRenderingEXT'
--
-- == New Structures
--
-- -   'ConditionalRenderingBeginInfoEXT'
--
-- -   Extending
--     'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo':
--
--     -   'CommandBufferInheritanceConditionalRenderingInfoEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceConditionalRenderingFeaturesEXT'
--
-- == New Enums
--
-- -   'ConditionalRenderingFlagBitsEXT'
--
-- == New Bitmasks
--
-- -   'ConditionalRenderingFlagsEXT'
--
-- == New Enum Constants
--
-- -   'EXT_CONDITIONAL_RENDERING_EXTENSION_NAME'
--
-- -   'EXT_CONDITIONAL_RENDERING_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits':
--
--     -   'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_CONDITIONAL_RENDERING_READ_BIT_EXT'
--
-- -   Extending
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BufferUsageFlagBits':
--
--     -   'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_CONDITIONAL_RENDERING_BIT_EXT'
--
-- -   Extending
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits':
--
--     -   'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_CONDITIONAL_RENDERING_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT'
--
-- == Issues
--
-- 1) Should conditional rendering affect copy and blit commands?
--
-- __RESOLVED__: Conditional rendering should not affect copies and blits.
--
-- 2) Should secondary command buffers be allowed to execute while
-- conditional rendering is active in the primary command buffer?
--
-- __RESOLVED__: The rendering commands in secondary command buffer will be
-- affected by an active conditional rendering in primary command buffer if
-- the @conditionalRenderingEnable@ is set to
-- 'Vulkan.Core10.FundamentalTypes.TRUE'. Conditional rendering /must/ not
-- be active in the primary command buffer if @conditionalRenderingEnable@
-- is 'Vulkan.Core10.FundamentalTypes.FALSE'.
--
-- == Examples
--
-- None.
--
-- == Version History
--
-- -   Revision 1, 2018-04-19 (Vikram Kushwaha)
--
--     -   First Version
--
-- -   Revision 2, 2018-05-21 (Vikram Kushwaha)
--
--     -   Add new pipeline stage, access flags and limit conditional
--         rendering to a subpass or entire render pass.
--
-- == See Also
--
-- 'CommandBufferInheritanceConditionalRenderingInfoEXT',
-- 'ConditionalRenderingBeginInfoEXT', 'ConditionalRenderingFlagBitsEXT',
-- 'ConditionalRenderingFlagsEXT',
-- 'PhysicalDeviceConditionalRenderingFeaturesEXT',
-- 'cmdBeginConditionalRenderingEXT', 'cmdEndConditionalRenderingEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_conditional_rendering 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_conditional_rendering  ( cmdBeginConditionalRenderingEXT
                                                       , cmdUseConditionalRenderingEXT
                                                       , cmdEndConditionalRenderingEXT
                                                       , ConditionalRenderingBeginInfoEXT(..)
                                                       , CommandBufferInheritanceConditionalRenderingInfoEXT(..)
                                                       , PhysicalDeviceConditionalRenderingFeaturesEXT(..)
                                                       , ConditionalRenderingFlagsEXT
                                                       , ConditionalRenderingFlagBitsEXT( CONDITIONAL_RENDERING_INVERTED_BIT_EXT
                                                                                        , ..
                                                                                        )
                                                       , EXT_CONDITIONAL_RENDERING_SPEC_VERSION
                                                       , pattern EXT_CONDITIONAL_RENDERING_SPEC_VERSION
                                                       , EXT_CONDITIONAL_RENDERING_EXTENSION_NAME
                                                       , pattern EXT_CONDITIONAL_RENDERING_EXTENSION_NAME
                                                       ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
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 GHC.Show (showString)
import Numeric (showHex)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
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 Control.Monad.IO.Class (MonadIO)
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
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 GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Buffer)
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(pVkCmdBeginConditionalRenderingEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdEndConditionalRenderingEXT))
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_CONDITIONAL_RENDERING_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdBeginConditionalRenderingEXT
  :: FunPtr (Ptr CommandBuffer_T -> Ptr ConditionalRenderingBeginInfoEXT -> IO ()) -> Ptr CommandBuffer_T -> Ptr ConditionalRenderingBeginInfoEXT -> IO ()

-- | vkCmdBeginConditionalRenderingEXT - Define the beginning of a
-- conditional rendering block
--
-- == Valid Usage
--
-- -   #VUID-vkCmdBeginConditionalRenderingEXT-None-01980# Conditional
--     rendering /must/ not already be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#active-conditional-rendering active>
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdBeginConditionalRenderingEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdBeginConditionalRenderingEXT-pConditionalRenderingBegin-parameter#
--     @pConditionalRenderingBegin@ /must/ be a valid pointer to a valid
--     'ConditionalRenderingBeginInfoEXT' structure
--
-- -   #VUID-vkCmdBeginConditionalRenderingEXT-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-vkCmdBeginConditionalRenderingEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, or compute operations
--
-- == 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#VkQueueFlagBits Supported Queue Types> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_conditional_rendering VK_EXT_conditional_rendering>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'ConditionalRenderingBeginInfoEXT'
cmdBeginConditionalRenderingEXT :: forall io
                                 . (MonadIO io)
                                => -- | @commandBuffer@ is the command buffer into which this command will be
                                   -- recorded.
                                   CommandBuffer
                                -> -- | @pConditionalRenderingBegin@ is a pointer to a
                                   -- 'ConditionalRenderingBeginInfoEXT' structure specifying parameters of
                                   -- conditional rendering.
                                   ConditionalRenderingBeginInfoEXT
                                -> io ()
cmdBeginConditionalRenderingEXT :: CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io ()
cmdBeginConditionalRenderingEXT CommandBuffer
commandBuffer ConditionalRenderingBeginInfoEXT
conditionalRenderingBegin = 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 vkCmdBeginConditionalRenderingEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
vkCmdBeginConditionalRenderingEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pConditionalRenderingBegin"
          ::: Ptr ConditionalRenderingBeginInfoEXT)
      -> IO ())
pVkCmdBeginConditionalRenderingEXT (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
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
vkCmdBeginConditionalRenderingEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pConditionalRenderingBegin"
          ::: Ptr ConditionalRenderingBeginInfoEXT)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> 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 vkCmdBeginConditionalRenderingEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBeginConditionalRenderingEXT' :: Ptr CommandBuffer_T
-> ("pConditionalRenderingBegin"
    ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ()
vkCmdBeginConditionalRenderingEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pConditionalRenderingBegin"
    ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ()
mkVkCmdBeginConditionalRenderingEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
vkCmdBeginConditionalRenderingEXTPtr
  "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin <- ((("pConditionalRenderingBegin"
   ::: Ptr ConditionalRenderingBeginInfoEXT)
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pConditionalRenderingBegin"
      ::: Ptr ConditionalRenderingBeginInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pConditionalRenderingBegin"
    ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT))
-> ((("pConditionalRenderingBegin"
      ::: Ptr ConditionalRenderingBeginInfoEXT)
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pConditionalRenderingBegin"
      ::: Ptr ConditionalRenderingBeginInfoEXT)
forall a b. (a -> b) -> a -> b
$ ConditionalRenderingBeginInfoEXT
-> (("pConditionalRenderingBegin"
     ::: Ptr ConditionalRenderingBeginInfoEXT)
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ConditionalRenderingBeginInfoEXT
conditionalRenderingBegin)
  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
"vkCmdBeginConditionalRenderingEXT" (Ptr CommandBuffer_T
-> ("pConditionalRenderingBegin"
    ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ()
vkCmdBeginConditionalRenderingEXT' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()

-- | This function will call the supplied action between calls to
-- 'cmdBeginConditionalRenderingEXT' and 'cmdEndConditionalRenderingEXT'
--
-- Note that 'cmdEndConditionalRenderingEXT' is *not* called if an
-- exception is thrown by the inner action.
cmdUseConditionalRenderingEXT :: forall io r . MonadIO io => CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io r -> io r
cmdUseConditionalRenderingEXT :: CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io r -> io r
cmdUseConditionalRenderingEXT CommandBuffer
commandBuffer ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin io r
a =
  (CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io ()
forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io ()
cmdBeginConditionalRenderingEXT CommandBuffer
commandBuffer ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin) io () -> io r -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> io r
a io r -> io () -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (CommandBuffer -> io ()
forall (io :: * -> *). MonadIO io => CommandBuffer -> io ()
cmdEndConditionalRenderingEXT CommandBuffer
commandBuffer)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdEndConditionalRenderingEXT
  :: FunPtr (Ptr CommandBuffer_T -> IO ()) -> Ptr CommandBuffer_T -> IO ()

-- | vkCmdEndConditionalRenderingEXT - Define the end of a conditional
-- rendering block
--
-- = Description
--
-- Once ended, conditional rendering becomes inactive.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdEndConditionalRenderingEXT-None-01985# Conditional
--     rendering /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#active-conditional-rendering active>
--
-- -   #VUID-vkCmdEndConditionalRenderingEXT-None-01986# If conditional
--     rendering was made
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#active-conditional-rendering active>
--     outside of a render pass instance, it /must/ not be ended inside a
--     render pass instance
--
-- -   #VUID-vkCmdEndConditionalRenderingEXT-None-01987# If conditional
--     rendering was made
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#active-conditional-rendering active>
--     within a subpass it /must/ be ended in the same subpass
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdEndConditionalRenderingEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdEndConditionalRenderingEXT-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-vkCmdEndConditionalRenderingEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, or compute operations
--
-- == 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#VkQueueFlagBits Supported Queue Types> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_conditional_rendering VK_EXT_conditional_rendering>,
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdEndConditionalRenderingEXT :: forall io
                               . (MonadIO io)
                              => -- | @commandBuffer@ is the command buffer into which this command will be
                                 -- recorded.
                                 CommandBuffer
                              -> io ()
cmdEndConditionalRenderingEXT :: CommandBuffer -> io ()
cmdEndConditionalRenderingEXT CommandBuffer
commandBuffer = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdEndConditionalRenderingEXTPtr :: FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndConditionalRenderingEXTPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> IO ())
pVkCmdEndConditionalRenderingEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndConditionalRenderingEXTPtr FunPtr (Ptr CommandBuffer_T -> IO ())
-> FunPtr (Ptr CommandBuffer_T -> IO ()) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr CommandBuffer_T -> 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 vkCmdEndConditionalRenderingEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdEndConditionalRenderingEXT' :: Ptr CommandBuffer_T -> IO ()
vkCmdEndConditionalRenderingEXT' = FunPtr (Ptr CommandBuffer_T -> IO ())
-> Ptr CommandBuffer_T -> IO ()
mkVkCmdEndConditionalRenderingEXT FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndConditionalRenderingEXTPtr
  String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdEndConditionalRenderingEXT" (Ptr CommandBuffer_T -> IO ()
vkCmdEndConditionalRenderingEXT' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)))
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkConditionalRenderingBeginInfoEXT - Structure specifying conditional
-- rendering begin information
--
-- = Description
--
-- If the 32-bit value at @offset@ in @buffer@ memory is zero, then the
-- rendering commands are discarded, otherwise they are executed as normal.
-- If the value of the predicate in buffer memory changes while conditional
-- rendering is active, the rendering commands /may/ be discarded in an
-- implementation-dependent way. Some implementations may latch the value
-- of the predicate upon beginning conditional rendering while others may
-- read it before every rendering command.
--
-- == Valid Usage
--
-- -   #VUID-VkConditionalRenderingBeginInfoEXT-buffer-01981# If @buffer@
--     is non-sparse then it /must/ be bound completely and contiguously to
--     a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   #VUID-VkConditionalRenderingBeginInfoEXT-buffer-01982# @buffer@
--     /must/ have been created with the
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_CONDITIONAL_RENDERING_BIT_EXT'
--     bit set
--
-- -   #VUID-VkConditionalRenderingBeginInfoEXT-offset-01983# @offset@
--     /must/ be less than the size of @buffer@ by at least 32 bits
--
-- -   #VUID-VkConditionalRenderingBeginInfoEXT-offset-01984# @offset@
--     /must/ be a multiple of 4
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkConditionalRenderingBeginInfoEXT-sType-sType# @sType@ /must/
--     be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT'
--
-- -   #VUID-VkConditionalRenderingBeginInfoEXT-pNext-pNext# @pNext@ /must/
--     be @NULL@
--
-- -   #VUID-VkConditionalRenderingBeginInfoEXT-buffer-parameter# @buffer@
--     /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   #VUID-VkConditionalRenderingBeginInfoEXT-flags-parameter# @flags@
--     /must/ be a valid combination of 'ConditionalRenderingFlagBitsEXT'
--     values
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_conditional_rendering VK_EXT_conditional_rendering>,
-- 'Vulkan.Core10.Handles.Buffer', 'ConditionalRenderingFlagsEXT',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdBeginConditionalRenderingEXT'
data ConditionalRenderingBeginInfoEXT = ConditionalRenderingBeginInfoEXT
  { -- | @buffer@ is a buffer containing the predicate for conditional rendering.
    ConditionalRenderingBeginInfoEXT -> Buffer
buffer :: Buffer
  , -- | @offset@ is the byte offset into @buffer@ where the predicate is
    -- located.
    ConditionalRenderingBeginInfoEXT -> DeviceSize
offset :: DeviceSize
  , -- | @flags@ is a bitmask of 'ConditionalRenderingFlagsEXT' specifying the
    -- behavior of conditional rendering.
    ConditionalRenderingBeginInfoEXT -> ConditionalRenderingFlagsEXT
flags :: ConditionalRenderingFlagsEXT
  }
  deriving (Typeable, ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
(ConditionalRenderingBeginInfoEXT
 -> ConditionalRenderingBeginInfoEXT -> Bool)
-> (ConditionalRenderingBeginInfoEXT
    -> ConditionalRenderingBeginInfoEXT -> Bool)
-> Eq ConditionalRenderingBeginInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
$c/= :: ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
== :: ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
$c== :: ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ConditionalRenderingBeginInfoEXT)
#endif
deriving instance Show ConditionalRenderingBeginInfoEXT

instance ToCStruct ConditionalRenderingBeginInfoEXT where
  withCStruct :: ConditionalRenderingBeginInfoEXT
-> (("pConditionalRenderingBegin"
     ::: Ptr ConditionalRenderingBeginInfoEXT)
    -> IO b)
-> IO b
withCStruct ConditionalRenderingBeginInfoEXT
x ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO b
f = Int
-> (("pConditionalRenderingBegin"
     ::: Ptr ConditionalRenderingBeginInfoEXT)
    -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((("pConditionalRenderingBegin"
   ::: Ptr ConditionalRenderingBeginInfoEXT)
  -> IO b)
 -> IO b)
-> (("pConditionalRenderingBegin"
     ::: Ptr ConditionalRenderingBeginInfoEXT)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \"pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p -> ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> ConditionalRenderingBeginInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ConditionalRenderingBeginInfoEXT
x (("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO b
f "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p)
  pokeCStruct :: ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> ConditionalRenderingBeginInfoEXT -> IO b -> IO b
pokeCStruct "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ConditionalRenderingBeginInfoEXT{DeviceSize
Buffer
ConditionalRenderingFlagsEXT
flags :: ConditionalRenderingFlagsEXT
offset :: DeviceSize
buffer :: Buffer
$sel:flags:ConditionalRenderingBeginInfoEXT :: ConditionalRenderingBeginInfoEXT -> ConditionalRenderingFlagsEXT
$sel:offset:ConditionalRenderingBeginInfoEXT :: ConditionalRenderingBeginInfoEXT -> DeviceSize
$sel:buffer:ConditionalRenderingBeginInfoEXT :: ConditionalRenderingBeginInfoEXT -> Buffer
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer)) (Buffer
buffer)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (DeviceSize
offset)
    Ptr ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr ConditionalRenderingFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr ConditionalRenderingFlagsEXT)) (ConditionalRenderingFlagsEXT
flags)
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO b -> IO b
pokeZeroCStruct "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer)) (Buffer
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ConditionalRenderingBeginInfoEXT where
  peekCStruct :: ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ConditionalRenderingBeginInfoEXT
peekCStruct "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p = do
    Buffer
buffer <- Ptr Buffer -> IO Buffer
forall a. Storable a => Ptr a -> IO a
peek @Buffer (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer))
    DeviceSize
offset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize))
    ConditionalRenderingFlagsEXT
flags <- Ptr ConditionalRenderingFlagsEXT -> IO ConditionalRenderingFlagsEXT
forall a. Storable a => Ptr a -> IO a
peek @ConditionalRenderingFlagsEXT (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr ConditionalRenderingFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr ConditionalRenderingFlagsEXT))
    ConditionalRenderingBeginInfoEXT
-> IO ConditionalRenderingBeginInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ConditionalRenderingBeginInfoEXT
 -> IO ConditionalRenderingBeginInfoEXT)
-> ConditionalRenderingBeginInfoEXT
-> IO ConditionalRenderingBeginInfoEXT
forall a b. (a -> b) -> a -> b
$ Buffer
-> DeviceSize
-> ConditionalRenderingFlagsEXT
-> ConditionalRenderingBeginInfoEXT
ConditionalRenderingBeginInfoEXT
             Buffer
buffer DeviceSize
offset ConditionalRenderingFlagsEXT
flags

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

instance Zero ConditionalRenderingBeginInfoEXT where
  zero :: ConditionalRenderingBeginInfoEXT
zero = Buffer
-> DeviceSize
-> ConditionalRenderingFlagsEXT
-> ConditionalRenderingBeginInfoEXT
ConditionalRenderingBeginInfoEXT
           Buffer
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           ConditionalRenderingFlagsEXT
forall a. Zero a => a
zero


-- | VkCommandBufferInheritanceConditionalRenderingInfoEXT - Structure
-- specifying command buffer inheritance information
--
-- = Description
--
-- If this structure is not present, the behavior is as if
-- @conditionalRenderingEnable@ is 'Vulkan.Core10.FundamentalTypes.FALSE'.
--
-- == Valid Usage
--
-- -   #VUID-VkCommandBufferInheritanceConditionalRenderingInfoEXT-conditionalRenderingEnable-01977#
--     If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-inheritedConditionalRendering inherited conditional rendering>
--     feature is not enabled, @conditionalRenderingEnable@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkCommandBufferInheritanceConditionalRenderingInfoEXT-sType-sType#
--     @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_CONDITIONAL_RENDERING_INFO_EXT'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_conditional_rendering VK_EXT_conditional_rendering>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data CommandBufferInheritanceConditionalRenderingInfoEXT = CommandBufferInheritanceConditionalRenderingInfoEXT
  { -- | @conditionalRenderingEnable@ specifies whether the command buffer /can/
    -- be executed while conditional rendering is active in the primary command
    -- buffer. If this is 'Vulkan.Core10.FundamentalTypes.TRUE', then this
    -- command buffer /can/ be executed whether the primary command buffer has
    -- active conditional rendering or not. If this is
    -- 'Vulkan.Core10.FundamentalTypes.FALSE', then the primary command buffer
    -- /must/ not have conditional rendering active.
    CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
conditionalRenderingEnable :: Bool }
  deriving (Typeable, CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
(CommandBufferInheritanceConditionalRenderingInfoEXT
 -> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool)
-> (CommandBufferInheritanceConditionalRenderingInfoEXT
    -> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool)
-> Eq CommandBufferInheritanceConditionalRenderingInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
$c/= :: CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
== :: CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
$c== :: CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CommandBufferInheritanceConditionalRenderingInfoEXT)
#endif
deriving instance Show CommandBufferInheritanceConditionalRenderingInfoEXT

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

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

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


-- | VkPhysicalDeviceConditionalRenderingFeaturesEXT - Structure describing
-- if a secondary command buffer can be executed if conditional rendering
-- is active in the primary command buffer
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceConditionalRenderingFeaturesEXT' 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. 'PhysicalDeviceConditionalRenderingFeaturesEXT' /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_conditional_rendering VK_EXT_conditional_rendering>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceConditionalRenderingFeaturesEXT = PhysicalDeviceConditionalRenderingFeaturesEXT
  { -- | #features-conditionalRendering# @conditionalRendering@ specifies whether
    -- conditional rendering is supported.
    PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
conditionalRendering :: Bool
  , -- | #features-inheritedConditionalRendering# @inheritedConditionalRendering@
    -- specifies whether a secondary command buffer /can/ be executed while
    -- conditional rendering is active in the primary command buffer.
    PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
inheritedConditionalRendering :: Bool
  }
  deriving (Typeable, PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
(PhysicalDeviceConditionalRenderingFeaturesEXT
 -> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool)
-> (PhysicalDeviceConditionalRenderingFeaturesEXT
    -> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool)
-> Eq PhysicalDeviceConditionalRenderingFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
$c/= :: PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
== :: PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
$c== :: PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceConditionalRenderingFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceConditionalRenderingFeaturesEXT

instance ToCStruct PhysicalDeviceConditionalRenderingFeaturesEXT where
  withCStruct :: PhysicalDeviceConditionalRenderingFeaturesEXT
-> (Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceConditionalRenderingFeaturesEXT
x Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p -> Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p PhysicalDeviceConditionalRenderingFeaturesEXT
x (Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b
f Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p PhysicalDeviceConditionalRenderingFeaturesEXT{Bool
inheritedConditionalRendering :: Bool
conditionalRendering :: Bool
$sel:inheritedConditionalRendering:PhysicalDeviceConditionalRenderingFeaturesEXT :: PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
$sel:conditionalRendering:PhysicalDeviceConditionalRenderingFeaturesEXT :: PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> 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 PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
conditionalRendering))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
inheritedConditionalRendering))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> 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 PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> 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 PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> 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))
    IO b
f

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

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

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


type ConditionalRenderingFlagsEXT = ConditionalRenderingFlagBitsEXT

-- | VkConditionalRenderingFlagBitsEXT - Specify the behavior of conditional
-- rendering
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_conditional_rendering VK_EXT_conditional_rendering>,
-- 'ConditionalRenderingFlagsEXT'
newtype ConditionalRenderingFlagBitsEXT = ConditionalRenderingFlagBitsEXT Flags
  deriving newtype (ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
(ConditionalRenderingFlagsEXT
 -> ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Bool)
-> Eq ConditionalRenderingFlagsEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c/= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
== :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c== :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
Eq, Eq ConditionalRenderingFlagsEXT
Eq ConditionalRenderingFlagsEXT
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Ordering)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> Ord ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Ordering
ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
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 :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$cmin :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
max :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$cmax :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
>= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c>= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
> :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c> :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
<= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c<= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
< :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c< :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
compare :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Ordering
$ccompare :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Ordering
$cp1Ord :: Eq ConditionalRenderingFlagsEXT
Ord, Ptr b -> Int -> IO ConditionalRenderingFlagsEXT
Ptr b -> Int -> ConditionalRenderingFlagsEXT -> IO ()
Ptr ConditionalRenderingFlagsEXT -> IO ConditionalRenderingFlagsEXT
Ptr ConditionalRenderingFlagsEXT
-> Int -> IO ConditionalRenderingFlagsEXT
Ptr ConditionalRenderingFlagsEXT
-> Int -> ConditionalRenderingFlagsEXT -> IO ()
Ptr ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> IO ()
ConditionalRenderingFlagsEXT -> Int
(ConditionalRenderingFlagsEXT -> Int)
-> (ConditionalRenderingFlagsEXT -> Int)
-> (Ptr ConditionalRenderingFlagsEXT
    -> Int -> IO ConditionalRenderingFlagsEXT)
-> (Ptr ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO ConditionalRenderingFlagsEXT)
-> (forall b.
    Ptr b -> Int -> ConditionalRenderingFlagsEXT -> IO ())
-> (Ptr ConditionalRenderingFlagsEXT
    -> IO ConditionalRenderingFlagsEXT)
-> (Ptr ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> IO ())
-> Storable ConditionalRenderingFlagsEXT
forall b. Ptr b -> Int -> IO ConditionalRenderingFlagsEXT
forall b. Ptr b -> Int -> ConditionalRenderingFlagsEXT -> 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 ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> IO ()
$cpoke :: Ptr ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> IO ()
peek :: Ptr ConditionalRenderingFlagsEXT -> IO ConditionalRenderingFlagsEXT
$cpeek :: Ptr ConditionalRenderingFlagsEXT -> IO ConditionalRenderingFlagsEXT
pokeByteOff :: Ptr b -> Int -> ConditionalRenderingFlagsEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ConditionalRenderingFlagsEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO ConditionalRenderingFlagsEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ConditionalRenderingFlagsEXT
pokeElemOff :: Ptr ConditionalRenderingFlagsEXT
-> Int -> ConditionalRenderingFlagsEXT -> IO ()
$cpokeElemOff :: Ptr ConditionalRenderingFlagsEXT
-> Int -> ConditionalRenderingFlagsEXT -> IO ()
peekElemOff :: Ptr ConditionalRenderingFlagsEXT
-> Int -> IO ConditionalRenderingFlagsEXT
$cpeekElemOff :: Ptr ConditionalRenderingFlagsEXT
-> Int -> IO ConditionalRenderingFlagsEXT
alignment :: ConditionalRenderingFlagsEXT -> Int
$calignment :: ConditionalRenderingFlagsEXT -> Int
sizeOf :: ConditionalRenderingFlagsEXT -> Int
$csizeOf :: ConditionalRenderingFlagsEXT -> Int
Storable, ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT -> Zero ConditionalRenderingFlagsEXT
forall a. a -> Zero a
zero :: ConditionalRenderingFlagsEXT
$czero :: ConditionalRenderingFlagsEXT
Zero, Eq ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT
Eq ConditionalRenderingFlagsEXT
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> ConditionalRenderingFlagsEXT
-> (Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT -> Int -> Bool)
-> (ConditionalRenderingFlagsEXT -> Maybe Int)
-> (ConditionalRenderingFlagsEXT -> Int)
-> (ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT -> Int)
-> Bits ConditionalRenderingFlagsEXT
Int -> ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT -> Bool
ConditionalRenderingFlagsEXT -> Int
ConditionalRenderingFlagsEXT -> Maybe Int
ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT -> Int -> Bool
ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: ConditionalRenderingFlagsEXT -> Int
$cpopCount :: ConditionalRenderingFlagsEXT -> Int
rotateR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$crotateR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
rotateL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$crotateL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
unsafeShiftR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cunsafeShiftR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
shiftR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cshiftR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
unsafeShiftL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cunsafeShiftL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
shiftL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cshiftL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
isSigned :: ConditionalRenderingFlagsEXT -> Bool
$cisSigned :: ConditionalRenderingFlagsEXT -> Bool
bitSize :: ConditionalRenderingFlagsEXT -> Int
$cbitSize :: ConditionalRenderingFlagsEXT -> Int
bitSizeMaybe :: ConditionalRenderingFlagsEXT -> Maybe Int
$cbitSizeMaybe :: ConditionalRenderingFlagsEXT -> Maybe Int
testBit :: ConditionalRenderingFlagsEXT -> Int -> Bool
$ctestBit :: ConditionalRenderingFlagsEXT -> Int -> Bool
complementBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$ccomplementBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
clearBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cclearBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
setBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$csetBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
bit :: Int -> ConditionalRenderingFlagsEXT
$cbit :: Int -> ConditionalRenderingFlagsEXT
zeroBits :: ConditionalRenderingFlagsEXT
$czeroBits :: ConditionalRenderingFlagsEXT
rotate :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$crotate :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
shift :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cshift :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
complement :: ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$ccomplement :: ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
xor :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$cxor :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
.|. :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$c.|. :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
.&. :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$c.&. :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$cp1Bits :: Eq ConditionalRenderingFlagsEXT
Bits, Bits ConditionalRenderingFlagsEXT
Bits ConditionalRenderingFlagsEXT
-> (ConditionalRenderingFlagsEXT -> Int)
-> (ConditionalRenderingFlagsEXT -> Int)
-> (ConditionalRenderingFlagsEXT -> Int)
-> FiniteBits ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: ConditionalRenderingFlagsEXT -> Int
$ccountTrailingZeros :: ConditionalRenderingFlagsEXT -> Int
countLeadingZeros :: ConditionalRenderingFlagsEXT -> Int
$ccountLeadingZeros :: ConditionalRenderingFlagsEXT -> Int
finiteBitSize :: ConditionalRenderingFlagsEXT -> Int
$cfiniteBitSize :: ConditionalRenderingFlagsEXT -> Int
$cp1FiniteBits :: Bits ConditionalRenderingFlagsEXT
FiniteBits)

-- | 'CONDITIONAL_RENDERING_INVERTED_BIT_EXT' specifies the condition used to
-- determine whether to discard rendering commands or not. That is, if the
-- 32-bit predicate read from @buffer@ memory at @offset@ is zero, the
-- rendering commands are not discarded, and if non zero, then they are
-- discarded.
pattern $bCONDITIONAL_RENDERING_INVERTED_BIT_EXT :: ConditionalRenderingFlagsEXT
$mCONDITIONAL_RENDERING_INVERTED_BIT_EXT :: forall r.
ConditionalRenderingFlagsEXT -> (Void# -> r) -> (Void# -> r) -> r
CONDITIONAL_RENDERING_INVERTED_BIT_EXT = ConditionalRenderingFlagBitsEXT 0x00000001

conNameConditionalRenderingFlagBitsEXT :: String
conNameConditionalRenderingFlagBitsEXT :: String
conNameConditionalRenderingFlagBitsEXT = String
"ConditionalRenderingFlagBitsEXT"

enumPrefixConditionalRenderingFlagBitsEXT :: String
enumPrefixConditionalRenderingFlagBitsEXT :: String
enumPrefixConditionalRenderingFlagBitsEXT = String
"CONDITIONAL_RENDERING_INVERTED_BIT_EXT"

showTableConditionalRenderingFlagBitsEXT :: [(ConditionalRenderingFlagBitsEXT, String)]
showTableConditionalRenderingFlagBitsEXT :: [(ConditionalRenderingFlagsEXT, String)]
showTableConditionalRenderingFlagBitsEXT = [(ConditionalRenderingFlagsEXT
CONDITIONAL_RENDERING_INVERTED_BIT_EXT, String
"")]

instance Show ConditionalRenderingFlagBitsEXT where
  showsPrec :: Int -> ConditionalRenderingFlagsEXT -> ShowS
showsPrec = String
-> [(ConditionalRenderingFlagsEXT, String)]
-> String
-> (ConditionalRenderingFlagsEXT -> Flags)
-> (Flags -> ShowS)
-> Int
-> ConditionalRenderingFlagsEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixConditionalRenderingFlagBitsEXT
                            [(ConditionalRenderingFlagsEXT, String)]
showTableConditionalRenderingFlagBitsEXT
                            String
conNameConditionalRenderingFlagBitsEXT
                            (\(ConditionalRenderingFlagBitsEXT Flags
x) -> Flags
x)
                            (\Flags
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read ConditionalRenderingFlagBitsEXT where
  readPrec :: ReadPrec ConditionalRenderingFlagsEXT
readPrec = String
-> [(ConditionalRenderingFlagsEXT, String)]
-> String
-> (Flags -> ConditionalRenderingFlagsEXT)
-> ReadPrec ConditionalRenderingFlagsEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixConditionalRenderingFlagBitsEXT
                          [(ConditionalRenderingFlagsEXT, String)]
showTableConditionalRenderingFlagBitsEXT
                          String
conNameConditionalRenderingFlagBitsEXT
                          Flags -> ConditionalRenderingFlagsEXT
ConditionalRenderingFlagBitsEXT


type EXT_CONDITIONAL_RENDERING_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_EXT_CONDITIONAL_RENDERING_SPEC_VERSION"
pattern EXT_CONDITIONAL_RENDERING_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_CONDITIONAL_RENDERING_SPEC_VERSION :: a
$mEXT_CONDITIONAL_RENDERING_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_CONDITIONAL_RENDERING_SPEC_VERSION = 2


type EXT_CONDITIONAL_RENDERING_EXTENSION_NAME = "VK_EXT_conditional_rendering"

-- No documentation found for TopLevel "VK_EXT_CONDITIONAL_RENDERING_EXTENSION_NAME"
pattern EXT_CONDITIONAL_RENDERING_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_CONDITIONAL_RENDERING_EXTENSION_NAME :: a
$mEXT_CONDITIONAL_RENDERING_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_CONDITIONAL_RENDERING_EXTENSION_NAME = "VK_EXT_conditional_rendering"