{-# language CPP #-}
-- | = Name
--
-- VK_EXT_discard_rectangles - device extension
--
-- == VK_EXT_discard_rectangles
--
-- [__Name String__]
--     @VK_EXT_discard_rectangles@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     100
--
-- [__Revision__]
--     2
--
-- [__Ratification Status__]
--     Ratified
--
-- [__Extension and Version Dependencies__]
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_physical_device_properties2 VK_KHR_get_physical_device_properties2>
--     or
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#versions-1.1 Version 1.1>
--
-- [__Contact__]
--
--     -   Piers Daniell
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_discard_rectangles] @pdaniell-nv%0A*Here describe the issue or question you have about the VK_EXT_discard_rectangles extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2023-01-18
--
-- [__Interactions and External Dependencies__]
--
--     -   Interacts with @VK_KHR_device_group@
--
--     -   Interacts with Vulkan 1.1
--
-- [__Contributors__]
--
--     -   Daniel Koch, NVIDIA
--
--     -   Jeff Bolz, NVIDIA
--
-- == Description
--
-- This extension provides additional orthogonally aligned “discard
-- rectangles” specified in framebuffer-space coordinates that restrict
-- rasterization of all points, lines and triangles.
--
-- From zero to an implementation-dependent limit (specified by
-- @maxDiscardRectangles@) number of discard rectangles can be operational
-- at once. When one or more discard rectangles are active, rasterized
-- fragments can either survive if the fragment is within any of the
-- operational discard rectangles ('DISCARD_RECTANGLE_MODE_INCLUSIVE_EXT'
-- mode) or be rejected if the fragment is within any of the operational
-- discard rectangles ('DISCARD_RECTANGLE_MODE_EXCLUSIVE_EXT' mode).
--
-- These discard rectangles operate orthogonally to the existing scissor
-- test functionality. The discard rectangles can be different for each
-- physical device in a device group by specifying the device mask and
-- setting discard rectangle dynamic state.
--
-- Version 2 of this extension introduces new dynamic states
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_ENABLE_EXT'
-- and
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_MODE_EXT',
-- and the corresponding functions 'cmdSetDiscardRectangleEnableEXT' and
-- 'cmdSetDiscardRectangleModeEXT'. Applications that use these dynamic
-- states must ensure the implementation advertises at least @specVersion@
-- @2@ of this extension.
--
-- == New Commands
--
-- -   'cmdSetDiscardRectangleEXT'
--
-- -   'cmdSetDiscardRectangleEnableEXT'
--
-- -   'cmdSetDiscardRectangleModeEXT'
--
-- == New Structures
--
-- -   Extending 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo':
--
--     -   'PipelineDiscardRectangleStateCreateInfoEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceDiscardRectanglePropertiesEXT'
--
-- == New Enums
--
-- -   'DiscardRectangleModeEXT'
--
-- == New Bitmasks
--
-- -   'PipelineDiscardRectangleStateCreateFlagsEXT'
--
-- == New Enum Constants
--
-- -   'EXT_DISCARD_RECTANGLES_EXTENSION_NAME'
--
-- -   'EXT_DISCARD_RECTANGLES_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.DynamicState.DynamicState':
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_ENABLE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_MODE_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_DISCARD_RECTANGLE_PROPERTIES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_DISCARD_RECTANGLE_STATE_CREATE_INFO_EXT'
--
-- == Version History
--
-- -   Revision 2, 2023-01-18 (Piers Daniell)
--
--     -   Add dynamic states for discard rectangle enable\/disable and
--         mode.
--
-- -   Revision 1, 2016-12-22 (Piers Daniell)
--
--     -   Internal revisions
--
-- == See Also
--
-- 'DiscardRectangleModeEXT',
-- 'PhysicalDeviceDiscardRectanglePropertiesEXT',
-- 'PipelineDiscardRectangleStateCreateFlagsEXT',
-- 'PipelineDiscardRectangleStateCreateInfoEXT',
-- 'cmdSetDiscardRectangleEXT', 'cmdSetDiscardRectangleEnableEXT',
-- 'cmdSetDiscardRectangleModeEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_discard_rectangles 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_discard_rectangles  ( cmdSetDiscardRectangleEXT
                                                    , cmdSetDiscardRectangleEnableEXT
                                                    , cmdSetDiscardRectangleModeEXT
                                                    , PhysicalDeviceDiscardRectanglePropertiesEXT(..)
                                                    , PipelineDiscardRectangleStateCreateInfoEXT(..)
                                                    , PipelineDiscardRectangleStateCreateFlagsEXT(..)
                                                    , DiscardRectangleModeEXT( DISCARD_RECTANGLE_MODE_INCLUSIVE_EXT
                                                                             , DISCARD_RECTANGLE_MODE_EXCLUSIVE_EXT
                                                                             , ..
                                                                             )
                                                    , EXT_DISCARD_RECTANGLES_SPEC_VERSION
                                                    , pattern EXT_DISCARD_RECTANGLES_SPEC_VERSION
                                                    , EXT_DISCARD_RECTANGLES_EXTENSION_NAME
                                                    , pattern EXT_DISCARD_RECTANGLES_EXTENSION_NAME
                                                    ) where

import Data.Bits (Bits)
import Data.Bits (FiniteBits)
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 GHC.Show (showsPrec)
import Numeric (showHex)
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 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 Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
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 (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(pVkCmdSetDiscardRectangleEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDiscardRectangleEnableEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDiscardRectangleModeEXT))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.FundamentalTypes (Rect2D)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DISCARD_RECTANGLE_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_DISCARD_RECTANGLE_STATE_CREATE_INFO_EXT))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdSetDiscardRectangleEXT
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Rect2D -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Rect2D -> IO ()

-- | vkCmdSetDiscardRectangleEXT - Set discard rectangles dynamically for a
-- command buffer
--
-- = Description
--
-- The discard rectangle taken from element i of @pDiscardRectangles@
-- replace the current state for the discard rectangle at index
-- @firstDiscardRectangle@ + i, for i in [0, @discardRectangleCount@).
--
-- This command sets the discard rectangles for subsequent drawing commands
-- when drawing using
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>,
-- or when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'PipelineDiscardRectangleStateCreateInfoEXT'::@pDiscardRectangles@
-- values used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetDiscardRectangleEXT-firstDiscardRectangle-00585# The
--     sum of @firstDiscardRectangle@ and @discardRectangleCount@ /must/ be
--     less than or equal to
--     'PhysicalDeviceDiscardRectanglePropertiesEXT'::@maxDiscardRectangles@
--
-- -   #VUID-vkCmdSetDiscardRectangleEXT-x-00587# The @x@ and @y@ member of
--     @offset@ in each 'Vulkan.Core10.FundamentalTypes.Rect2D' element of
--     @pDiscardRectangles@ /must/ be greater than or equal to @0@
--
-- -   #VUID-vkCmdSetDiscardRectangleEXT-offset-00588# Evaluation of
--     (@offset.x@ + @extent.width@) in each
--     'Vulkan.Core10.FundamentalTypes.Rect2D' element of
--     @pDiscardRectangles@ /must/ not cause a signed integer addition
--     overflow
--
-- -   #VUID-vkCmdSetDiscardRectangleEXT-offset-00589# Evaluation of
--     (@offset.y@ + @extent.height@) in each
--     'Vulkan.Core10.FundamentalTypes.Rect2D' element of
--     @pDiscardRectangles@ /must/ not cause a signed integer addition
--     overflow
--
-- -   #VUID-vkCmdSetDiscardRectangleEXT-viewportScissor2D-04788# If this
--     command is recorded in a secondary command buffer with
--     'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV'::@viewportScissor2D@
--     enabled, then this function /must/ not be called
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetDiscardRectangleEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetDiscardRectangleEXT-pDiscardRectangles-parameter#
--     @pDiscardRectangles@ /must/ be a valid pointer to an array of
--     @discardRectangleCount@ 'Vulkan.Core10.FundamentalTypes.Rect2D'
--     structures
--
-- -   #VUID-vkCmdSetDiscardRectangleEXT-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-vkCmdSetDiscardRectangleEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetDiscardRectangleEXT-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- -   #VUID-vkCmdSetDiscardRectangleEXT-discardRectangleCount-arraylength#
--     @discardRectangleCount@ /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_discard_rectangles VK_EXT_discard_rectangles>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.Rect2D'
cmdSetDiscardRectangleEXT :: forall io
                           . (MonadIO io)
                          => -- | @commandBuffer@ is the command buffer into which the command will be
                             -- recorded.
                             CommandBuffer
                          -> -- | @firstDiscardRectangle@ is the index of the first discard rectangle
                             -- whose state is updated by the command.
                             ("firstDiscardRectangle" ::: Word32)
                          -> -- | @pDiscardRectangles@ is a pointer to an array of
                             -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures specifying discard
                             -- rectangles.
                             ("discardRectangles" ::: Vector Rect2D)
                          -> io ()
cmdSetDiscardRectangleEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> ("firstDiscardRectangle" ::: Word32)
-> ("discardRectangles" ::: Vector Rect2D)
-> io ()
cmdSetDiscardRectangleEXT CommandBuffer
commandBuffer
                            "firstDiscardRectangle" ::: Word32
firstDiscardRectangle
                            "discardRectangles" ::: Vector Rect2D
discardRectangles = IO () -> io ()
forall a. IO a -> io a
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 vkCmdSetDiscardRectangleEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstDiscardRectangle" ::: Word32)
   -> ("firstDiscardRectangle" ::: Word32)
   -> Ptr Rect2D
   -> IO ())
vkCmdSetDiscardRectangleEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstDiscardRectangle" ::: Word32)
      -> ("firstDiscardRectangle" ::: Word32)
      -> Ptr Rect2D
      -> IO ())
pVkCmdSetDiscardRectangleEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT () IO ()
forall (m :: * -> *) a. Monad m => m a -> ContT () m a
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
   -> ("firstDiscardRectangle" ::: Word32)
   -> ("firstDiscardRectangle" ::: Word32)
   -> Ptr Rect2D
   -> IO ())
vkCmdSetDiscardRectangleEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstDiscardRectangle" ::: Word32)
   -> ("firstDiscardRectangle" ::: Word32)
   -> Ptr Rect2D
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstDiscardRectangle" ::: Word32)
      -> ("firstDiscardRectangle" ::: Word32)
      -> Ptr Rect2D
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstDiscardRectangle" ::: Word32)
   -> ("firstDiscardRectangle" ::: Word32)
   -> Ptr Rect2D
   -> 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 vkCmdSetDiscardRectangleEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetDiscardRectangleEXT' :: Ptr CommandBuffer_T
-> ("firstDiscardRectangle" ::: Word32)
-> ("firstDiscardRectangle" ::: Word32)
-> Ptr Rect2D
-> IO ()
vkCmdSetDiscardRectangleEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstDiscardRectangle" ::: Word32)
   -> ("firstDiscardRectangle" ::: Word32)
   -> Ptr Rect2D
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstDiscardRectangle" ::: Word32)
-> ("firstDiscardRectangle" ::: Word32)
-> Ptr Rect2D
-> IO ()
mkVkCmdSetDiscardRectangleEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("firstDiscardRectangle" ::: Word32)
   -> ("firstDiscardRectangle" ::: Word32)
   -> Ptr Rect2D
   -> IO ())
vkCmdSetDiscardRectangleEXTPtr
  Ptr Rect2D
pPDiscardRectangles <- ((Ptr Rect2D -> IO ()) -> IO ()) -> ContT () IO (Ptr Rect2D)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Rect2D -> IO ()) -> IO ()) -> ContT () IO (Ptr Rect2D))
-> ((Ptr Rect2D -> IO ()) -> IO ()) -> ContT () IO (Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Rect2D ((("discardRectangles" ::: Vector Rect2D) -> Int
forall a. Vector a -> Int
Data.Vector.length ("discardRectangles" ::: Vector Rect2D
discardRectangles)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
16)
  IO () -> ContT () IO ()
forall (m :: * -> *) a. Monad m => m a -> ContT () m a
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 -> Rect2D -> IO ())
-> ("discardRectangles" ::: Vector Rect2D) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Rect2D
e -> Ptr Rect2D -> Rect2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rect2D
pPDiscardRectangles Ptr Rect2D -> Int -> Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D) (Rect2D
e)) ("discardRectangles" ::: Vector Rect2D
discardRectangles)
  IO () -> ContT () IO ()
forall (m :: * -> *) a. Monad m => m a -> ContT () m a
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
"vkCmdSetDiscardRectangleEXT" (Ptr CommandBuffer_T
-> ("firstDiscardRectangle" ::: Word32)
-> ("firstDiscardRectangle" ::: Word32)
-> Ptr Rect2D
-> IO ()
vkCmdSetDiscardRectangleEXT'
                                                           (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                           ("firstDiscardRectangle" ::: Word32
firstDiscardRectangle)
                                                           ((Int -> "firstDiscardRectangle" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("discardRectangles" ::: Vector Rect2D) -> Int
forall a. Vector a -> Int
Data.Vector.length (("discardRectangles" ::: Vector Rect2D) -> Int)
-> ("discardRectangles" ::: Vector Rect2D) -> Int
forall a b. (a -> b) -> a -> b
$ ("discardRectangles" ::: Vector Rect2D
discardRectangles)) :: Word32))
                                                           (Ptr Rect2D
pPDiscardRectangles))
  () -> ContT () IO ()
forall a. a -> ContT () IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdSetDiscardRectangleEnableEXT - Enable discard rectangles
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the discard rectangle enable for subsequent drawing
-- commands when drawing using
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>,
-- or when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_ENABLE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is implied by the
-- 'PipelineDiscardRectangleStateCreateInfoEXT'::@discardRectangleCount@
-- value used to create the currently active pipeline, where a non-zero
-- @discardRectangleCount@ implicitly enables discard rectangles, otherwise
-- they are disabled.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetDiscardRectangleEnableEXT-specVersion-07851# The
--     @VK_EXT_discard_rectangles@ extension /must/ be enabled, and the
--     implementation /must/ support at least @specVersion@ @2@ of this
--     extension
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetDiscardRectangleEnableEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetDiscardRectangleEnableEXT-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-vkCmdSetDiscardRectangleEnableEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetDiscardRectangleEnableEXT-videocoding# This command
--     /must/ only be called outside of a video coding scope
--
-- == 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_discard_rectangles VK_EXT_discard_rectangles>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetDiscardRectangleEnableEXT :: forall io
                                 . (MonadIO io)
                                => -- | @commandBuffer@ is the command buffer into which the command will be
                                   -- recorded.
                                   CommandBuffer
                                -> -- | @discardRectangleEnable@ specifies whether discard rectangles are
                                   -- enabled or not.
                                   ("discardRectangleEnable" ::: Bool)
                                -> io ()
cmdSetDiscardRectangleEnableEXT :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetDiscardRectangleEnableEXT CommandBuffer
commandBuffer
                                  Bool
discardRectangleEnable = IO () -> io ()
forall a. IO a -> io a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetDiscardRectangleEnableEXTPtr :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ())
vkCmdSetDiscardRectangleEnableEXTPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ())
pVkCmdSetDiscardRectangleEnableEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ())
vkCmdSetDiscardRectangleEnableEXTPtr FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ())
-> FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr CommandBuffer_T -> 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 vkCmdSetDiscardRectangleEnableEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetDiscardRectangleEnableEXT' :: Ptr CommandBuffer_T -> Bool32 -> IO ()
vkCmdSetDiscardRectangleEnableEXT' = FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ())
-> Ptr CommandBuffer_T -> Bool32 -> IO ()
mkVkCmdSetDiscardRectangleEnableEXT FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ())
vkCmdSetDiscardRectangleEnableEXTPtr
  String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetDiscardRectangleEnableEXT" (Ptr CommandBuffer_T -> Bool32 -> IO ()
vkCmdSetDiscardRectangleEnableEXT'
                                                          (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                          (Bool -> Bool32
boolToBool32 (Bool
discardRectangleEnable)))
  () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkCmdSetDiscardRectangleModeEXT - Sets the discard rectangle mode
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the discard rectangle mode for subsequent drawing
-- commands when drawing using
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>,
-- or when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_MODE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'PipelineDiscardRectangleStateCreateInfoEXT'::@discardRectangleMode@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetDiscardRectangleModeEXT-specVersion-07852# The
--     @VK_EXT_discard_rectangles@ extension /must/ be enabled, and the
--     implementation /must/ support at least @specVersion@ @2@ of this
--     extension
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetDiscardRectangleModeEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetDiscardRectangleModeEXT-discardRectangleMode-parameter#
--     @discardRectangleMode@ /must/ be a valid 'DiscardRectangleModeEXT'
--     value
--
-- -   #VUID-vkCmdSetDiscardRectangleModeEXT-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-vkCmdSetDiscardRectangleModeEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetDiscardRectangleModeEXT-videocoding# This command
--     /must/ only be called outside of a video coding scope
--
-- == 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_discard_rectangles VK_EXT_discard_rectangles>,
-- 'Vulkan.Core10.Handles.CommandBuffer', 'DiscardRectangleModeEXT'
cmdSetDiscardRectangleModeEXT :: forall io
                               . (MonadIO io)
                              => -- | @commandBuffer@ is the command buffer into which the command will be
                                 -- recorded.
                                 CommandBuffer
                              -> -- | @discardRectangleMode@ specifies the discard rectangle mode for all
                                 -- discard rectangles, either inclusive or exclusive.
                                 DiscardRectangleModeEXT
                              -> io ()
cmdSetDiscardRectangleModeEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> DiscardRectangleModeEXT -> io ()
cmdSetDiscardRectangleModeEXT CommandBuffer
commandBuffer DiscardRectangleModeEXT
discardRectangleMode = IO () -> io ()
forall a. IO a -> io a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetDiscardRectangleModeEXTPtr :: FunPtr (Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> IO ())
vkCmdSetDiscardRectangleModeEXTPtr = DeviceCmds
-> FunPtr (Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> IO ())
pVkCmdSetDiscardRectangleModeEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> IO ())
vkCmdSetDiscardRectangleModeEXTPtr FunPtr (Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> IO ())
-> FunPtr (Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> 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 vkCmdSetDiscardRectangleModeEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetDiscardRectangleModeEXT' :: Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> IO ()
vkCmdSetDiscardRectangleModeEXT' = FunPtr (Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> IO ())
-> Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> IO ()
mkVkCmdSetDiscardRectangleModeEXT FunPtr (Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> IO ())
vkCmdSetDiscardRectangleModeEXTPtr
  String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetDiscardRectangleModeEXT" (Ptr CommandBuffer_T -> DiscardRectangleModeEXT -> IO ()
vkCmdSetDiscardRectangleModeEXT'
                                                        (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                        (DiscardRectangleModeEXT
discardRectangleMode))
  () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkPhysicalDeviceDiscardRectanglePropertiesEXT - Structure describing
-- discard rectangle limits that can be supported by an implementation
--
-- = Description
--
-- If the 'PhysicalDeviceDiscardRectanglePropertiesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_discard_rectangles VK_EXT_discard_rectangles>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceDiscardRectanglePropertiesEXT = PhysicalDeviceDiscardRectanglePropertiesEXT
  { -- | #limits-maxDiscardRectangles# @maxDiscardRectangles@ is the maximum
    -- number of active discard rectangles that /can/ be specified.
    PhysicalDeviceDiscardRectanglePropertiesEXT
-> "firstDiscardRectangle" ::: Word32
maxDiscardRectangles :: Word32 }
  deriving (Typeable, PhysicalDeviceDiscardRectanglePropertiesEXT
-> PhysicalDeviceDiscardRectanglePropertiesEXT -> Bool
(PhysicalDeviceDiscardRectanglePropertiesEXT
 -> PhysicalDeviceDiscardRectanglePropertiesEXT -> Bool)
-> (PhysicalDeviceDiscardRectanglePropertiesEXT
    -> PhysicalDeviceDiscardRectanglePropertiesEXT -> Bool)
-> Eq PhysicalDeviceDiscardRectanglePropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhysicalDeviceDiscardRectanglePropertiesEXT
-> PhysicalDeviceDiscardRectanglePropertiesEXT -> Bool
== :: PhysicalDeviceDiscardRectanglePropertiesEXT
-> PhysicalDeviceDiscardRectanglePropertiesEXT -> Bool
$c/= :: PhysicalDeviceDiscardRectanglePropertiesEXT
-> PhysicalDeviceDiscardRectanglePropertiesEXT -> Bool
/= :: PhysicalDeviceDiscardRectanglePropertiesEXT
-> PhysicalDeviceDiscardRectanglePropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDiscardRectanglePropertiesEXT)
#endif
deriving instance Show PhysicalDeviceDiscardRectanglePropertiesEXT

instance ToCStruct PhysicalDeviceDiscardRectanglePropertiesEXT where
  withCStruct :: forall b.
PhysicalDeviceDiscardRectanglePropertiesEXT
-> (Ptr PhysicalDeviceDiscardRectanglePropertiesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceDiscardRectanglePropertiesEXT
x Ptr PhysicalDeviceDiscardRectanglePropertiesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceDiscardRectanglePropertiesEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceDiscardRectanglePropertiesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceDiscardRectanglePropertiesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p -> Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> PhysicalDeviceDiscardRectanglePropertiesEXT -> IO b -> IO b
forall b.
Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> PhysicalDeviceDiscardRectanglePropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p PhysicalDeviceDiscardRectanglePropertiesEXT
x (Ptr PhysicalDeviceDiscardRectanglePropertiesEXT -> IO b
f Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> PhysicalDeviceDiscardRectanglePropertiesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p PhysicalDeviceDiscardRectanglePropertiesEXT{"firstDiscardRectangle" ::: Word32
$sel:maxDiscardRectangles:PhysicalDeviceDiscardRectanglePropertiesEXT :: PhysicalDeviceDiscardRectanglePropertiesEXT
-> "firstDiscardRectangle" ::: Word32
maxDiscardRectangles :: "firstDiscardRectangle" ::: Word32
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DISCARD_RECTANGLE_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("firstDiscardRectangle" ::: Word32)
-> ("firstDiscardRectangle" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> Int -> Ptr ("firstDiscardRectangle" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ("firstDiscardRectangle" ::: Word32
maxDiscardRectangles)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDiscardRectanglePropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DISCARD_RECTANGLE_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("firstDiscardRectangle" ::: Word32)
-> ("firstDiscardRectangle" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> Int -> Ptr ("firstDiscardRectangle" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ("firstDiscardRectangle" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceDiscardRectanglePropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> IO PhysicalDeviceDiscardRectanglePropertiesEXT
peekCStruct Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p = do
    "firstDiscardRectangle" ::: Word32
maxDiscardRectangles <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
p Ptr PhysicalDeviceDiscardRectanglePropertiesEXT
-> Int -> Ptr ("firstDiscardRectangle" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    PhysicalDeviceDiscardRectanglePropertiesEXT
-> IO PhysicalDeviceDiscardRectanglePropertiesEXT
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceDiscardRectanglePropertiesEXT
 -> IO PhysicalDeviceDiscardRectanglePropertiesEXT)
-> PhysicalDeviceDiscardRectanglePropertiesEXT
-> IO PhysicalDeviceDiscardRectanglePropertiesEXT
forall a b. (a -> b) -> a -> b
$ ("firstDiscardRectangle" ::: Word32)
-> PhysicalDeviceDiscardRectanglePropertiesEXT
PhysicalDeviceDiscardRectanglePropertiesEXT
             "firstDiscardRectangle" ::: Word32
maxDiscardRectangles

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

instance Zero PhysicalDeviceDiscardRectanglePropertiesEXT where
  zero :: PhysicalDeviceDiscardRectanglePropertiesEXT
zero = ("firstDiscardRectangle" ::: Word32)
-> PhysicalDeviceDiscardRectanglePropertiesEXT
PhysicalDeviceDiscardRectanglePropertiesEXT
           "firstDiscardRectangle" ::: Word32
forall a. Zero a => a
zero


-- | VkPipelineDiscardRectangleStateCreateInfoEXT - Structure specifying
-- discard rectangle
--
-- = Description
--
-- If the
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_EXT'
-- dynamic state is enabled for a pipeline, the @pDiscardRectangles@ member
-- is ignored. If the
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_ENABLE_EXT'
-- dynamic state is not enabled for the pipeline the presence of this
-- structure in the 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo'
-- chain, and a @discardRectangleCount@ greater than zero, implicitly
-- enables discard rectangles in the pipeline, otherwise discard rectangles
-- /must/ enabled or disabled by 'cmdSetDiscardRectangleEnableEXT'. If the
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_MODE_EXT'
-- dynamic state is enabled for the pipeline, the @discardRectangleMode@
-- member is ignored, and the discard rectangle mode /must/ be set by
-- 'cmdSetDiscardRectangleModeEXT'.
--
-- When this structure is included in the @pNext@ chain of
-- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo', it defines
-- parameters of the discard rectangle test. If the
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_EXT'
-- dynamic state is not enabled, and this structure is not included in the
-- @pNext@ chain, it is equivalent to specifying this structure with a
-- @discardRectangleCount@ of @0@.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_discard_rectangles VK_EXT_discard_rectangles>,
-- 'DiscardRectangleModeEXT',
-- 'PipelineDiscardRectangleStateCreateFlagsEXT',
-- 'Vulkan.Core10.FundamentalTypes.Rect2D',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineDiscardRectangleStateCreateInfoEXT = PipelineDiscardRectangleStateCreateInfoEXT
  { -- | @flags@ is reserved for future use.
    --
    -- #VUID-VkPipelineDiscardRectangleStateCreateInfoEXT-flags-zerobitmask#
    -- @flags@ /must/ be @0@
    PipelineDiscardRectangleStateCreateInfoEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
flags :: PipelineDiscardRectangleStateCreateFlagsEXT
  , -- | @discardRectangleMode@ is a 'DiscardRectangleModeEXT' value determining
    -- whether the discard rectangle test is inclusive or exclusive.
    --
    -- #VUID-VkPipelineDiscardRectangleStateCreateInfoEXT-discardRectangleMode-parameter#
    -- @discardRectangleMode@ /must/ be a valid 'DiscardRectangleModeEXT' value
    PipelineDiscardRectangleStateCreateInfoEXT
-> DiscardRectangleModeEXT
discardRectangleMode :: DiscardRectangleModeEXT
  , -- | @pDiscardRectangles@ is a pointer to an array of
    -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures defining discard
    -- rectangles.
    PipelineDiscardRectangleStateCreateInfoEXT
-> "discardRectangles" ::: Vector Rect2D
discardRectangles :: Vector Rect2D
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineDiscardRectangleStateCreateInfoEXT)
#endif
deriving instance Show PipelineDiscardRectangleStateCreateInfoEXT

instance ToCStruct PipelineDiscardRectangleStateCreateInfoEXT where
  withCStruct :: forall b.
PipelineDiscardRectangleStateCreateInfoEXT
-> (Ptr PipelineDiscardRectangleStateCreateInfoEXT -> IO b) -> IO b
withCStruct PipelineDiscardRectangleStateCreateInfoEXT
x Ptr PipelineDiscardRectangleStateCreateInfoEXT -> IO b
f = Int
-> (Ptr PipelineDiscardRectangleStateCreateInfoEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((Ptr PipelineDiscardRectangleStateCreateInfoEXT -> IO b) -> IO b)
-> (Ptr PipelineDiscardRectangleStateCreateInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PipelineDiscardRectangleStateCreateInfoEXT
p -> Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> PipelineDiscardRectangleStateCreateInfoEXT -> IO b -> IO b
forall b.
Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> PipelineDiscardRectangleStateCreateInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineDiscardRectangleStateCreateInfoEXT
p PipelineDiscardRectangleStateCreateInfoEXT
x (Ptr PipelineDiscardRectangleStateCreateInfoEXT -> IO b
f Ptr PipelineDiscardRectangleStateCreateInfoEXT
p)
  pokeCStruct :: forall b.
Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> PipelineDiscardRectangleStateCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr PipelineDiscardRectangleStateCreateInfoEXT
p PipelineDiscardRectangleStateCreateInfoEXT{"discardRectangles" ::: Vector Rect2D
DiscardRectangleModeEXT
PipelineDiscardRectangleStateCreateFlagsEXT
$sel:flags:PipelineDiscardRectangleStateCreateInfoEXT :: PipelineDiscardRectangleStateCreateInfoEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
$sel:discardRectangleMode:PipelineDiscardRectangleStateCreateInfoEXT :: PipelineDiscardRectangleStateCreateInfoEXT
-> DiscardRectangleModeEXT
$sel:discardRectangles:PipelineDiscardRectangleStateCreateInfoEXT :: PipelineDiscardRectangleStateCreateInfoEXT
-> "discardRectangles" ::: Vector Rect2D
flags :: PipelineDiscardRectangleStateCreateFlagsEXT
discardRectangleMode :: DiscardRectangleModeEXT
discardRectangles :: "discardRectangles" ::: Vector Rect2D
..} 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 (m :: * -> *) a. Monad m => m a -> ContT b m a
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 PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_DISCARD_RECTANGLE_STATE_CREATE_INFO_EXT)
    IO () -> ContT b IO ()
forall (m :: * -> *) a. Monad m => m a -> ContT b m a
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 PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> 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 (m :: * -> *) a. Monad m => m a -> ContT b m a
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 PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr PipelineDiscardRectangleStateCreateFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineDiscardRectangleStateCreateFlagsEXT)) (PipelineDiscardRectangleStateCreateFlagsEXT
flags)
    IO () -> ContT b IO ()
forall (m :: * -> *) a. Monad m => m a -> ContT b m a
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 DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr DiscardRectangleModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr DiscardRectangleModeEXT)) (DiscardRectangleModeEXT
discardRectangleMode)
    IO () -> ContT b IO ()
forall (m :: * -> *) a. Monad m => m a -> ContT b m a
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 ("firstDiscardRectangle" ::: Word32)
-> ("firstDiscardRectangle" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr ("firstDiscardRectangle" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) ((Int -> "firstDiscardRectangle" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("discardRectangles" ::: Vector Rect2D) -> Int
forall a. Vector a -> Int
Data.Vector.length (("discardRectangles" ::: Vector Rect2D) -> Int)
-> ("discardRectangles" ::: Vector Rect2D) -> Int
forall a b. (a -> b) -> a -> b
$ ("discardRectangles" ::: Vector Rect2D
discardRectangles)) :: Word32))
    Ptr Rect2D
pPDiscardRectangles' <- ((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D))
-> ((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Rect2D ((("discardRectangles" ::: Vector Rect2D) -> Int
forall a. Vector a -> Int
Data.Vector.length ("discardRectangles" ::: Vector Rect2D
discardRectangles)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
16)
    IO () -> ContT b IO ()
forall (m :: * -> *) a. Monad m => m a -> ContT b m a
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 -> Rect2D -> IO ())
-> ("discardRectangles" ::: Vector Rect2D) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Rect2D
e -> Ptr Rect2D -> Rect2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rect2D
pPDiscardRectangles' Ptr Rect2D -> Int -> Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D) (Rect2D
e)) ("discardRectangles" ::: Vector Rect2D
discardRectangles)
    IO () -> ContT b IO ()
forall (m :: * -> *) a. Monad m => m a -> ContT b m a
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 Rect2D) -> Ptr Rect2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr (Ptr Rect2D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr Rect2D))) (Ptr Rect2D
pPDiscardRectangles')
    IO b -> ContT b IO b
forall (m :: * -> *) a. Monad m => m a -> ContT b m a
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
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PipelineDiscardRectangleStateCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr PipelineDiscardRectangleStateCreateInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_DISCARD_RECTANGLE_STATE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr DiscardRectangleModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr DiscardRectangleModeEXT)) (DiscardRectangleModeEXT
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PipelineDiscardRectangleStateCreateInfoEXT where
  peekCStruct :: Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> IO PipelineDiscardRectangleStateCreateInfoEXT
peekCStruct Ptr PipelineDiscardRectangleStateCreateInfoEXT
p = do
    PipelineDiscardRectangleStateCreateFlagsEXT
flags <- forall a. Storable a => Ptr a -> IO a
peek @PipelineDiscardRectangleStateCreateFlagsEXT ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr PipelineDiscardRectangleStateCreateFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineDiscardRectangleStateCreateFlagsEXT))
    DiscardRectangleModeEXT
discardRectangleMode <- forall a. Storable a => Ptr a -> IO a
peek @DiscardRectangleModeEXT ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr DiscardRectangleModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr DiscardRectangleModeEXT))
    "firstDiscardRectangle" ::: Word32
discardRectangleCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr ("firstDiscardRectangle" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
    Ptr Rect2D
pDiscardRectangles <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Rect2D) ((Ptr PipelineDiscardRectangleStateCreateInfoEXT
p Ptr PipelineDiscardRectangleStateCreateInfoEXT
-> Int -> Ptr (Ptr Rect2D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr Rect2D)))
    "discardRectangles" ::: Vector Rect2D
pDiscardRectangles' <- Int
-> (Int -> IO Rect2D) -> IO ("discardRectangles" ::: Vector Rect2D)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("firstDiscardRectangle" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "firstDiscardRectangle" ::: Word32
discardRectangleCount) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Rect2D ((Ptr Rect2D
pDiscardRectangles Ptr Rect2D -> Int -> Ptr Rect2D
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D)))
    PipelineDiscardRectangleStateCreateInfoEXT
-> IO PipelineDiscardRectangleStateCreateInfoEXT
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineDiscardRectangleStateCreateInfoEXT
 -> IO PipelineDiscardRectangleStateCreateInfoEXT)
-> PipelineDiscardRectangleStateCreateInfoEXT
-> IO PipelineDiscardRectangleStateCreateInfoEXT
forall a b. (a -> b) -> a -> b
$ PipelineDiscardRectangleStateCreateFlagsEXT
-> DiscardRectangleModeEXT
-> ("discardRectangles" ::: Vector Rect2D)
-> PipelineDiscardRectangleStateCreateInfoEXT
PipelineDiscardRectangleStateCreateInfoEXT
             PipelineDiscardRectangleStateCreateFlagsEXT
flags DiscardRectangleModeEXT
discardRectangleMode "discardRectangles" ::: Vector Rect2D
pDiscardRectangles'

instance Zero PipelineDiscardRectangleStateCreateInfoEXT where
  zero :: PipelineDiscardRectangleStateCreateInfoEXT
zero = PipelineDiscardRectangleStateCreateFlagsEXT
-> DiscardRectangleModeEXT
-> ("discardRectangles" ::: Vector Rect2D)
-> PipelineDiscardRectangleStateCreateInfoEXT
PipelineDiscardRectangleStateCreateInfoEXT
           PipelineDiscardRectangleStateCreateFlagsEXT
forall a. Zero a => a
zero
           DiscardRectangleModeEXT
forall a. Zero a => a
zero
           "discardRectangles" ::: Vector Rect2D
forall a. Monoid a => a
mempty


-- | VkPipelineDiscardRectangleStateCreateFlagsEXT - Reserved for future use
--
-- = Description
--
-- 'PipelineDiscardRectangleStateCreateFlagsEXT' is a bitmask type for
-- setting a mask, but is currently reserved for future use.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_discard_rectangles VK_EXT_discard_rectangles>,
-- 'PipelineDiscardRectangleStateCreateInfoEXT'
newtype PipelineDiscardRectangleStateCreateFlagsEXT = PipelineDiscardRectangleStateCreateFlagsEXT Flags
  deriving newtype (PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
(PipelineDiscardRectangleStateCreateFlagsEXT
 -> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool)
-> Eq PipelineDiscardRectangleStateCreateFlagsEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
== :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
$c/= :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
/= :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
Eq, Eq PipelineDiscardRectangleStateCreateFlagsEXT
Eq PipelineDiscardRectangleStateCreateFlagsEXT =>
(PipelineDiscardRectangleStateCreateFlagsEXT
 -> PipelineDiscardRectangleStateCreateFlagsEXT -> Ordering)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> Ord PipelineDiscardRectangleStateCreateFlagsEXT
PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Ordering
PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
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
$ccompare :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Ordering
compare :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Ordering
$c< :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
< :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
$c<= :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
<= :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
$c> :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
> :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
$c>= :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
>= :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
$cmax :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
max :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
$cmin :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
min :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
Ord, Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> IO PipelineDiscardRectangleStateCreateFlagsEXT
Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> IO PipelineDiscardRectangleStateCreateFlagsEXT
Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ()
Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ()
PipelineDiscardRectangleStateCreateFlagsEXT -> Int
(PipelineDiscardRectangleStateCreateFlagsEXT -> Int)
-> (PipelineDiscardRectangleStateCreateFlagsEXT -> Int)
-> (Ptr PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> IO PipelineDiscardRectangleStateCreateFlagsEXT)
-> (Ptr PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ())
-> (forall b.
    Ptr b -> Int -> IO PipelineDiscardRectangleStateCreateFlagsEXT)
-> (forall b.
    Ptr b
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ())
-> (Ptr PipelineDiscardRectangleStateCreateFlagsEXT
    -> IO PipelineDiscardRectangleStateCreateFlagsEXT)
-> (Ptr PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ())
-> Storable PipelineDiscardRectangleStateCreateFlagsEXT
forall b.
Ptr b -> Int -> IO PipelineDiscardRectangleStateCreateFlagsEXT
forall b.
Ptr b
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT -> 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
$csizeOf :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
sizeOf :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
$calignment :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
alignment :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
$cpeekElemOff :: Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> IO PipelineDiscardRectangleStateCreateFlagsEXT
peekElemOff :: Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> IO PipelineDiscardRectangleStateCreateFlagsEXT
$cpokeElemOff :: Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ()
pokeElemOff :: Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ()
$cpeekByteOff :: forall b.
Ptr b -> Int -> IO PipelineDiscardRectangleStateCreateFlagsEXT
peekByteOff :: forall b.
Ptr b -> Int -> IO PipelineDiscardRectangleStateCreateFlagsEXT
$cpokeByteOff :: forall b.
Ptr b
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ()
pokeByteOff :: forall b.
Ptr b
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ()
$cpeek :: Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> IO PipelineDiscardRectangleStateCreateFlagsEXT
peek :: Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> IO PipelineDiscardRectangleStateCreateFlagsEXT
$cpoke :: Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ()
poke :: Ptr PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT -> IO ()
Storable, PipelineDiscardRectangleStateCreateFlagsEXT
PipelineDiscardRectangleStateCreateFlagsEXT
-> Zero PipelineDiscardRectangleStateCreateFlagsEXT
forall a. a -> Zero a
$czero :: PipelineDiscardRectangleStateCreateFlagsEXT
zero :: PipelineDiscardRectangleStateCreateFlagsEXT
Zero, Eq PipelineDiscardRectangleStateCreateFlagsEXT
PipelineDiscardRectangleStateCreateFlagsEXT
Eq PipelineDiscardRectangleStateCreateFlagsEXT =>
(PipelineDiscardRectangleStateCreateFlagsEXT
 -> PipelineDiscardRectangleStateCreateFlagsEXT
 -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> (Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT -> Int -> Bool)
-> (PipelineDiscardRectangleStateCreateFlagsEXT -> Maybe Int)
-> (PipelineDiscardRectangleStateCreateFlagsEXT -> Int)
-> (PipelineDiscardRectangleStateCreateFlagsEXT -> Bool)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> Int -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> (PipelineDiscardRectangleStateCreateFlagsEXT -> Int)
-> Bits PipelineDiscardRectangleStateCreateFlagsEXT
Int -> PipelineDiscardRectangleStateCreateFlagsEXT
PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
PipelineDiscardRectangleStateCreateFlagsEXT -> Int
PipelineDiscardRectangleStateCreateFlagsEXT -> Maybe Int
PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
PipelineDiscardRectangleStateCreateFlagsEXT -> Int -> Bool
PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
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
$c.&. :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
.&. :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
$c.|. :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
.|. :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
$cxor :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
xor :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
$ccomplement :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
complement :: PipelineDiscardRectangleStateCreateFlagsEXT
-> PipelineDiscardRectangleStateCreateFlagsEXT
$cshift :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
shift :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$crotate :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
rotate :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$czeroBits :: PipelineDiscardRectangleStateCreateFlagsEXT
zeroBits :: PipelineDiscardRectangleStateCreateFlagsEXT
$cbit :: Int -> PipelineDiscardRectangleStateCreateFlagsEXT
bit :: Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$csetBit :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
setBit :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$cclearBit :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
clearBit :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$ccomplementBit :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
complementBit :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$ctestBit :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int -> Bool
testBit :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int -> Bool
$cbitSizeMaybe :: PipelineDiscardRectangleStateCreateFlagsEXT -> Maybe Int
bitSizeMaybe :: PipelineDiscardRectangleStateCreateFlagsEXT -> Maybe Int
$cbitSize :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
bitSize :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
$cisSigned :: PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
isSigned :: PipelineDiscardRectangleStateCreateFlagsEXT -> Bool
$cshiftL :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
shiftL :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$cunsafeShiftL :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
unsafeShiftL :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$cshiftR :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
shiftR :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$cunsafeShiftR :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
unsafeShiftR :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$crotateL :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
rotateL :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$crotateR :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
rotateR :: PipelineDiscardRectangleStateCreateFlagsEXT
-> Int -> PipelineDiscardRectangleStateCreateFlagsEXT
$cpopCount :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
popCount :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
Bits, Bits PipelineDiscardRectangleStateCreateFlagsEXT
Bits PipelineDiscardRectangleStateCreateFlagsEXT =>
(PipelineDiscardRectangleStateCreateFlagsEXT -> Int)
-> (PipelineDiscardRectangleStateCreateFlagsEXT -> Int)
-> (PipelineDiscardRectangleStateCreateFlagsEXT -> Int)
-> FiniteBits PipelineDiscardRectangleStateCreateFlagsEXT
PipelineDiscardRectangleStateCreateFlagsEXT -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
finiteBitSize :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
$ccountLeadingZeros :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
countLeadingZeros :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
$ccountTrailingZeros :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
countTrailingZeros :: PipelineDiscardRectangleStateCreateFlagsEXT -> Int
FiniteBits)

conNamePipelineDiscardRectangleStateCreateFlagsEXT :: String
conNamePipelineDiscardRectangleStateCreateFlagsEXT :: String
conNamePipelineDiscardRectangleStateCreateFlagsEXT = String
"PipelineDiscardRectangleStateCreateFlagsEXT"

enumPrefixPipelineDiscardRectangleStateCreateFlagsEXT :: String
enumPrefixPipelineDiscardRectangleStateCreateFlagsEXT :: String
enumPrefixPipelineDiscardRectangleStateCreateFlagsEXT = String
""

showTablePipelineDiscardRectangleStateCreateFlagsEXT :: [(PipelineDiscardRectangleStateCreateFlagsEXT, String)]
showTablePipelineDiscardRectangleStateCreateFlagsEXT :: [(PipelineDiscardRectangleStateCreateFlagsEXT, String)]
showTablePipelineDiscardRectangleStateCreateFlagsEXT = []

instance Show PipelineDiscardRectangleStateCreateFlagsEXT where
  showsPrec :: Int -> PipelineDiscardRectangleStateCreateFlagsEXT -> ShowS
showsPrec =
    String
-> [(PipelineDiscardRectangleStateCreateFlagsEXT, String)]
-> String
-> (PipelineDiscardRectangleStateCreateFlagsEXT
    -> "firstDiscardRectangle" ::: Word32)
-> (("firstDiscardRectangle" ::: Word32) -> ShowS)
-> Int
-> PipelineDiscardRectangleStateCreateFlagsEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixPipelineDiscardRectangleStateCreateFlagsEXT
      [(PipelineDiscardRectangleStateCreateFlagsEXT, String)]
showTablePipelineDiscardRectangleStateCreateFlagsEXT
      String
conNamePipelineDiscardRectangleStateCreateFlagsEXT
      (\(PipelineDiscardRectangleStateCreateFlagsEXT "firstDiscardRectangle" ::: Word32
x) -> "firstDiscardRectangle" ::: Word32
x)
      (\"firstDiscardRectangle" ::: Word32
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("firstDiscardRectangle" ::: Word32) -> ShowS
forall a. Integral a => a -> ShowS
showHex "firstDiscardRectangle" ::: Word32
x)

instance Read PipelineDiscardRectangleStateCreateFlagsEXT where
  readPrec :: ReadPrec PipelineDiscardRectangleStateCreateFlagsEXT
readPrec =
    String
-> [(PipelineDiscardRectangleStateCreateFlagsEXT, String)]
-> String
-> (("firstDiscardRectangle" ::: Word32)
    -> PipelineDiscardRectangleStateCreateFlagsEXT)
-> ReadPrec PipelineDiscardRectangleStateCreateFlagsEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixPipelineDiscardRectangleStateCreateFlagsEXT
      [(PipelineDiscardRectangleStateCreateFlagsEXT, String)]
showTablePipelineDiscardRectangleStateCreateFlagsEXT
      String
conNamePipelineDiscardRectangleStateCreateFlagsEXT
      ("firstDiscardRectangle" ::: Word32)
-> PipelineDiscardRectangleStateCreateFlagsEXT
PipelineDiscardRectangleStateCreateFlagsEXT

-- | VkDiscardRectangleModeEXT - Specify the discard rectangle mode
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_discard_rectangles VK_EXT_discard_rectangles>,
-- 'PipelineDiscardRectangleStateCreateInfoEXT',
-- 'cmdSetDiscardRectangleModeEXT'
newtype DiscardRectangleModeEXT = DiscardRectangleModeEXT Int32
  deriving newtype (DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
(DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool)
-> (DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool)
-> Eq DiscardRectangleModeEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
== :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
$c/= :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
/= :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
Eq, Eq DiscardRectangleModeEXT
Eq DiscardRectangleModeEXT =>
(DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Ordering)
-> (DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool)
-> (DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool)
-> (DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool)
-> (DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool)
-> (DiscardRectangleModeEXT
    -> DiscardRectangleModeEXT -> DiscardRectangleModeEXT)
-> (DiscardRectangleModeEXT
    -> DiscardRectangleModeEXT -> DiscardRectangleModeEXT)
-> Ord DiscardRectangleModeEXT
DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Ordering
DiscardRectangleModeEXT
-> DiscardRectangleModeEXT -> DiscardRectangleModeEXT
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
$ccompare :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Ordering
compare :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Ordering
$c< :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
< :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
$c<= :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
<= :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
$c> :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
> :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
$c>= :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
>= :: DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> Bool
$cmax :: DiscardRectangleModeEXT
-> DiscardRectangleModeEXT -> DiscardRectangleModeEXT
max :: DiscardRectangleModeEXT
-> DiscardRectangleModeEXT -> DiscardRectangleModeEXT
$cmin :: DiscardRectangleModeEXT
-> DiscardRectangleModeEXT -> DiscardRectangleModeEXT
min :: DiscardRectangleModeEXT
-> DiscardRectangleModeEXT -> DiscardRectangleModeEXT
Ord, Ptr DiscardRectangleModeEXT -> IO DiscardRectangleModeEXT
Ptr DiscardRectangleModeEXT -> Int -> IO DiscardRectangleModeEXT
Ptr DiscardRectangleModeEXT
-> Int -> DiscardRectangleModeEXT -> IO ()
Ptr DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> IO ()
DiscardRectangleModeEXT -> Int
(DiscardRectangleModeEXT -> Int)
-> (DiscardRectangleModeEXT -> Int)
-> (Ptr DiscardRectangleModeEXT
    -> Int -> IO DiscardRectangleModeEXT)
-> (Ptr DiscardRectangleModeEXT
    -> Int -> DiscardRectangleModeEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO DiscardRectangleModeEXT)
-> (forall b. Ptr b -> Int -> DiscardRectangleModeEXT -> IO ())
-> (Ptr DiscardRectangleModeEXT -> IO DiscardRectangleModeEXT)
-> (Ptr DiscardRectangleModeEXT
    -> DiscardRectangleModeEXT -> IO ())
-> Storable DiscardRectangleModeEXT
forall b. Ptr b -> Int -> IO DiscardRectangleModeEXT
forall b. Ptr b -> Int -> DiscardRectangleModeEXT -> 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
$csizeOf :: DiscardRectangleModeEXT -> Int
sizeOf :: DiscardRectangleModeEXT -> Int
$calignment :: DiscardRectangleModeEXT -> Int
alignment :: DiscardRectangleModeEXT -> Int
$cpeekElemOff :: Ptr DiscardRectangleModeEXT -> Int -> IO DiscardRectangleModeEXT
peekElemOff :: Ptr DiscardRectangleModeEXT -> Int -> IO DiscardRectangleModeEXT
$cpokeElemOff :: Ptr DiscardRectangleModeEXT
-> Int -> DiscardRectangleModeEXT -> IO ()
pokeElemOff :: Ptr DiscardRectangleModeEXT
-> Int -> DiscardRectangleModeEXT -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DiscardRectangleModeEXT
peekByteOff :: forall b. Ptr b -> Int -> IO DiscardRectangleModeEXT
$cpokeByteOff :: forall b. Ptr b -> Int -> DiscardRectangleModeEXT -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> DiscardRectangleModeEXT -> IO ()
$cpeek :: Ptr DiscardRectangleModeEXT -> IO DiscardRectangleModeEXT
peek :: Ptr DiscardRectangleModeEXT -> IO DiscardRectangleModeEXT
$cpoke :: Ptr DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> IO ()
poke :: Ptr DiscardRectangleModeEXT -> DiscardRectangleModeEXT -> IO ()
Storable, DiscardRectangleModeEXT
DiscardRectangleModeEXT -> Zero DiscardRectangleModeEXT
forall a. a -> Zero a
$czero :: DiscardRectangleModeEXT
zero :: DiscardRectangleModeEXT
Zero)

-- | 'DISCARD_RECTANGLE_MODE_INCLUSIVE_EXT' specifies that the discard
-- rectangle test is inclusive.
pattern $bDISCARD_RECTANGLE_MODE_INCLUSIVE_EXT :: DiscardRectangleModeEXT
$mDISCARD_RECTANGLE_MODE_INCLUSIVE_EXT :: forall {r}.
DiscardRectangleModeEXT -> ((# #) -> r) -> ((# #) -> r) -> r
DISCARD_RECTANGLE_MODE_INCLUSIVE_EXT = DiscardRectangleModeEXT 0

-- | 'DISCARD_RECTANGLE_MODE_EXCLUSIVE_EXT' specifies that the discard
-- rectangle test is exclusive.
pattern $bDISCARD_RECTANGLE_MODE_EXCLUSIVE_EXT :: DiscardRectangleModeEXT
$mDISCARD_RECTANGLE_MODE_EXCLUSIVE_EXT :: forall {r}.
DiscardRectangleModeEXT -> ((# #) -> r) -> ((# #) -> r) -> r
DISCARD_RECTANGLE_MODE_EXCLUSIVE_EXT = DiscardRectangleModeEXT 1

{-# COMPLETE
  DISCARD_RECTANGLE_MODE_INCLUSIVE_EXT
  , DISCARD_RECTANGLE_MODE_EXCLUSIVE_EXT ::
    DiscardRectangleModeEXT
  #-}

conNameDiscardRectangleModeEXT :: String
conNameDiscardRectangleModeEXT :: String
conNameDiscardRectangleModeEXT = String
"DiscardRectangleModeEXT"

enumPrefixDiscardRectangleModeEXT :: String
enumPrefixDiscardRectangleModeEXT :: String
enumPrefixDiscardRectangleModeEXT = String
"DISCARD_RECTANGLE_MODE_"

showTableDiscardRectangleModeEXT :: [(DiscardRectangleModeEXT, String)]
showTableDiscardRectangleModeEXT :: [(DiscardRectangleModeEXT, String)]
showTableDiscardRectangleModeEXT =
  [
    ( DiscardRectangleModeEXT
DISCARD_RECTANGLE_MODE_INCLUSIVE_EXT
    , String
"INCLUSIVE_EXT"
    )
  ,
    ( DiscardRectangleModeEXT
DISCARD_RECTANGLE_MODE_EXCLUSIVE_EXT
    , String
"EXCLUSIVE_EXT"
    )
  ]

instance Show DiscardRectangleModeEXT where
  showsPrec :: Int -> DiscardRectangleModeEXT -> ShowS
showsPrec =
    String
-> [(DiscardRectangleModeEXT, String)]
-> String
-> (DiscardRectangleModeEXT -> Int32)
-> (Int32 -> ShowS)
-> Int
-> DiscardRectangleModeEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixDiscardRectangleModeEXT
      [(DiscardRectangleModeEXT, String)]
showTableDiscardRectangleModeEXT
      String
conNameDiscardRectangleModeEXT
      (\(DiscardRectangleModeEXT Int32
x) -> Int32
x)
      (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read DiscardRectangleModeEXT where
  readPrec :: ReadPrec DiscardRectangleModeEXT
readPrec =
    String
-> [(DiscardRectangleModeEXT, String)]
-> String
-> (Int32 -> DiscardRectangleModeEXT)
-> ReadPrec DiscardRectangleModeEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixDiscardRectangleModeEXT
      [(DiscardRectangleModeEXT, String)]
showTableDiscardRectangleModeEXT
      String
conNameDiscardRectangleModeEXT
      Int32 -> DiscardRectangleModeEXT
DiscardRectangleModeEXT

type EXT_DISCARD_RECTANGLES_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_EXT_DISCARD_RECTANGLES_SPEC_VERSION"
pattern EXT_DISCARD_RECTANGLES_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DISCARD_RECTANGLES_SPEC_VERSION :: forall a. Integral a => a
$mEXT_DISCARD_RECTANGLES_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DISCARD_RECTANGLES_SPEC_VERSION = 2


type EXT_DISCARD_RECTANGLES_EXTENSION_NAME = "VK_EXT_discard_rectangles"

-- No documentation found for TopLevel "VK_EXT_DISCARD_RECTANGLES_EXTENSION_NAME"
pattern EXT_DISCARD_RECTANGLES_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DISCARD_RECTANGLES_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_DISCARD_RECTANGLES_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DISCARD_RECTANGLES_EXTENSION_NAME = "VK_EXT_discard_rectangles"