{-# language CPP #-}
-- No documentation found for Chapter "Promoted_From_VK_KHR_maintenance2"
module Vulkan.Core11.Promoted_From_VK_KHR_maintenance2  ( InputAttachmentAspectReference(..)
                                                        , RenderPassInputAttachmentAspectCreateInfo(..)
                                                        , PhysicalDevicePointClippingProperties(..)
                                                        , ImageViewUsageCreateInfo(..)
                                                        , PipelineTessellationDomainOriginStateCreateInfo(..)
                                                        , ImageLayout(..)
                                                        , StructureType(..)
                                                        , ImageCreateFlagBits(..)
                                                        , ImageCreateFlags
                                                        , PointClippingBehavior(..)
                                                        , TessellationDomainOrigin(..)
                                                        ) where

import Foreign.Marshal.Alloc (allocaBytes)
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 Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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 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.Enums.ImageAspectFlagBits (ImageAspectFlags)
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlags)
import Vulkan.Core11.Enums.PointClippingBehavior (PointClippingBehavior)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core11.Enums.TessellationDomainOrigin (TessellationDomainOrigin)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_VIEW_USAGE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_POINT_CLIPPING_PROPERTIES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_TESSELLATION_DOMAIN_ORIGIN_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_INPUT_ATTACHMENT_ASPECT_CREATE_INFO))
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlagBits(..))
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlags)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout(..))
import Vulkan.Core11.Enums.PointClippingBehavior (PointClippingBehavior(..))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
import Vulkan.Core11.Enums.TessellationDomainOrigin (TessellationDomainOrigin(..))
-- | VkInputAttachmentAspectReference - Structure specifying a subpass\/input
-- attachment pair and an aspect mask that /can/ be read.
--
-- = Description
--
-- This structure specifies an aspect mask for a specific input attachment
-- of a specific subpass in the render pass.
--
-- @subpass@ and @inputAttachmentIndex@ index into the render pass as:
--
-- > pCreateInfo->pSubpasses[subpass].pInputAttachments[inputAttachmentIndex]
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>,
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlags',
-- 'RenderPassInputAttachmentAspectCreateInfo'
data InputAttachmentAspectReference = InputAttachmentAspectReference
  { -- | @subpass@ is an index into the @pSubpasses@ array of the parent
    -- 'Vulkan.Core10.Pass.RenderPassCreateInfo' structure.
    InputAttachmentAspectReference -> Word32
subpass :: Word32
  , -- | @inputAttachmentIndex@ is an index into the @pInputAttachments@ of the
    -- specified subpass.
    InputAttachmentAspectReference -> Word32
inputAttachmentIndex :: Word32
  , -- | @aspectMask@ is a mask of which aspect(s) /can/ be accessed within the
    -- specified subpass.
    --
    -- #VUID-VkInputAttachmentAspectReference-aspectMask-01964# @aspectMask@
    -- /must/ not include
    -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_METADATA_BIT'
    --
    -- #VUID-VkInputAttachmentAspectReference-aspectMask-02250# @aspectMask@
    -- /must/ not include @VK_IMAGE_ASPECT_MEMORY_PLANE_i_BIT_EXT@ for any
    -- index /i/
    --
    -- #VUID-VkInputAttachmentAspectReference-aspectMask-parameter#
    -- @aspectMask@ /must/ be a valid combination of
    -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits' values
    --
    -- #VUID-VkInputAttachmentAspectReference-aspectMask-requiredbitmask#
    -- @aspectMask@ /must/ not be @0@
    InputAttachmentAspectReference -> ImageAspectFlags
aspectMask :: ImageAspectFlags
  }
  deriving (Typeable, InputAttachmentAspectReference
-> InputAttachmentAspectReference -> Bool
(InputAttachmentAspectReference
 -> InputAttachmentAspectReference -> Bool)
-> (InputAttachmentAspectReference
    -> InputAttachmentAspectReference -> Bool)
-> Eq InputAttachmentAspectReference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputAttachmentAspectReference
-> InputAttachmentAspectReference -> Bool
$c/= :: InputAttachmentAspectReference
-> InputAttachmentAspectReference -> Bool
== :: InputAttachmentAspectReference
-> InputAttachmentAspectReference -> Bool
$c== :: InputAttachmentAspectReference
-> InputAttachmentAspectReference -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (InputAttachmentAspectReference)
#endif
deriving instance Show InputAttachmentAspectReference

instance ToCStruct InputAttachmentAspectReference where
  withCStruct :: forall b.
InputAttachmentAspectReference
-> (Ptr InputAttachmentAspectReference -> IO b) -> IO b
withCStruct InputAttachmentAspectReference
x Ptr InputAttachmentAspectReference -> IO b
f = Int -> (Ptr InputAttachmentAspectReference -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
12 ((Ptr InputAttachmentAspectReference -> IO b) -> IO b)
-> (Ptr InputAttachmentAspectReference -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr InputAttachmentAspectReference
p -> Ptr InputAttachmentAspectReference
-> InputAttachmentAspectReference -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr InputAttachmentAspectReference
p InputAttachmentAspectReference
x (Ptr InputAttachmentAspectReference -> IO b
f Ptr InputAttachmentAspectReference
p)
  pokeCStruct :: forall b.
Ptr InputAttachmentAspectReference
-> InputAttachmentAspectReference -> IO b -> IO b
pokeCStruct Ptr InputAttachmentAspectReference
p InputAttachmentAspectReference{Word32
ImageAspectFlags
aspectMask :: ImageAspectFlags
inputAttachmentIndex :: Word32
subpass :: Word32
$sel:aspectMask:InputAttachmentAspectReference :: InputAttachmentAspectReference -> ImageAspectFlags
$sel:inputAttachmentIndex:InputAttachmentAspectReference :: InputAttachmentAspectReference -> Word32
$sel:subpass:InputAttachmentAspectReference :: InputAttachmentAspectReference -> Word32
..} IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p Ptr InputAttachmentAspectReference -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
subpass)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p Ptr InputAttachmentAspectReference -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Word32
inputAttachmentIndex)
    Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p Ptr InputAttachmentAspectReference -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr ImageAspectFlags)) (ImageAspectFlags
aspectMask)
    IO b
f
  cStructSize :: Int
cStructSize = Int
12
  cStructAlignment :: Int
cStructAlignment = Int
4
  pokeZeroCStruct :: forall b. Ptr InputAttachmentAspectReference -> IO b -> IO b
pokeZeroCStruct Ptr InputAttachmentAspectReference
p IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p Ptr InputAttachmentAspectReference -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p Ptr InputAttachmentAspectReference -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr InputAttachmentAspectReference
p Ptr InputAttachmentAspectReference -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr ImageAspectFlags)) (ImageAspectFlags
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct InputAttachmentAspectReference where
  peekCStruct :: Ptr InputAttachmentAspectReference
-> IO InputAttachmentAspectReference
peekCStruct Ptr InputAttachmentAspectReference
p = do
    Word32
subpass <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr InputAttachmentAspectReference
p Ptr InputAttachmentAspectReference -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32))
    Word32
inputAttachmentIndex <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr InputAttachmentAspectReference
p Ptr InputAttachmentAspectReference -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32))
    ImageAspectFlags
aspectMask <- forall a. Storable a => Ptr a -> IO a
peek @ImageAspectFlags ((Ptr InputAttachmentAspectReference
p Ptr InputAttachmentAspectReference -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr ImageAspectFlags))
    InputAttachmentAspectReference -> IO InputAttachmentAspectReference
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputAttachmentAspectReference
 -> IO InputAttachmentAspectReference)
-> InputAttachmentAspectReference
-> IO InputAttachmentAspectReference
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32 -> ImageAspectFlags -> InputAttachmentAspectReference
InputAttachmentAspectReference
             Word32
subpass Word32
inputAttachmentIndex ImageAspectFlags
aspectMask

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

instance Zero InputAttachmentAspectReference where
  zero :: InputAttachmentAspectReference
zero = Word32
-> Word32 -> ImageAspectFlags -> InputAttachmentAspectReference
InputAttachmentAspectReference
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           ImageAspectFlags
forall a. Zero a => a
zero


-- | VkRenderPassInputAttachmentAspectCreateInfo - Structure specifying, for
-- a given subpass\/input attachment pair, which aspect /can/ be read.
--
-- = Description
--
-- To specify which aspects of an input attachment /can/ be read, add a
-- 'RenderPassInputAttachmentAspectCreateInfo' structure to the @pNext@
-- chain of the 'Vulkan.Core10.Pass.RenderPassCreateInfo' structure:
--
-- An application /can/ access any aspect of an input attachment that does
-- not have a specified aspect mask in the @pAspectReferences@ array.
-- Otherwise, an application /must/ not access aspect(s) of an input
-- attachment other than those in its specified aspect mask.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>,
-- 'InputAttachmentAspectReference',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data RenderPassInputAttachmentAspectCreateInfo = RenderPassInputAttachmentAspectCreateInfo
  { -- | @pAspectReferences@ is a pointer to an array of @aspectReferenceCount@
    -- 'InputAttachmentAspectReference' structures containing a mask describing
    -- which aspect(s) /can/ be accessed for a given input attachment within a
    -- given subpass.
    --
    -- #VUID-VkRenderPassInputAttachmentAspectCreateInfo-pAspectReferences-parameter#
    -- @pAspectReferences@ /must/ be a valid pointer to an array of
    -- @aspectReferenceCount@ valid 'InputAttachmentAspectReference' structures
    RenderPassInputAttachmentAspectCreateInfo
-> Vector InputAttachmentAspectReference
aspectReferences :: Vector InputAttachmentAspectReference }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RenderPassInputAttachmentAspectCreateInfo)
#endif
deriving instance Show RenderPassInputAttachmentAspectCreateInfo

instance ToCStruct RenderPassInputAttachmentAspectCreateInfo where
  withCStruct :: forall b.
RenderPassInputAttachmentAspectCreateInfo
-> (Ptr RenderPassInputAttachmentAspectCreateInfo -> IO b) -> IO b
withCStruct RenderPassInputAttachmentAspectCreateInfo
x Ptr RenderPassInputAttachmentAspectCreateInfo -> IO b
f = Int
-> (Ptr RenderPassInputAttachmentAspectCreateInfo -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr RenderPassInputAttachmentAspectCreateInfo -> IO b) -> IO b)
-> (Ptr RenderPassInputAttachmentAspectCreateInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr RenderPassInputAttachmentAspectCreateInfo
p -> Ptr RenderPassInputAttachmentAspectCreateInfo
-> RenderPassInputAttachmentAspectCreateInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr RenderPassInputAttachmentAspectCreateInfo
p RenderPassInputAttachmentAspectCreateInfo
x (Ptr RenderPassInputAttachmentAspectCreateInfo -> IO b
f Ptr RenderPassInputAttachmentAspectCreateInfo
p)
  pokeCStruct :: forall b.
Ptr RenderPassInputAttachmentAspectCreateInfo
-> RenderPassInputAttachmentAspectCreateInfo -> IO b -> IO b
pokeCStruct Ptr RenderPassInputAttachmentAspectCreateInfo
p RenderPassInputAttachmentAspectCreateInfo{Vector InputAttachmentAspectReference
aspectReferences :: Vector InputAttachmentAspectReference
$sel:aspectReferences:RenderPassInputAttachmentAspectCreateInfo :: RenderPassInputAttachmentAspectCreateInfo
-> Vector InputAttachmentAspectReference
..} 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 RenderPassInputAttachmentAspectCreateInfo
p Ptr RenderPassInputAttachmentAspectCreateInfo
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_INPUT_ATTACHMENT_ASPECT_CREATE_INFO)
    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 RenderPassInputAttachmentAspectCreateInfo
p Ptr RenderPassInputAttachmentAspectCreateInfo
-> 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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassInputAttachmentAspectCreateInfo
p Ptr RenderPassInputAttachmentAspectCreateInfo -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector InputAttachmentAspectReference -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector InputAttachmentAspectReference -> Int)
-> Vector InputAttachmentAspectReference -> Int
forall a b. (a -> b) -> a -> b
$ (Vector InputAttachmentAspectReference
aspectReferences)) :: Word32))
    Ptr InputAttachmentAspectReference
pPAspectReferences' <- ((Ptr InputAttachmentAspectReference -> IO b) -> IO b)
-> ContT b IO (Ptr InputAttachmentAspectReference)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr InputAttachmentAspectReference -> IO b) -> IO b)
 -> ContT b IO (Ptr InputAttachmentAspectReference))
-> ((Ptr InputAttachmentAspectReference -> IO b) -> IO b)
-> ContT b IO (Ptr InputAttachmentAspectReference)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @InputAttachmentAspectReference ((Vector InputAttachmentAspectReference -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector InputAttachmentAspectReference
aspectReferences)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
12)
    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 -> InputAttachmentAspectReference -> IO ())
-> Vector InputAttachmentAspectReference -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i InputAttachmentAspectReference
e -> Ptr InputAttachmentAspectReference
-> InputAttachmentAspectReference -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr InputAttachmentAspectReference
pPAspectReferences' Ptr InputAttachmentAspectReference
-> Int -> Ptr InputAttachmentAspectReference
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr InputAttachmentAspectReference) (InputAttachmentAspectReference
e)) (Vector InputAttachmentAspectReference
aspectReferences)
    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 InputAttachmentAspectReference)
-> Ptr InputAttachmentAspectReference -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassInputAttachmentAspectCreateInfo
p Ptr RenderPassInputAttachmentAspectCreateInfo
-> Int -> Ptr (Ptr InputAttachmentAspectReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr InputAttachmentAspectReference))) (Ptr InputAttachmentAspectReference
pPAspectReferences')
    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 RenderPassInputAttachmentAspectCreateInfo -> IO b -> IO b
pokeZeroCStruct Ptr RenderPassInputAttachmentAspectCreateInfo
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassInputAttachmentAspectCreateInfo
p Ptr RenderPassInputAttachmentAspectCreateInfo
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_INPUT_ATTACHMENT_ASPECT_CREATE_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassInputAttachmentAspectCreateInfo
p Ptr RenderPassInputAttachmentAspectCreateInfo
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct RenderPassInputAttachmentAspectCreateInfo where
  peekCStruct :: Ptr RenderPassInputAttachmentAspectCreateInfo
-> IO RenderPassInputAttachmentAspectCreateInfo
peekCStruct Ptr RenderPassInputAttachmentAspectCreateInfo
p = do
    Word32
aspectReferenceCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RenderPassInputAttachmentAspectCreateInfo
p Ptr RenderPassInputAttachmentAspectCreateInfo -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Ptr InputAttachmentAspectReference
pAspectReferences <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr InputAttachmentAspectReference) ((Ptr RenderPassInputAttachmentAspectCreateInfo
p Ptr RenderPassInputAttachmentAspectCreateInfo
-> Int -> Ptr (Ptr InputAttachmentAspectReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr InputAttachmentAspectReference)))
    Vector InputAttachmentAspectReference
pAspectReferences' <- Int
-> (Int -> IO InputAttachmentAspectReference)
-> IO (Vector InputAttachmentAspectReference)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
aspectReferenceCount) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @InputAttachmentAspectReference ((Ptr InputAttachmentAspectReference
pAspectReferences Ptr InputAttachmentAspectReference
-> Int -> Ptr InputAttachmentAspectReference
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr InputAttachmentAspectReference)))
    RenderPassInputAttachmentAspectCreateInfo
-> IO RenderPassInputAttachmentAspectCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RenderPassInputAttachmentAspectCreateInfo
 -> IO RenderPassInputAttachmentAspectCreateInfo)
-> RenderPassInputAttachmentAspectCreateInfo
-> IO RenderPassInputAttachmentAspectCreateInfo
forall a b. (a -> b) -> a -> b
$ Vector InputAttachmentAspectReference
-> RenderPassInputAttachmentAspectCreateInfo
RenderPassInputAttachmentAspectCreateInfo
             Vector InputAttachmentAspectReference
pAspectReferences'

instance Zero RenderPassInputAttachmentAspectCreateInfo where
  zero :: RenderPassInputAttachmentAspectCreateInfo
zero = Vector InputAttachmentAspectReference
-> RenderPassInputAttachmentAspectCreateInfo
RenderPassInputAttachmentAspectCreateInfo
           Vector InputAttachmentAspectReference
forall a. Monoid a => a
mempty


-- | VkPhysicalDevicePointClippingProperties - Structure describing the point
-- clipping behavior supported by an implementation
--
-- = Description
--
-- If the 'PhysicalDevicePointClippingProperties' structure is included in
-- the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>,
-- 'Vulkan.Core11.Enums.PointClippingBehavior.PointClippingBehavior',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDevicePointClippingProperties = PhysicalDevicePointClippingProperties
  { -- | #extension-limits-pointClipping# @pointClippingBehavior@ is a
    -- 'Vulkan.Core11.Enums.PointClippingBehavior.PointClippingBehavior' value
    -- specifying the point clipping behavior supported by the implementation.
    PhysicalDevicePointClippingProperties -> PointClippingBehavior
pointClippingBehavior :: PointClippingBehavior }
  deriving (Typeable, PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> Bool
(PhysicalDevicePointClippingProperties
 -> PhysicalDevicePointClippingProperties -> Bool)
-> (PhysicalDevicePointClippingProperties
    -> PhysicalDevicePointClippingProperties -> Bool)
-> Eq PhysicalDevicePointClippingProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> Bool
$c/= :: PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> Bool
== :: PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> Bool
$c== :: PhysicalDevicePointClippingProperties
-> PhysicalDevicePointClippingProperties -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevicePointClippingProperties)
#endif
deriving instance Show PhysicalDevicePointClippingProperties

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

instance FromCStruct PhysicalDevicePointClippingProperties where
  peekCStruct :: Ptr PhysicalDevicePointClippingProperties
-> IO PhysicalDevicePointClippingProperties
peekCStruct Ptr PhysicalDevicePointClippingProperties
p = do
    PointClippingBehavior
pointClippingBehavior <- forall a. Storable a => Ptr a -> IO a
peek @PointClippingBehavior ((Ptr PhysicalDevicePointClippingProperties
p Ptr PhysicalDevicePointClippingProperties
-> Int -> Ptr PointClippingBehavior
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PointClippingBehavior))
    PhysicalDevicePointClippingProperties
-> IO PhysicalDevicePointClippingProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDevicePointClippingProperties
 -> IO PhysicalDevicePointClippingProperties)
-> PhysicalDevicePointClippingProperties
-> IO PhysicalDevicePointClippingProperties
forall a b. (a -> b) -> a -> b
$ PointClippingBehavior -> PhysicalDevicePointClippingProperties
PhysicalDevicePointClippingProperties
             PointClippingBehavior
pointClippingBehavior

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

instance Zero PhysicalDevicePointClippingProperties where
  zero :: PhysicalDevicePointClippingProperties
zero = PointClippingBehavior -> PhysicalDevicePointClippingProperties
PhysicalDevicePointClippingProperties
           PointClippingBehavior
forall a. Zero a => a
zero


-- | VkImageViewUsageCreateInfo - Specify the intended usage of an image view
--
-- = Description
--
-- When this structure is chained to
-- 'Vulkan.Core10.ImageView.ImageViewCreateInfo' the @usage@ field
-- overrides the implicit @usage@ parameter inherited from image creation
-- time and its value is used instead for the purposes of determining the
-- valid usage conditions of 'Vulkan.Core10.ImageView.ImageViewCreateInfo'.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>,
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data ImageViewUsageCreateInfo = ImageViewUsageCreateInfo
  { -- | @usage@ is a bitmask of
    -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlagBits' specifying
    -- allowed usages of the image view.
    --
    -- #VUID-VkImageViewUsageCreateInfo-usage-parameter# @usage@ /must/ be a
    -- valid combination of
    -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlagBits' values
    --
    -- #VUID-VkImageViewUsageCreateInfo-usage-requiredbitmask# @usage@ /must/
    -- not be @0@
    ImageViewUsageCreateInfo -> ImageUsageFlags
usage :: ImageUsageFlags }
  deriving (Typeable, ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool
(ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool)
-> (ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool)
-> Eq ImageViewUsageCreateInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool
$c/= :: ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool
== :: ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool
$c== :: ImageViewUsageCreateInfo -> ImageViewUsageCreateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageViewUsageCreateInfo)
#endif
deriving instance Show ImageViewUsageCreateInfo

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

instance FromCStruct ImageViewUsageCreateInfo where
  peekCStruct :: Ptr ImageViewUsageCreateInfo -> IO ImageViewUsageCreateInfo
peekCStruct Ptr ImageViewUsageCreateInfo
p = do
    ImageUsageFlags
usage <- forall a. Storable a => Ptr a -> IO a
peek @ImageUsageFlags ((Ptr ImageViewUsageCreateInfo
p Ptr ImageViewUsageCreateInfo -> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageUsageFlags))
    ImageViewUsageCreateInfo -> IO ImageViewUsageCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageViewUsageCreateInfo -> IO ImageViewUsageCreateInfo)
-> ImageViewUsageCreateInfo -> IO ImageViewUsageCreateInfo
forall a b. (a -> b) -> a -> b
$ ImageUsageFlags -> ImageViewUsageCreateInfo
ImageViewUsageCreateInfo
             ImageUsageFlags
usage

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

instance Zero ImageViewUsageCreateInfo where
  zero :: ImageViewUsageCreateInfo
zero = ImageUsageFlags -> ImageViewUsageCreateInfo
ImageViewUsageCreateInfo
           ImageUsageFlags
forall a. Zero a => a
zero


-- | VkPipelineTessellationDomainOriginStateCreateInfo - Structure specifying
-- the orientation of the tessellation domain
--
-- = Description
--
-- If the 'PipelineTessellationDomainOriginStateCreateInfo' structure is
-- included in the @pNext@ chain of
-- 'Vulkan.Core10.Pipeline.PipelineTessellationStateCreateInfo', it
-- controls the origin of the tessellation domain. If this structure is not
-- present, it is as if @domainOrigin@ was
-- 'Vulkan.Core11.Enums.TessellationDomainOrigin.TESSELLATION_DOMAIN_ORIGIN_UPPER_LEFT'.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Core11.Enums.TessellationDomainOrigin.TessellationDomainOrigin'
data PipelineTessellationDomainOriginStateCreateInfo = PipelineTessellationDomainOriginStateCreateInfo
  { -- | @domainOrigin@ is a
    -- 'Vulkan.Core11.Enums.TessellationDomainOrigin.TessellationDomainOrigin'
    -- value controlling the origin of the tessellation domain space.
    --
    -- #VUID-VkPipelineTessellationDomainOriginStateCreateInfo-domainOrigin-parameter#
    -- @domainOrigin@ /must/ be a valid
    -- 'Vulkan.Core11.Enums.TessellationDomainOrigin.TessellationDomainOrigin'
    -- value
    PipelineTessellationDomainOriginStateCreateInfo
-> TessellationDomainOrigin
domainOrigin :: TessellationDomainOrigin }
  deriving (Typeable, PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> Bool
(PipelineTessellationDomainOriginStateCreateInfo
 -> PipelineTessellationDomainOriginStateCreateInfo -> Bool)
-> (PipelineTessellationDomainOriginStateCreateInfo
    -> PipelineTessellationDomainOriginStateCreateInfo -> Bool)
-> Eq PipelineTessellationDomainOriginStateCreateInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> Bool
$c/= :: PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> Bool
== :: PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> Bool
$c== :: PipelineTessellationDomainOriginStateCreateInfo
-> PipelineTessellationDomainOriginStateCreateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineTessellationDomainOriginStateCreateInfo)
#endif
deriving instance Show PipelineTessellationDomainOriginStateCreateInfo

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

instance FromCStruct PipelineTessellationDomainOriginStateCreateInfo where
  peekCStruct :: Ptr PipelineTessellationDomainOriginStateCreateInfo
-> IO PipelineTessellationDomainOriginStateCreateInfo
peekCStruct Ptr PipelineTessellationDomainOriginStateCreateInfo
p = do
    TessellationDomainOrigin
domainOrigin <- forall a. Storable a => Ptr a -> IO a
peek @TessellationDomainOrigin ((Ptr PipelineTessellationDomainOriginStateCreateInfo
p Ptr PipelineTessellationDomainOriginStateCreateInfo
-> Int -> Ptr TessellationDomainOrigin
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr TessellationDomainOrigin))
    PipelineTessellationDomainOriginStateCreateInfo
-> IO PipelineTessellationDomainOriginStateCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineTessellationDomainOriginStateCreateInfo
 -> IO PipelineTessellationDomainOriginStateCreateInfo)
-> PipelineTessellationDomainOriginStateCreateInfo
-> IO PipelineTessellationDomainOriginStateCreateInfo
forall a b. (a -> b) -> a -> b
$ TessellationDomainOrigin
-> PipelineTessellationDomainOriginStateCreateInfo
PipelineTessellationDomainOriginStateCreateInfo
             TessellationDomainOrigin
domainOrigin

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

instance Zero PipelineTessellationDomainOriginStateCreateInfo where
  zero :: PipelineTessellationDomainOriginStateCreateInfo
zero = TessellationDomainOrigin
-> PipelineTessellationDomainOriginStateCreateInfo
PipelineTessellationDomainOriginStateCreateInfo
           TessellationDomainOrigin
forall a. Zero a => a
zero