{-# language CPP #-}
module Vulkan.Extensions.VK_NV_scissor_exclusive  ( cmdSetExclusiveScissorNV
                                                  , PhysicalDeviceExclusiveScissorFeaturesNV(..)
                                                  , PipelineViewportExclusiveScissorStateCreateInfoNV(..)
                                                  , NV_SCISSOR_EXCLUSIVE_SPEC_VERSION
                                                  , pattern NV_SCISSOR_EXCLUSIVE_SPEC_VERSION
                                                  , NV_SCISSOR_EXCLUSIVE_EXTENSION_NAME
                                                  , pattern NV_SCISSOR_EXCLUSIVE_EXTENSION_NAME
                                                  ) where

import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetExclusiveScissorNV))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.FundamentalTypes (Rect2D)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_EXCLUSIVE_SCISSOR_FEATURES_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_VIEWPORT_EXCLUSIVE_SCISSOR_STATE_CREATE_INFO_NV))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdSetExclusiveScissorNV
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Rect2D -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Rect2D -> IO ()

-- | vkCmdSetExclusiveScissorNV - Set the dynamic exclusive scissor
-- rectangles on a command buffer
--
-- = Description
--
-- The scissor rectangles taken from element i of @pExclusiveScissors@
-- replace the current state for the scissor index @firstExclusiveScissor@
-- + i, for i in [0, @exclusiveScissorCount@).
--
-- This command sets the state for a given draw when the graphics pipeline
-- is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
--
-- == Valid Usage
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-exclusiveScissor exclusive scissor>
--     feature /must/ be enabled
--
-- -   @firstExclusiveScissor@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@
--
-- -   The sum of @firstExclusiveScissor@ and @exclusiveScissorCount@
--     /must/ be between @1@ and
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@,
--     inclusive
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports>
--     feature is not enabled, @firstExclusiveScissor@ /must/ be @0@
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports>
--     feature is not enabled, @exclusiveScissorCount@ /must/ be @1@
--
-- -   The @x@ and @y@ members of @offset@ in each member of
--     @pExclusiveScissors@ /must/ be greater than or equal to @0@
--
-- -   Evaluation of (@offset.x@ + @extent.width@) for each member of
--     @pExclusiveScissors@ /must/ not cause a signed integer addition
--     overflow
--
-- -   Evaluation of (@offset.y@ + @extent.height@) for each member of
--     @pExclusiveScissors@ /must/ not cause a signed integer addition
--     overflow
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pExclusiveScissors@ /must/ be a valid pointer to an array of
--     @exclusiveScissorCount@ 'Vulkan.Core10.FundamentalTypes.Rect2D'
--     structures
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   @exclusiveScissorCount@ /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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.Rect2D'
cmdSetExclusiveScissorNV :: forall io
                          . (MonadIO io)
                         => -- | @commandBuffer@ is the command buffer into which the command will be
                            -- recorded.
                            CommandBuffer
                         -> -- | @firstExclusiveScissor@ is the index of the first exclusive scissor
                            -- rectangle whose state is updated by the command.
                            ("firstExclusiveScissor" ::: Word32)
                         -> -- | @pExclusiveScissors@ is a pointer to an array of
                            -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures defining exclusive
                            -- scissor rectangles.
                            ("exclusiveScissors" ::: Vector Rect2D)
                         -> io ()
cmdSetExclusiveScissorNV :: CommandBuffer
-> ("firstExclusiveScissor" ::: Word32)
-> ("exclusiveScissors" ::: Vector Rect2D)
-> io ()
cmdSetExclusiveScissorNV commandBuffer :: CommandBuffer
commandBuffer firstExclusiveScissor :: "firstExclusiveScissor" ::: Word32
firstExclusiveScissor exclusiveScissors :: "exclusiveScissors" ::: Vector Rect2D
exclusiveScissors = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetExclusiveScissorNVPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("pExclusiveScissors" ::: Ptr Rect2D)
   -> IO ())
vkCmdSetExclusiveScissorNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstExclusiveScissor" ::: Word32)
      -> ("firstExclusiveScissor" ::: Word32)
      -> ("pExclusiveScissors" ::: Ptr Rect2D)
      -> IO ())
pVkCmdSetExclusiveScissorNV (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("pExclusiveScissors" ::: Ptr Rect2D)
   -> IO ())
vkCmdSetExclusiveScissorNVPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("pExclusiveScissors" ::: Ptr Rect2D)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstExclusiveScissor" ::: Word32)
      -> ("firstExclusiveScissor" ::: Word32)
      -> ("pExclusiveScissors" ::: Ptr Rect2D)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("pExclusiveScissors" ::: 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 "" "The function pointer for vkCmdSetExclusiveScissorNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetExclusiveScissorNV' :: Ptr CommandBuffer_T
-> ("firstExclusiveScissor" ::: Word32)
-> ("firstExclusiveScissor" ::: Word32)
-> ("pExclusiveScissors" ::: Ptr Rect2D)
-> IO ()
vkCmdSetExclusiveScissorNV' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("pExclusiveScissors" ::: Ptr Rect2D)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstExclusiveScissor" ::: Word32)
-> ("firstExclusiveScissor" ::: Word32)
-> ("pExclusiveScissors" ::: Ptr Rect2D)
-> IO ()
mkVkCmdSetExclusiveScissorNV FunPtr
  (Ptr CommandBuffer_T
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("firstExclusiveScissor" ::: Word32)
   -> ("pExclusiveScissors" ::: Ptr Rect2D)
   -> IO ())
vkCmdSetExclusiveScissorNVPtr
  "pExclusiveScissors" ::: Ptr Rect2D
pPExclusiveScissors <- ((("pExclusiveScissors" ::: Ptr Rect2D) -> IO ()) -> IO ())
-> ContT () IO ("pExclusiveScissors" ::: Ptr Rect2D)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pExclusiveScissors" ::: Ptr Rect2D) -> IO ()) -> IO ())
 -> ContT () IO ("pExclusiveScissors" ::: Ptr Rect2D))
-> ((("pExclusiveScissors" ::: Ptr Rect2D) -> IO ()) -> IO ())
-> ContT () IO ("pExclusiveScissors" ::: Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pExclusiveScissors" ::: Ptr Rect2D) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Rect2D ((("exclusiveScissors" ::: Vector Rect2D) -> Int
forall a. Vector a -> Int
Data.Vector.length ("exclusiveScissors" ::: Vector Rect2D
exclusiveScissors)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 4
  (Int -> Rect2D -> ContT () IO ())
-> ("exclusiveScissors" ::: Vector Rect2D) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Rect2D
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pExclusiveScissors" ::: Ptr Rect2D) -> Rect2D -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pExclusiveScissors" ::: Ptr Rect2D
pPExclusiveScissors ("pExclusiveScissors" ::: Ptr Rect2D)
-> Int -> "pExclusiveScissors" ::: Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D) (Rect2D
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("exclusiveScissors" ::: Vector Rect2D
exclusiveScissors)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("firstExclusiveScissor" ::: Word32)
-> ("firstExclusiveScissor" ::: Word32)
-> ("pExclusiveScissors" ::: Ptr Rect2D)
-> IO ()
vkCmdSetExclusiveScissorNV' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("firstExclusiveScissor" ::: Word32
firstExclusiveScissor) ((Int -> "firstExclusiveScissor" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("exclusiveScissors" ::: Vector Rect2D) -> Int
forall a. Vector a -> Int
Data.Vector.length (("exclusiveScissors" ::: Vector Rect2D) -> Int)
-> ("exclusiveScissors" ::: Vector Rect2D) -> Int
forall a b. (a -> b) -> a -> b
$ ("exclusiveScissors" ::: Vector Rect2D
exclusiveScissors)) :: Word32)) ("pExclusiveScissors" ::: Ptr Rect2D
pPExclusiveScissors)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkPhysicalDeviceExclusiveScissorFeaturesNV - Structure describing
-- exclusive scissor features that can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceExclusiveScissorFeaturesNV' structure
-- describe the following features:
--
-- = Description
--
-- See
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-exclusive-scissor Exclusive Scissor Test>
-- for more information.
--
-- If the 'PhysicalDeviceExclusiveScissorFeaturesNV' structure is included
-- in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether the feature is supported.
-- 'PhysicalDeviceExclusiveScissorFeaturesNV' /can/ also be included in the
-- @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable the
-- feature.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceExclusiveScissorFeaturesNV = PhysicalDeviceExclusiveScissorFeaturesNV
  { -- | @exclusiveScissor@ indicates that the implementation supports the
    -- exclusive scissor test.
    PhysicalDeviceExclusiveScissorFeaturesNV -> Bool
exclusiveScissor :: Bool }
  deriving (Typeable, PhysicalDeviceExclusiveScissorFeaturesNV
-> PhysicalDeviceExclusiveScissorFeaturesNV -> Bool
(PhysicalDeviceExclusiveScissorFeaturesNV
 -> PhysicalDeviceExclusiveScissorFeaturesNV -> Bool)
-> (PhysicalDeviceExclusiveScissorFeaturesNV
    -> PhysicalDeviceExclusiveScissorFeaturesNV -> Bool)
-> Eq PhysicalDeviceExclusiveScissorFeaturesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceExclusiveScissorFeaturesNV
-> PhysicalDeviceExclusiveScissorFeaturesNV -> Bool
$c/= :: PhysicalDeviceExclusiveScissorFeaturesNV
-> PhysicalDeviceExclusiveScissorFeaturesNV -> Bool
== :: PhysicalDeviceExclusiveScissorFeaturesNV
-> PhysicalDeviceExclusiveScissorFeaturesNV -> Bool
$c== :: PhysicalDeviceExclusiveScissorFeaturesNV
-> PhysicalDeviceExclusiveScissorFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceExclusiveScissorFeaturesNV)
#endif
deriving instance Show PhysicalDeviceExclusiveScissorFeaturesNV

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

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

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

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


-- | VkPipelineViewportExclusiveScissorStateCreateInfoNV - Structure
-- specifying parameters controlling exclusive scissor testing
--
-- = Description
--
-- If the
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV'
-- dynamic state is enabled for a pipeline, the @pExclusiveScissors@ member
-- is ignored.
--
-- When this structure is included in the @pNext@ chain of
-- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo', it defines
-- parameters of the exclusive scissor test. If this structure is not
-- included in the @pNext@ chain, it is equivalent to specifying this
-- structure with a @exclusiveScissorCount@ of @0@.
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports>
--     feature is not enabled, @exclusiveScissorCount@ /must/ be @0@ or @1@
--
-- -   @exclusiveScissorCount@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@
--
-- -   @exclusiveScissorCount@ /must/ be @0@ or greater than or equal to
--     the @viewportCount@ member of
--     'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_VIEWPORT_EXCLUSIVE_SCISSOR_STATE_CREATE_INFO_NV'
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Rect2D',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineViewportExclusiveScissorStateCreateInfoNV = PipelineViewportExclusiveScissorStateCreateInfoNV
  { -- | @pExclusiveScissors@ is a pointer to an array of
    -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures defining exclusive
    -- scissor rectangles.
    PipelineViewportExclusiveScissorStateCreateInfoNV
-> "exclusiveScissors" ::: Vector Rect2D
exclusiveScissors :: Vector Rect2D }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineViewportExclusiveScissorStateCreateInfoNV)
#endif
deriving instance Show PipelineViewportExclusiveScissorStateCreateInfoNV

instance ToCStruct PipelineViewportExclusiveScissorStateCreateInfoNV where
  withCStruct :: PipelineViewportExclusiveScissorStateCreateInfoNV
-> (Ptr PipelineViewportExclusiveScissorStateCreateInfoNV -> IO b)
-> IO b
withCStruct x :: PipelineViewportExclusiveScissorStateCreateInfoNV
x f :: Ptr PipelineViewportExclusiveScissorStateCreateInfoNV -> IO b
f = Int
-> Int
-> (Ptr PipelineViewportExclusiveScissorStateCreateInfoNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PipelineViewportExclusiveScissorStateCreateInfoNV -> IO b)
 -> IO b)
-> (Ptr PipelineViewportExclusiveScissorStateCreateInfoNV -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p -> Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> PipelineViewportExclusiveScissorStateCreateInfoNV
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p PipelineViewportExclusiveScissorStateCreateInfoNV
x (Ptr PipelineViewportExclusiveScissorStateCreateInfoNV -> IO b
f Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p)
  pokeCStruct :: Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> PipelineViewportExclusiveScissorStateCreateInfoNV
-> IO b
-> IO b
pokeCStruct p :: Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p PipelineViewportExclusiveScissorStateCreateInfoNV{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_VIEWPORT_EXCLUSIVE_SCISSOR_STATE_CREATE_INFO_NV)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("firstExclusiveScissor" ::: Word32)
-> ("firstExclusiveScissor" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> Int -> Ptr ("firstExclusiveScissor" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> "firstExclusiveScissor" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("exclusiveScissors" ::: Vector Rect2D) -> Int
forall a. Vector a -> Int
Data.Vector.length (("exclusiveScissors" ::: Vector Rect2D) -> Int)
-> ("exclusiveScissors" ::: Vector Rect2D) -> Int
forall a b. (a -> b) -> a -> b
$ ("exclusiveScissors" ::: Vector Rect2D
exclusiveScissors)) :: Word32))
    "pExclusiveScissors" ::: Ptr Rect2D
pPExclusiveScissors' <- ((("pExclusiveScissors" ::: Ptr Rect2D) -> IO b) -> IO b)
-> ContT b IO ("pExclusiveScissors" ::: Ptr Rect2D)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pExclusiveScissors" ::: Ptr Rect2D) -> IO b) -> IO b)
 -> ContT b IO ("pExclusiveScissors" ::: Ptr Rect2D))
-> ((("pExclusiveScissors" ::: Ptr Rect2D) -> IO b) -> IO b)
-> ContT b IO ("pExclusiveScissors" ::: Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pExclusiveScissors" ::: Ptr Rect2D) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Rect2D ((("exclusiveScissors" ::: Vector Rect2D) -> Int
forall a. Vector a -> Int
Data.Vector.length ("exclusiveScissors" ::: Vector Rect2D
exclusiveScissors)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 4
    (Int -> Rect2D -> ContT b IO ())
-> ("exclusiveScissors" ::: Vector Rect2D) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Rect2D
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pExclusiveScissors" ::: Ptr Rect2D) -> Rect2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pExclusiveScissors" ::: Ptr Rect2D
pPExclusiveScissors' ("pExclusiveScissors" ::: Ptr Rect2D)
-> Int -> "pExclusiveScissors" ::: Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D) (Rect2D
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) ("exclusiveScissors" ::: Vector Rect2D
exclusiveScissors)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pExclusiveScissors" ::: Ptr Rect2D)
-> ("pExclusiveScissors" ::: Ptr Rect2D) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> Int -> Ptr ("pExclusiveScissors" ::: Ptr Rect2D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Rect2D))) ("pExclusiveScissors" ::: Ptr Rect2D
pPExclusiveScissors')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> IO b -> IO b
pokeZeroCStruct p :: Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_VIEWPORT_EXCLUSIVE_SCISSOR_STATE_CREATE_INFO_NV)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    "pExclusiveScissors" ::: Ptr Rect2D
pPExclusiveScissors' <- ((("pExclusiveScissors" ::: Ptr Rect2D) -> IO b) -> IO b)
-> ContT b IO ("pExclusiveScissors" ::: Ptr Rect2D)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pExclusiveScissors" ::: Ptr Rect2D) -> IO b) -> IO b)
 -> ContT b IO ("pExclusiveScissors" ::: Ptr Rect2D))
-> ((("pExclusiveScissors" ::: Ptr Rect2D) -> IO b) -> IO b)
-> ContT b IO ("pExclusiveScissors" ::: Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pExclusiveScissors" ::: Ptr Rect2D) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Rect2D ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 4
    (Int -> Rect2D -> ContT b IO ())
-> ("exclusiveScissors" ::: Vector Rect2D) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Rect2D
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pExclusiveScissors" ::: Ptr Rect2D) -> Rect2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pExclusiveScissors" ::: Ptr Rect2D
pPExclusiveScissors' ("pExclusiveScissors" ::: Ptr Rect2D)
-> Int -> "pExclusiveScissors" ::: Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D) (Rect2D
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) ("exclusiveScissors" ::: Vector Rect2D
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pExclusiveScissors" ::: Ptr Rect2D)
-> ("pExclusiveScissors" ::: Ptr Rect2D) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> Int -> Ptr ("pExclusiveScissors" ::: Ptr Rect2D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Rect2D))) ("pExclusiveScissors" ::: Ptr Rect2D
pPExclusiveScissors')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct PipelineViewportExclusiveScissorStateCreateInfoNV where
  peekCStruct :: Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> IO PipelineViewportExclusiveScissorStateCreateInfoNV
peekCStruct p :: Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p = do
    "firstExclusiveScissor" ::: Word32
exclusiveScissorCount <- Ptr ("firstExclusiveScissor" ::: Word32)
-> IO ("firstExclusiveScissor" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> Int -> Ptr ("firstExclusiveScissor" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "pExclusiveScissors" ::: Ptr Rect2D
pExclusiveScissors <- Ptr ("pExclusiveScissors" ::: Ptr Rect2D)
-> IO ("pExclusiveScissors" ::: Ptr Rect2D)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Rect2D) ((Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
p Ptr PipelineViewportExclusiveScissorStateCreateInfoNV
-> Int -> Ptr ("pExclusiveScissors" ::: Ptr Rect2D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Rect2D)))
    "exclusiveScissors" ::: Vector Rect2D
pExclusiveScissors' <- Int
-> (Int -> IO Rect2D) -> IO ("exclusiveScissors" ::: Vector Rect2D)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("firstExclusiveScissor" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "firstExclusiveScissor" ::: Word32
exclusiveScissorCount) (\i :: Int
i -> ("pExclusiveScissors" ::: Ptr Rect2D) -> IO Rect2D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Rect2D (("pExclusiveScissors" ::: Ptr Rect2D
pExclusiveScissors ("pExclusiveScissors" ::: Ptr Rect2D)
-> Int -> "pExclusiveScissors" ::: Ptr Rect2D
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D)))
    PipelineViewportExclusiveScissorStateCreateInfoNV
-> IO PipelineViewportExclusiveScissorStateCreateInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineViewportExclusiveScissorStateCreateInfoNV
 -> IO PipelineViewportExclusiveScissorStateCreateInfoNV)
-> PipelineViewportExclusiveScissorStateCreateInfoNV
-> IO PipelineViewportExclusiveScissorStateCreateInfoNV
forall a b. (a -> b) -> a -> b
$ ("exclusiveScissors" ::: Vector Rect2D)
-> PipelineViewportExclusiveScissorStateCreateInfoNV
PipelineViewportExclusiveScissorStateCreateInfoNV
             "exclusiveScissors" ::: Vector Rect2D
pExclusiveScissors'

instance Zero PipelineViewportExclusiveScissorStateCreateInfoNV where
  zero :: PipelineViewportExclusiveScissorStateCreateInfoNV
zero = ("exclusiveScissors" ::: Vector Rect2D)
-> PipelineViewportExclusiveScissorStateCreateInfoNV
PipelineViewportExclusiveScissorStateCreateInfoNV
           "exclusiveScissors" ::: Vector Rect2D
forall a. Monoid a => a
mempty


type NV_SCISSOR_EXCLUSIVE_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_NV_SCISSOR_EXCLUSIVE_SPEC_VERSION"
pattern NV_SCISSOR_EXCLUSIVE_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_SCISSOR_EXCLUSIVE_SPEC_VERSION :: a
$mNV_SCISSOR_EXCLUSIVE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_SCISSOR_EXCLUSIVE_SPEC_VERSION = 1


type NV_SCISSOR_EXCLUSIVE_EXTENSION_NAME = "VK_NV_scissor_exclusive"

-- No documentation found for TopLevel "VK_NV_SCISSOR_EXCLUSIVE_EXTENSION_NAME"
pattern NV_SCISSOR_EXCLUSIVE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_SCISSOR_EXCLUSIVE_EXTENSION_NAME :: a
$mNV_SCISSOR_EXCLUSIVE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_SCISSOR_EXCLUSIVE_EXTENSION_NAME = "VK_NV_scissor_exclusive"