{-# language CPP #-}
-- | = Name
--
-- VK_NV_clip_space_w_scaling - device extension
--
-- == VK_NV_clip_space_w_scaling
--
-- [__Name String__]
--     @VK_NV_clip_space_w_scaling@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     88
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
-- [__Contact__]
--
--     -   Eric Werness
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_NV_clip_space_w_scaling] @ewerness-nv%0A*Here describe the issue or question you have about the VK_NV_clip_space_w_scaling extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2017-02-15
--
-- [__Contributors__]
--
--     -   Eric Werness, NVIDIA
--
--     -   Kedarnath Thangudu, NVIDIA
--
-- == Description
--
-- Virtual Reality (VR) applications often involve a post-processing step
-- to apply a “barrel” distortion to the rendered image to correct the
-- “pincushion” distortion introduced by the optics in a VR device. The
-- barrel distorted image has lower resolution along the edges compared to
-- the center. Since the original image is rendered at high resolution,
-- which is uniform across the complete image, a lot of pixels towards the
-- edges do not make it to the final post-processed image.
--
-- This extension provides a mechanism to render VR scenes at a non-uniform
-- resolution, in particular a resolution that falls linearly from the
-- center towards the edges. This is achieved by scaling the w coordinate
-- of the vertices in the clip space before perspective divide. The clip
-- space w coordinate of the vertices /can/ be offset as of a function of x
-- and y coordinates as follows:
--
-- w\' = w + Ax + By
--
-- In the intended use case for viewport position scaling, an application
-- should use a set of four viewports, one for each of the four quadrants
-- of a Cartesian coordinate system. Each viewport is set to the dimension
-- of the image, but is scissored to the quadrant it represents. The
-- application should specify A and B coefficients of the w-scaling
-- equation above, that have the same value, but different signs, for each
-- of the viewports. The signs of A and B should match the signs of x and y
-- for the quadrant that they represent such that the value of w\' will
-- always be greater than or equal to the original w value for the entire
-- image. Since the offset to w, (Ax + By), is always positive, and
-- increases with the absolute values of x and y, the effective resolution
-- will fall off linearly from the center of the image to its edges.
--
-- == New Commands
--
-- -   'cmdSetViewportWScalingNV'
--
-- == New Structures
--
-- -   'ViewportWScalingNV'
--
-- -   Extending 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo':
--
--     -   'PipelineViewportWScalingStateCreateInfoNV'
--
-- == New Enum Constants
--
-- -   'NV_CLIP_SPACE_W_SCALING_EXTENSION_NAME'
--
-- -   'NV_CLIP_SPACE_W_SCALING_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.DynamicState.DynamicState':
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_VIEWPORT_W_SCALING_STATE_CREATE_INFO_NV'
--
-- == Issues
--
-- 1) Is the pipeline struct name too long?
--
-- __RESOLVED__: It fits with the naming convention.
--
-- 2) Separate W scaling section or fold into coordinate transformations?
--
-- __RESOLVED__: Leaving it as its own section for now.
--
-- == Examples
--
-- > VkViewport viewports[4];
-- > VkRect2D scissors[4];
-- > VkViewportWScalingNV scalings[4];
-- >
-- > for (int i = 0; i < 4; i++) {
-- >     int x = (i & 2) ? 0 : currentWindowWidth / 2;
-- >     int y = (i & 1) ? 0 : currentWindowHeight / 2;
-- >
-- >     viewports[i].x = 0;
-- >     viewports[i].y = 0;
-- >     viewports[i].width = currentWindowWidth;
-- >     viewports[i].height = currentWindowHeight;
-- >     viewports[i].minDepth = 0.0f;
-- >     viewports[i].maxDepth = 1.0f;
-- >
-- >     scissors[i].offset.x = x;
-- >     scissors[i].offset.y = y;
-- >     scissors[i].extent.width = currentWindowWidth/2;
-- >     scissors[i].extent.height = currentWindowHeight/2;
-- >
-- >     const float factor = 0.15;
-- >     scalings[i].xcoeff = ((i & 2) ? -1.0 : 1.0) * factor;
-- >     scalings[i].ycoeff = ((i & 1) ? -1.0 : 1.0) * factor;
-- > }
-- >
-- > VkPipelineViewportWScalingStateCreateInfoNV vpWScalingStateInfo = { VK_STRUCTURE_TYPE_PIPELINE_VIEWPORT_W_SCALING_STATE_CREATE_INFO_NV };
-- >
-- > vpWScalingStateInfo.viewportWScalingEnable = VK_TRUE;
-- > vpWScalingStateInfo.viewportCount = 4;
-- > vpWScalingStateInfo.pViewportWScalings = &scalings[0];
-- >
-- > VkPipelineViewportStateCreateInfo vpStateInfo = { VK_STRUCTURE_TYPE_PIPELINE_VIEWPORT_STATE_CREATE_INFO };
-- > vpStateInfo.viewportCount = 4;
-- > vpStateInfo.pViewports = &viewports[0];
-- > vpStateInfo.scissorCount = 4;
-- > vpStateInfo.pScissors = &scissors[0];
-- > vpStateInfo.pNext = &vpWScalingStateInfo;
--
-- Example shader to read from a w-scaled texture:
--
-- > // Vertex Shader
-- > // Draw a triangle that covers the whole screen
-- > const vec4 positions[3] = vec4[3](vec4(-1, -1, 0, 1),
-- >                                   vec4( 3, -1, 0, 1),
-- >                                   vec4(-1,  3, 0, 1));
-- > out vec2 uv;
-- > void main()
-- > {
-- >     vec4 pos = positions[ gl_VertexID ];
-- >     gl_Position = pos;
-- >     uv = pos.xy;
-- > }
-- >
-- > // Fragment Shader
-- > uniform sampler2D tex;
-- > uniform float xcoeff;
-- > uniform float ycoeff;
-- > out vec4 Color;
-- > in vec2 uv;
-- >
-- > void main()
-- > {
-- >     // Handle uv as if upper right quadrant
-- >     vec2 uvabs = abs(uv);
-- >
-- >     // unscale: transform w-scaled image into an unscaled image
-- >     //   scale: transform unscaled image int a w-scaled image
-- >     float unscale = 1.0 / (1 + xcoeff * uvabs.x + xcoeff * uvabs.y);
-- >     //float scale = 1.0 / (1 - xcoeff * uvabs.x - xcoeff * uvabs.y);
-- >
-- >     vec2 P = vec2(unscale * uvabs.x, unscale * uvabs.y);
-- >
-- >     // Go back to the right quadrant
-- >     P *= sign(uv);
-- >
-- >     Color = texture(tex, P * 0.5 + 0.5);
-- > }
--
-- == Version History
--
-- -   Revision 1, 2017-02-15 (Eric Werness)
--
--     -   Internal revisions
--
-- == See Also
--
-- 'PipelineViewportWScalingStateCreateInfoNV', 'ViewportWScalingNV',
-- 'cmdSetViewportWScalingNV'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_NV_clip_space_w_scaling Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_NV_clip_space_w_scaling  ( cmdSetViewportWScalingNV
                                                     , ViewportWScalingNV(..)
                                                     , PipelineViewportWScalingStateCreateInfoNV(..)
                                                     , NV_CLIP_SPACE_W_SCALING_SPEC_VERSION
                                                     , pattern NV_CLIP_SPACE_W_SCALING_SPEC_VERSION
                                                     , NV_CLIP_SPACE_W_SCALING_EXTENSION_NAME
                                                     , pattern NV_CLIP_SPACE_W_SCALING_EXTENSION_NAME
                                                     ) where

import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.Coerce (coerce)
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 qualified Data.Vector (null)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(..))
import Foreign.C.Types (CFloat(CFloat))
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(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetViewportWScalingNV))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_VIEWPORT_W_SCALING_STATE_CREATE_INFO_NV))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdSetViewportWScalingNV
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr ViewportWScalingNV -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr ViewportWScalingNV -> IO ()

-- | vkCmdSetViewportWScalingNV - Set the viewport W scaling dynamically for
-- a command buffer
--
-- = Description
--
-- The viewport parameters taken from element i of @pViewportWScalings@
-- replace the current state for the viewport index @firstViewport@ + i,
-- for i in [0, @viewportCount@).
--
-- This command sets the viewport __W__ scaling for subsequent drawing
-- commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'PipelineViewportWScalingStateCreateInfoNV'::@pViewportWScalings@ values
-- used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetViewportWScalingNV-firstViewport-01324# The sum of
--     @firstViewport@ and @viewportCount@ /must/ be between @1@ and
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@,
--     inclusive
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetViewportWScalingNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetViewportWScalingNV-pViewportWScalings-parameter#
--     @pViewportWScalings@ /must/ be a valid pointer to an array of
--     @viewportCount@ 'ViewportWScalingNV' structures
--
-- -   #VUID-vkCmdSetViewportWScalingNV-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-vkCmdSetViewportWScalingNV-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetViewportWScalingNV-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- -   #VUID-vkCmdSetViewportWScalingNV-viewportCount-arraylength#
--     @viewportCount@ /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_NV_clip_space_w_scaling VK_NV_clip_space_w_scaling>,
-- 'Vulkan.Core10.Handles.CommandBuffer', 'ViewportWScalingNV'
cmdSetViewportWScalingNV :: forall io
                          . (MonadIO io)
                         => -- | @commandBuffer@ is the command buffer into which the command will be
                            -- recorded.
                            CommandBuffer
                         -> -- | @firstViewport@ is the index of the first viewport whose parameters are
                            -- updated by the command.
                            ("firstViewport" ::: Word32)
                         -> -- | @pViewportWScalings@ is a pointer to an array of 'ViewportWScalingNV'
                            -- structures specifying viewport parameters.
                            ("viewportWScalings" ::: Vector ViewportWScalingNV)
                         -> io ()
cmdSetViewportWScalingNV :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> ("firstViewport" ::: Word32)
-> ("viewportWScalings" ::: Vector ViewportWScalingNV)
-> io ()
cmdSetViewportWScalingNV CommandBuffer
commandBuffer
                           "firstViewport" ::: Word32
firstViewport
                           "viewportWScalings" ::: Vector ViewportWScalingNV
viewportWScalings = 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 vkCmdSetViewportWScalingNVPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
   -> IO ())
vkCmdSetViewportWScalingNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
      -> IO ())
pVkCmdSetViewportWScalingNV (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
   -> IO ())
vkCmdSetViewportWScalingNVPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("firstViewport" ::: Word32)
      -> ("firstViewport" ::: Word32)
      -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
   -> 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 vkCmdSetViewportWScalingNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetViewportWScalingNV' :: Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> IO ()
vkCmdSetViewportWScalingNV' = FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> IO ()
mkVkCmdSetViewportWScalingNV FunPtr
  (Ptr CommandBuffer_T
   -> ("firstViewport" ::: Word32)
   -> ("firstViewport" ::: Word32)
   -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
   -> IO ())
vkCmdSetViewportWScalingNVPtr
  "pViewportWScalings" ::: Ptr ViewportWScalingNV
pPViewportWScalings <- ((("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO ())
 -> IO ())
-> ContT () IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO ())
  -> IO ())
 -> ContT () IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV))
-> ((("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO ())
    -> IO ())
-> ContT () IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @ViewportWScalingNV ((("viewportWScalings" ::: Vector ViewportWScalingNV) -> Int
forall a. Vector a -> Int
Data.Vector.length ("viewportWScalings" ::: Vector ViewportWScalingNV
viewportWScalings)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> ViewportWScalingNV -> IO ())
-> ("viewportWScalings" ::: Vector ViewportWScalingNV) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i ViewportWScalingNV
e -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ViewportWScalingNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pViewportWScalings" ::: Ptr ViewportWScalingNV
pPViewportWScalings ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> "pViewportWScalings" ::: Ptr ViewportWScalingNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ViewportWScalingNV) (ViewportWScalingNV
e)) ("viewportWScalings" ::: Vector ViewportWScalingNV
viewportWScalings)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetViewportWScalingNV" (Ptr CommandBuffer_T
-> ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32)
-> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> IO ()
vkCmdSetViewportWScalingNV'
                                                          (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                          ("firstViewport" ::: Word32
firstViewport)
                                                          ((Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("viewportWScalings" ::: Vector ViewportWScalingNV) -> Int
forall a. Vector a -> Int
Data.Vector.length (("viewportWScalings" ::: Vector ViewportWScalingNV) -> Int)
-> ("viewportWScalings" ::: Vector ViewportWScalingNV) -> Int
forall a b. (a -> b) -> a -> b
$ ("viewportWScalings" ::: Vector ViewportWScalingNV
viewportWScalings)) :: Word32))
                                                          ("pViewportWScalings" ::: Ptr ViewportWScalingNV
pPViewportWScalings))
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkViewportWScalingNV - Structure specifying a viewport
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_clip_space_w_scaling VK_NV_clip_space_w_scaling>,
-- 'PipelineViewportWScalingStateCreateInfoNV', 'cmdSetViewportWScalingNV'
data ViewportWScalingNV = ViewportWScalingNV
  { -- | @xcoeff@ and @ycoeff@ are the viewport’s W scaling factor for x and y
    -- respectively.
    ViewportWScalingNV -> Float
xcoeff :: Float
  , -- No documentation found for Nested "VkViewportWScalingNV" "ycoeff"
    ViewportWScalingNV -> Float
ycoeff :: Float
  }
  deriving (Typeable, ViewportWScalingNV -> ViewportWScalingNV -> Bool
(ViewportWScalingNV -> ViewportWScalingNV -> Bool)
-> (ViewportWScalingNV -> ViewportWScalingNV -> Bool)
-> Eq ViewportWScalingNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ViewportWScalingNV -> ViewportWScalingNV -> Bool
$c/= :: ViewportWScalingNV -> ViewportWScalingNV -> Bool
== :: ViewportWScalingNV -> ViewportWScalingNV -> Bool
$c== :: ViewportWScalingNV -> ViewportWScalingNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ViewportWScalingNV)
#endif
deriving instance Show ViewportWScalingNV

instance ToCStruct ViewportWScalingNV where
  withCStruct :: forall b.
ViewportWScalingNV
-> (("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
-> IO b
withCStruct ViewportWScalingNV
x ("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b
f = Int
-> (("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
8 ((("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
 -> IO b)
-> (("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \"pViewportWScalings" ::: Ptr ViewportWScalingNV
p -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ViewportWScalingNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pViewportWScalings" ::: Ptr ViewportWScalingNV
p ViewportWScalingNV
x (("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b
f "pViewportWScalings" ::: Ptr ViewportWScalingNV
p)
  pokeCStruct :: forall b.
("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ViewportWScalingNV -> IO b -> IO b
pokeCStruct "pViewportWScalings" ::: Ptr ViewportWScalingNV
p ViewportWScalingNV{Float
ycoeff :: Float
xcoeff :: Float
$sel:ycoeff:ViewportWScalingNV :: ViewportWScalingNV -> Float
$sel:xcoeff:ViewportWScalingNV :: ViewportWScalingNV -> Float
..} IO b
f = do
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pViewportWScalings" ::: Ptr ViewportWScalingNV
p ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
xcoeff))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pViewportWScalings" ::: Ptr ViewportWScalingNV
p ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
ycoeff))
    IO b
f
  cStructSize :: Int
cStructSize = Int
8
  cStructAlignment :: Int
cStructAlignment = Int
4
  pokeZeroCStruct :: forall b.
("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b -> IO b
pokeZeroCStruct "pViewportWScalings" ::: Ptr ViewportWScalingNV
p IO b
f = do
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pViewportWScalings" ::: Ptr ViewportWScalingNV
p ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pViewportWScalings" ::: Ptr ViewportWScalingNV
p ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct ViewportWScalingNV where
  peekCStruct :: ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> IO ViewportWScalingNV
peekCStruct "pViewportWScalings" ::: Ptr ViewportWScalingNV
p = do
    CFloat
xcoeff <- forall a. Storable a => Ptr a -> IO a
peek @CFloat (("pViewportWScalings" ::: Ptr ViewportWScalingNV
p ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr CFloat))
    CFloat
ycoeff <- forall a. Storable a => Ptr a -> IO a
peek @CFloat (("pViewportWScalings" ::: Ptr ViewportWScalingNV
p ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat))
    ViewportWScalingNV -> IO ViewportWScalingNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ViewportWScalingNV -> IO ViewportWScalingNV)
-> ViewportWScalingNV -> IO ViewportWScalingNV
forall a b. (a -> b) -> a -> b
$ Float -> Float -> ViewportWScalingNV
ViewportWScalingNV
             (forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
xcoeff) (forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
ycoeff)

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

instance Zero ViewportWScalingNV where
  zero :: ViewportWScalingNV
zero = Float -> Float -> ViewportWScalingNV
ViewportWScalingNV
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero


-- | VkPipelineViewportWScalingStateCreateInfoNV - Structure specifying
-- parameters of a newly created pipeline viewport W scaling state
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_clip_space_w_scaling VK_NV_clip_space_w_scaling>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'ViewportWScalingNV'
data PipelineViewportWScalingStateCreateInfoNV = PipelineViewportWScalingStateCreateInfoNV
  { -- | @viewportWScalingEnable@ controls whether viewport __W__ scaling is
    -- enabled.
    PipelineViewportWScalingStateCreateInfoNV -> Bool
viewportWScalingEnable :: Bool
  , -- | @viewportCount@ is the number of viewports used by __W__ scaling, and
    -- /must/ match the number of viewports in the pipeline if viewport __W__
    -- scaling is enabled.
    --
    -- #VUID-VkPipelineViewportWScalingStateCreateInfoNV-viewportCount-arraylength#
    -- @viewportCount@ /must/ be greater than @0@
    PipelineViewportWScalingStateCreateInfoNV
-> "firstViewport" ::: Word32
viewportCount :: Word32
  , -- | @pViewportWScalings@ is a pointer to an array of 'ViewportWScalingNV'
    -- structures defining the __W__ scaling parameters for the corresponding
    -- viewports. If the viewport __W__ scaling state is dynamic, this member
    -- is ignored.
    PipelineViewportWScalingStateCreateInfoNV
-> "viewportWScalings" ::: Vector ViewportWScalingNV
viewportWScalings :: Vector ViewportWScalingNV
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineViewportWScalingStateCreateInfoNV)
#endif
deriving instance Show PipelineViewportWScalingStateCreateInfoNV

instance ToCStruct PipelineViewportWScalingStateCreateInfoNV where
  withCStruct :: forall b.
PipelineViewportWScalingStateCreateInfoNV
-> (Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b) -> IO b
withCStruct PipelineViewportWScalingStateCreateInfoNV
x Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b
f = Int
-> (Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b) -> IO b)
-> (Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PipelineViewportWScalingStateCreateInfoNV
p -> Ptr PipelineViewportWScalingStateCreateInfoNV
-> PipelineViewportWScalingStateCreateInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineViewportWScalingStateCreateInfoNV
p PipelineViewportWScalingStateCreateInfoNV
x (Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b
f Ptr PipelineViewportWScalingStateCreateInfoNV
p)
  pokeCStruct :: forall b.
Ptr PipelineViewportWScalingStateCreateInfoNV
-> PipelineViewportWScalingStateCreateInfoNV -> IO b -> IO b
pokeCStruct Ptr PipelineViewportWScalingStateCreateInfoNV
p PipelineViewportWScalingStateCreateInfoNV{Bool
"firstViewport" ::: Word32
"viewportWScalings" ::: Vector ViewportWScalingNV
viewportWScalings :: "viewportWScalings" ::: Vector ViewportWScalingNV
viewportCount :: "firstViewport" ::: Word32
viewportWScalingEnable :: Bool
$sel:viewportWScalings:PipelineViewportWScalingStateCreateInfoNV :: PipelineViewportWScalingStateCreateInfoNV
-> "viewportWScalings" ::: Vector ViewportWScalingNV
$sel:viewportCount:PipelineViewportWScalingStateCreateInfoNV :: PipelineViewportWScalingStateCreateInfoNV
-> "firstViewport" ::: Word32
$sel:viewportWScalingEnable:PipelineViewportWScalingStateCreateInfoNV :: PipelineViewportWScalingStateCreateInfoNV -> Bool
..} IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_VIEWPORT_W_SCALING_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 PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
viewportWScalingEnable))
    let pViewportWScalingsLength :: Int
pViewportWScalingsLength = ("viewportWScalings" ::: Vector ViewportWScalingNV) -> Int
forall a. Vector a -> Int
Data.Vector.length (("viewportWScalings" ::: Vector ViewportWScalingNV) -> Int)
-> ("viewportWScalings" ::: Vector ViewportWScalingNV) -> Int
forall a b. (a -> b) -> a -> b
$ ("viewportWScalings" ::: Vector ViewportWScalingNV
viewportWScalings)
    "firstViewport" ::: Word32
viewportCount'' <- IO ("firstViewport" ::: Word32)
-> ContT b IO ("firstViewport" ::: Word32)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("firstViewport" ::: Word32)
 -> ContT b IO ("firstViewport" ::: Word32))
-> IO ("firstViewport" ::: Word32)
-> ContT b IO ("firstViewport" ::: Word32)
forall a b. (a -> b) -> a -> b
$ if ("firstViewport" ::: Word32
viewportCount) ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32) -> Bool
forall a. Eq a => a -> a -> Bool
== "firstViewport" ::: Word32
0
      then ("firstViewport" ::: Word32) -> IO ("firstViewport" ::: Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("firstViewport" ::: Word32) -> IO ("firstViewport" ::: Word32))
-> ("firstViewport" ::: Word32) -> IO ("firstViewport" ::: Word32)
forall a b. (a -> b) -> a -> b
$ Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pViewportWScalingsLength
      else do
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Int -> "firstViewport" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pViewportWScalingsLength ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32) -> Bool
forall a. Eq a => a -> a -> Bool
== ("firstViewport" ::: Word32
viewportCount) Bool -> Bool -> Bool
|| Int
pViewportWScalingsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (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
"pViewportWScalings must be empty or have 'viewportCount' elements" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
        ("firstViewport" ::: Word32) -> IO ("firstViewport" ::: Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ("firstViewport" ::: Word32
viewportCount)
    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 ("firstViewport" ::: Word32)
-> ("firstViewport" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV
-> Int -> Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) ("firstViewport" ::: Word32
viewportCount'')
    "pViewportWScalings" ::: Ptr ViewportWScalingNV
pViewportWScalings'' <- if ("viewportWScalings" ::: Vector ViewportWScalingNV) -> Bool
forall a. Vector a -> Bool
Data.Vector.null ("viewportWScalings" ::: Vector ViewportWScalingNV
viewportWScalings)
      then ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ContT b IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pViewportWScalings" ::: Ptr ViewportWScalingNV
forall a. Ptr a
nullPtr
      else do
        "pViewportWScalings" ::: Ptr ViewportWScalingNV
pPViewportWScalings <- ((("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
 -> IO b)
-> ContT b IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
  -> IO b)
 -> ContT b IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV))
-> ((("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
    -> IO b)
-> ContT b IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @ViewportWScalingNV (((("viewportWScalings" ::: Vector ViewportWScalingNV) -> Int
forall a. Vector a -> Int
Data.Vector.length ("viewportWScalings" ::: Vector ViewportWScalingNV
viewportWScalings))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8)
        IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> ViewportWScalingNV -> IO ())
-> ("viewportWScalings" ::: Vector ViewportWScalingNV) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i ViewportWScalingNV
e -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ViewportWScalingNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pViewportWScalings" ::: Ptr ViewportWScalingNV
pPViewportWScalings ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> "pViewportWScalings" ::: Ptr ViewportWScalingNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ViewportWScalingNV) (ViewportWScalingNV
e)) (("viewportWScalings" ::: Vector ViewportWScalingNV
viewportWScalings))
        ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ContT b IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("pViewportWScalings" ::: Ptr ViewportWScalingNV)
 -> ContT b IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV))
-> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ContT b IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
forall a b. (a -> b) -> a -> b
$ "pViewportWScalings" ::: Ptr ViewportWScalingNV
pPViewportWScalings
    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 ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV
-> Int -> Ptr ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr ViewportWScalingNV))) "pViewportWScalings" ::: Ptr ViewportWScalingNV
pViewportWScalings''
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr PipelineViewportWScalingStateCreateInfoNV
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_VIEWPORT_W_SCALING_STATE_CREATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PipelineViewportWScalingStateCreateInfoNV where
  peekCStruct :: Ptr PipelineViewportWScalingStateCreateInfoNV
-> IO PipelineViewportWScalingStateCreateInfoNV
peekCStruct Ptr PipelineViewportWScalingStateCreateInfoNV
p = do
    Bool32
viewportWScalingEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    "firstViewport" ::: Word32
viewportCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV
-> Int -> Ptr ("firstViewport" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32))
    "pViewportWScalings" ::: Ptr ViewportWScalingNV
pViewportWScalings <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ViewportWScalingNV) ((Ptr PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV
-> Int -> Ptr ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr ViewportWScalingNV)))
    let pViewportWScalingsLength :: Int
pViewportWScalingsLength = if "pViewportWScalings" ::: Ptr ViewportWScalingNV
pViewportWScalings ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> Bool
forall a. Eq a => a -> a -> Bool
== "pViewportWScalings" ::: Ptr ViewportWScalingNV
forall a. Ptr a
nullPtr then Int
0 else (("firstViewport" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "firstViewport" ::: Word32
viewportCount)
    "viewportWScalings" ::: Vector ViewportWScalingNV
pViewportWScalings' <- Int
-> (Int -> IO ViewportWScalingNV)
-> IO ("viewportWScalings" ::: Vector ViewportWScalingNV)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM Int
pViewportWScalingsLength (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ViewportWScalingNV (("pViewportWScalings" ::: Ptr ViewportWScalingNV
pViewportWScalings ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> "pViewportWScalings" ::: Ptr ViewportWScalingNV
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ViewportWScalingNV)))
    PipelineViewportWScalingStateCreateInfoNV
-> IO PipelineViewportWScalingStateCreateInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineViewportWScalingStateCreateInfoNV
 -> IO PipelineViewportWScalingStateCreateInfoNV)
-> PipelineViewportWScalingStateCreateInfoNV
-> IO PipelineViewportWScalingStateCreateInfoNV
forall a b. (a -> b) -> a -> b
$ Bool
-> ("firstViewport" ::: Word32)
-> ("viewportWScalings" ::: Vector ViewportWScalingNV)
-> PipelineViewportWScalingStateCreateInfoNV
PipelineViewportWScalingStateCreateInfoNV
             (Bool32 -> Bool
bool32ToBool Bool32
viewportWScalingEnable)
             "firstViewport" ::: Word32
viewportCount
             "viewportWScalings" ::: Vector ViewportWScalingNV
pViewportWScalings'

instance Zero PipelineViewportWScalingStateCreateInfoNV where
  zero :: PipelineViewportWScalingStateCreateInfoNV
zero = Bool
-> ("firstViewport" ::: Word32)
-> ("viewportWScalings" ::: Vector ViewportWScalingNV)
-> PipelineViewportWScalingStateCreateInfoNV
PipelineViewportWScalingStateCreateInfoNV
           Bool
forall a. Zero a => a
zero
           "firstViewport" ::: Word32
forall a. Zero a => a
zero
           "viewportWScalings" ::: Vector ViewportWScalingNV
forall a. Monoid a => a
mempty


type NV_CLIP_SPACE_W_SCALING_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_NV_CLIP_SPACE_W_SCALING_SPEC_VERSION"
pattern NV_CLIP_SPACE_W_SCALING_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_CLIP_SPACE_W_SCALING_SPEC_VERSION :: forall a. Integral a => a
$mNV_CLIP_SPACE_W_SCALING_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_CLIP_SPACE_W_SCALING_SPEC_VERSION = 1


type NV_CLIP_SPACE_W_SCALING_EXTENSION_NAME = "VK_NV_clip_space_w_scaling"

-- No documentation found for TopLevel "VK_NV_CLIP_SPACE_W_SCALING_EXTENSION_NAME"
pattern NV_CLIP_SPACE_W_SCALING_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_CLIP_SPACE_W_SCALING_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_CLIP_SPACE_W_SCALING_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_CLIP_SPACE_W_SCALING_EXTENSION_NAME = "VK_NV_clip_space_w_scaling"