{-# language CPP #-}
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 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 qualified Data.Vector (null)
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
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_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetViewportWScalingNV))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
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_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 ()
cmdSetViewportWScalingNV :: forall io
                          . (MonadIO io)
                         => 
                            
                            CommandBuffer
                         -> 
                            
                            ("firstViewport" ::: Word32)
                         -> 
                            
                            ("viewportWScalings" ::: Vector ViewportWScalingNV)
                         -> io ()
cmdSetViewportWScalingNV :: CommandBuffer
-> ("firstViewport" ::: Word32)
-> ("viewportWScalings" ::: Vector ViewportWScalingNV)
-> io ()
cmdSetViewportWScalingNV commandBuffer :: CommandBuffer
commandBuffer firstViewport :: "firstViewport" ::: Word32
firstViewport viewportWScalings :: "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 (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
   -> ("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 "" "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
$ Int
-> Int
-> (("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @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
* 8) 4
  (Int -> ViewportWScalingNV -> ContT () IO ())
-> ("viewportWScalings" ::: Vector ViewportWScalingNV)
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ViewportWScalingNV
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
$ ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ViewportWScalingNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pViewportWScalings" ::: Ptr ViewportWScalingNV
pPViewportWScalings ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> "pViewportWScalings" ::: Ptr ViewportWScalingNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ViewportWScalingNV) (ViewportWScalingNV
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
$ ())) ("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
$ 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
$ ()
data ViewportWScalingNV = ViewportWScalingNV
  { 
    
    ViewportWScalingNV -> Float
xcoeff :: Float
  , 
    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 :: ViewportWScalingNV
-> (("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
-> IO b
withCStruct x :: ViewportWScalingNV
x f :: ("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b
f = Int
-> Int
-> (("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 4 ((("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
 -> IO b)
-> (("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "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 :: ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ViewportWScalingNV -> IO b -> IO b
pokeCStruct p :: "pViewportWScalings" ::: Ptr ViewportWScalingNV
p ViewportWScalingNV{..} f :: 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` 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` 4 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
ycoeff))
    IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: ("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b -> IO b
pokeZeroCStruct p :: "pViewportWScalings" ::: Ptr ViewportWScalingNV
p f :: 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` 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` 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 p :: "pViewportWScalings" ::: Ptr ViewportWScalingNV
p = do
    CFloat
xcoeff <- Ptr CFloat -> IO CFloat
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` 0 :: Ptr CFloat))
    CFloat
ycoeff <- Ptr CFloat -> IO CFloat
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` 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
             ((\(CFloat a :: Float
a) -> Float
a) CFloat
xcoeff) ((\(CFloat a :: Float
a) -> Float
a) CFloat
ycoeff)
instance Storable ViewportWScalingNV where
  sizeOf :: ViewportWScalingNV -> Int
sizeOf ~ViewportWScalingNV
_ = 8
  alignment :: ViewportWScalingNV -> Int
alignment ~ViewportWScalingNV
_ = 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 ptr :: "pViewportWScalings" ::: Ptr ViewportWScalingNV
ptr poked :: 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
data PipelineViewportWScalingStateCreateInfoNV = PipelineViewportWScalingStateCreateInfoNV
  { 
    
    PipelineViewportWScalingStateCreateInfoNV -> Bool
viewportWScalingEnable :: Bool
  , 
    
    
    
    
    PipelineViewportWScalingStateCreateInfoNV
-> "firstViewport" ::: Word32
viewportCount :: Word32
  , 
    
    
    
    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 :: PipelineViewportWScalingStateCreateInfoNV
-> (Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b) -> IO b
withCStruct x :: PipelineViewportWScalingStateCreateInfoNV
x f :: Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b
f = Int
-> Int
-> (Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b) -> IO b)
-> (Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: 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 :: Ptr PipelineViewportWScalingStateCreateInfoNV
-> PipelineViewportWScalingStateCreateInfoNV -> IO b -> IO b
pokeCStruct p :: Ptr PipelineViewportWScalingStateCreateInfoNV
p PipelineViewportWScalingStateCreateInfoNV{..} 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 PipelineViewportWScalingStateCreateInfoNV
p Ptr PipelineViewportWScalingStateCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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` 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` 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
== 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
== 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 "" "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` 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
$ Int
-> Int
-> (("pViewportWScalings" ::: Ptr ViewportWScalingNV) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @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
* 8) 4
        (Int -> ViewportWScalingNV -> ContT b IO ())
-> ("viewportWScalings" ::: Vector ViewportWScalingNV)
-> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ViewportWScalingNV
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
$ ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> ViewportWScalingNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pViewportWScalings" ::: Ptr ViewportWScalingNV
pPViewportWScalings ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> Int -> "pViewportWScalings" ::: Ptr ViewportWScalingNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ViewportWScalingNV) (ViewportWScalingNV
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
$ ())) (("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` 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 = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PipelineViewportWScalingStateCreateInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr PipelineViewportWScalingStateCreateInfoNV
p f :: 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` 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` 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` 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 p :: Ptr PipelineViewportWScalingStateCreateInfoNV
p = do
    Bool32
viewportWScalingEnable <- Ptr Bool32 -> IO Bool32
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` 16 :: Ptr Bool32))
    "firstViewport" ::: Word32
viewportCount <- Ptr ("firstViewport" ::: Word32) -> IO ("firstViewport" ::: Word32)
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` 20 :: Ptr Word32))
    "pViewportWScalings" ::: Ptr ViewportWScalingNV
pViewportWScalings <- Ptr ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> IO ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
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` 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 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 (\i :: Int
i -> ("pViewportWScalings" ::: Ptr ViewportWScalingNV)
-> IO ViewportWScalingNV
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` (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
pattern NV_CLIP_SPACE_W_SCALING_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_CLIP_SPACE_W_SCALING_SPEC_VERSION :: 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"
pattern NV_CLIP_SPACE_W_SCALING_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_CLIP_SPACE_W_SCALING_EXTENSION_NAME :: 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"