{-# language CPP #-}
-- No documentation found for Chapter "Promoted_From_VK_KHR_separate_depth_stencil_layouts"
module Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts  ( PhysicalDeviceSeparateDepthStencilLayoutsFeatures(..)
                                                                          , AttachmentReferenceStencilLayout(..)
                                                                          , AttachmentDescriptionStencilLayout(..)
                                                                          , ImageLayout(..)
                                                                          , StructureType(..)
                                                                          ) where

import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_STENCIL_LAYOUT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ATTACHMENT_REFERENCE_STENCIL_LAYOUT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SEPARATE_DEPTH_STENCIL_LAYOUTS_FEATURES))
import Vulkan.Core10.Enums.ImageLayout (ImageLayout(..))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
-- | VkPhysicalDeviceSeparateDepthStencilLayoutsFeatures - Structure
-- describing whether the implementation can do depth and stencil image
-- barriers separately
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceSeparateDepthStencilLayoutsFeatures' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceSeparateDepthStencilLayoutsFeatures' /can/
-- also be used in the @pNext@ chain of
-- 'Vulkan.Core10.Device.DeviceCreateInfo' to selectively enable these
-- features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_separate_depth_stencil_layouts VK_KHR_separate_depth_stencil_layouts>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceSeparateDepthStencilLayoutsFeatures = PhysicalDeviceSeparateDepthStencilLayoutsFeatures
  { -- | #extension-features-separateDepthStencilLayouts#
    -- @separateDepthStencilLayouts@ indicates whether the implementation
    -- supports a 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' for a
    -- depth\/stencil image with only one of
    -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' or
    -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT' set,
    -- and whether
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL',
    -- or
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
    -- can be used.
    PhysicalDeviceSeparateDepthStencilLayoutsFeatures -> Bool
separateDepthStencilLayouts :: Bool }
  deriving (Typeable, PhysicalDeviceSeparateDepthStencilLayoutsFeatures
-> PhysicalDeviceSeparateDepthStencilLayoutsFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceSeparateDepthStencilLayoutsFeatures
-> PhysicalDeviceSeparateDepthStencilLayoutsFeatures -> Bool
$c/= :: PhysicalDeviceSeparateDepthStencilLayoutsFeatures
-> PhysicalDeviceSeparateDepthStencilLayoutsFeatures -> Bool
== :: PhysicalDeviceSeparateDepthStencilLayoutsFeatures
-> PhysicalDeviceSeparateDepthStencilLayoutsFeatures -> Bool
$c== :: PhysicalDeviceSeparateDepthStencilLayoutsFeatures
-> PhysicalDeviceSeparateDepthStencilLayoutsFeatures -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceSeparateDepthStencilLayoutsFeatures)
#endif
deriving instance Show PhysicalDeviceSeparateDepthStencilLayoutsFeatures

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

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

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

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


-- | VkAttachmentReferenceStencilLayout - Structure specifying an attachment
-- description
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_separate_depth_stencil_layouts VK_KHR_separate_depth_stencil_layouts>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AttachmentReferenceStencilLayout = AttachmentReferenceStencilLayout
  { -- | @stencilLayout@ is a 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
    -- specifying the layout the stencil aspect of the attachment uses during
    -- the subpass.
    --
    -- #VUID-VkAttachmentReferenceStencilLayout-stencilLayout-03318#
    -- @stencilLayout@ /must/ not be
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PREINITIALIZED',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL',
    -- or 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PRESENT_SRC_KHR'
    --
    -- #VUID-VkAttachmentReferenceStencilLayout-stencilLayout-parameter#
    -- @stencilLayout@ /must/ be a valid
    -- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
    AttachmentReferenceStencilLayout -> ImageLayout
stencilLayout :: ImageLayout }
  deriving (Typeable, AttachmentReferenceStencilLayout
-> AttachmentReferenceStencilLayout -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachmentReferenceStencilLayout
-> AttachmentReferenceStencilLayout -> Bool
$c/= :: AttachmentReferenceStencilLayout
-> AttachmentReferenceStencilLayout -> Bool
== :: AttachmentReferenceStencilLayout
-> AttachmentReferenceStencilLayout -> Bool
$c== :: AttachmentReferenceStencilLayout
-> AttachmentReferenceStencilLayout -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AttachmentReferenceStencilLayout)
#endif
deriving instance Show AttachmentReferenceStencilLayout

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

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

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

instance Zero AttachmentReferenceStencilLayout where
  zero :: AttachmentReferenceStencilLayout
zero = ImageLayout -> AttachmentReferenceStencilLayout
AttachmentReferenceStencilLayout
           forall a. Zero a => a
zero


-- | VkAttachmentDescriptionStencilLayout - Structure specifying an
-- attachment description
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_separate_depth_stencil_layouts VK_KHR_separate_depth_stencil_layouts>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AttachmentDescriptionStencilLayout = AttachmentDescriptionStencilLayout
  { -- | @stencilInitialLayout@ is the layout the stencil aspect of the
    -- attachment image subresource will be in when a render pass instance
    -- begins.
    --
    -- #VUID-VkAttachmentDescriptionStencilLayout-stencilInitialLayout-03308#
    -- @stencilInitialLayout@ /must/ not be
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL',
    -- or
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL'
    --
    -- #VUID-VkAttachmentDescriptionStencilLayout-stencilInitialLayout-parameter#
    -- @stencilInitialLayout@ /must/ be a valid
    -- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
    AttachmentDescriptionStencilLayout -> ImageLayout
stencilInitialLayout :: ImageLayout
  , -- | @stencilFinalLayout@ is the layout the stencil aspect of the attachment
    -- image subresource will be transitioned to when a render pass instance
    -- ends.
    --
    -- #VUID-VkAttachmentDescriptionStencilLayout-stencilFinalLayout-03309#
    -- @stencilFinalLayout@ /must/ not be
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL',
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL',
    -- or
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL'
    --
    -- #VUID-VkAttachmentDescriptionStencilLayout-stencilFinalLayout-03310#
    -- @stencilFinalLayout@ /must/ not be
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED' or
    -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PREINITIALIZED'
    --
    -- #VUID-VkAttachmentDescriptionStencilLayout-stencilFinalLayout-parameter#
    -- @stencilFinalLayout@ /must/ be a valid
    -- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
    AttachmentDescriptionStencilLayout -> ImageLayout
stencilFinalLayout :: ImageLayout
  }
  deriving (Typeable, AttachmentDescriptionStencilLayout
-> AttachmentDescriptionStencilLayout -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachmentDescriptionStencilLayout
-> AttachmentDescriptionStencilLayout -> Bool
$c/= :: AttachmentDescriptionStencilLayout
-> AttachmentDescriptionStencilLayout -> Bool
== :: AttachmentDescriptionStencilLayout
-> AttachmentDescriptionStencilLayout -> Bool
$c== :: AttachmentDescriptionStencilLayout
-> AttachmentDescriptionStencilLayout -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AttachmentDescriptionStencilLayout)
#endif
deriving instance Show AttachmentDescriptionStencilLayout

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

instance FromCStruct AttachmentDescriptionStencilLayout where
  peekCStruct :: Ptr AttachmentDescriptionStencilLayout
-> IO AttachmentDescriptionStencilLayout
peekCStruct Ptr AttachmentDescriptionStencilLayout
p = do
    ImageLayout
stencilInitialLayout <- forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr AttachmentDescriptionStencilLayout
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ImageLayout))
    ImageLayout
stencilFinalLayout <- forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr AttachmentDescriptionStencilLayout
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr ImageLayout))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ImageLayout -> ImageLayout -> AttachmentDescriptionStencilLayout
AttachmentDescriptionStencilLayout
             ImageLayout
stencilInitialLayout ImageLayout
stencilFinalLayout

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

instance Zero AttachmentDescriptionStencilLayout where
  zero :: AttachmentDescriptionStencilLayout
zero = ImageLayout -> ImageLayout -> AttachmentDescriptionStencilLayout
AttachmentDescriptionStencilLayout
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero