{-# language CPP #-}
module Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve  ( PhysicalDeviceDepthStencilResolveProperties(..)
                                                                 , SubpassDescriptionDepthStencilResolve(..)
                                                                 , StructureType(..)
                                                                 , ResolveModeFlagBits(..)
                                                                 , ResolveModeFlags
                                                                 ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Utils (maybePeek)
import GHC.Ptr (castPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
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 Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (peekSomeCStruct)
import Vulkan.CStruct.Extends (withSomeCStruct)
import Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2 (AttachmentReference2)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core12.Enums.ResolveModeFlagBits (ResolveModeFlagBits)
import Vulkan.Core12.Enums.ResolveModeFlagBits (ResolveModeFlags)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_STENCIL_RESOLVE_PROPERTIES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SUBPASS_DESCRIPTION_DEPTH_STENCIL_RESOLVE))
import Vulkan.Core12.Enums.ResolveModeFlagBits (ResolveModeFlagBits(..))
import Vulkan.Core12.Enums.ResolveModeFlagBits (ResolveModeFlags)
import Vulkan.Core10.Enums.StructureType (StructureType(..))
-- | VkPhysicalDeviceDepthStencilResolveProperties - Structure describing
-- depth\/stencil resolve properties that can be supported by an
-- implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceDepthStencilResolveProperties'
-- structure describe the following implementation-dependent limits:
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceDepthStencilResolveProperties = PhysicalDeviceDepthStencilResolveProperties
  { -- | @supportedDepthResolveModes@ is a bitmask of
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlagBits' indicating
    -- the set of supported depth resolve modes.
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_SAMPLE_ZERO_BIT'
    -- /must/ be included in the set but implementations /may/ support
    -- additional modes.
    PhysicalDeviceDepthStencilResolveProperties -> ResolveModeFlags
supportedDepthResolveModes :: ResolveModeFlags
  , -- | @supportedStencilResolveModes@ is a bitmask of
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlagBits' indicating
    -- the set of supported stencil resolve modes.
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_SAMPLE_ZERO_BIT'
    -- /must/ be included in the set but implementations /may/ support
    -- additional modes.
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_AVERAGE_BIT'
    -- /must/ not be included in the set.
    PhysicalDeviceDepthStencilResolveProperties -> ResolveModeFlags
supportedStencilResolveModes :: ResolveModeFlags
  , -- | @independentResolveNone@ is 'Vulkan.Core10.FundamentalTypes.TRUE' if the
    -- implementation supports setting the depth and stencil resolve modes to
    -- different values when one of those modes is
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_NONE'. Otherwise
    -- the implementation only supports setting both modes to the same value.
    PhysicalDeviceDepthStencilResolveProperties -> Bool
independentResolveNone :: Bool
  , -- | @independentResolve@ is 'Vulkan.Core10.FundamentalTypes.TRUE' if the
    -- implementation supports all combinations of the supported depth and
    -- stencil resolve modes, including setting either depth or stencil resolve
    -- mode to 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_NONE'. An
    -- implementation that supports @independentResolve@ /must/ also support
    -- @independentResolveNone@.
    PhysicalDeviceDepthStencilResolveProperties -> Bool
independentResolve :: Bool
  }
  deriving (Typeable, PhysicalDeviceDepthStencilResolveProperties
-> PhysicalDeviceDepthStencilResolveProperties -> Bool
(PhysicalDeviceDepthStencilResolveProperties
 -> PhysicalDeviceDepthStencilResolveProperties -> Bool)
-> (PhysicalDeviceDepthStencilResolveProperties
    -> PhysicalDeviceDepthStencilResolveProperties -> Bool)
-> Eq PhysicalDeviceDepthStencilResolveProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDepthStencilResolveProperties
-> PhysicalDeviceDepthStencilResolveProperties -> Bool
$c/= :: PhysicalDeviceDepthStencilResolveProperties
-> PhysicalDeviceDepthStencilResolveProperties -> Bool
== :: PhysicalDeviceDepthStencilResolveProperties
-> PhysicalDeviceDepthStencilResolveProperties -> Bool
$c== :: PhysicalDeviceDepthStencilResolveProperties
-> PhysicalDeviceDepthStencilResolveProperties -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDepthStencilResolveProperties)
#endif
deriving instance Show PhysicalDeviceDepthStencilResolveProperties

instance ToCStruct PhysicalDeviceDepthStencilResolveProperties where
  withCStruct :: PhysicalDeviceDepthStencilResolveProperties
-> (Ptr PhysicalDeviceDepthStencilResolveProperties -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceDepthStencilResolveProperties
x f :: Ptr PhysicalDeviceDepthStencilResolveProperties -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceDepthStencilResolveProperties -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PhysicalDeviceDepthStencilResolveProperties -> IO b) -> IO b)
-> (Ptr PhysicalDeviceDepthStencilResolveProperties -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceDepthStencilResolveProperties
p -> Ptr PhysicalDeviceDepthStencilResolveProperties
-> PhysicalDeviceDepthStencilResolveProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthStencilResolveProperties
p PhysicalDeviceDepthStencilResolveProperties
x (Ptr PhysicalDeviceDepthStencilResolveProperties -> IO b
f Ptr PhysicalDeviceDepthStencilResolveProperties
p)
  pokeCStruct :: Ptr PhysicalDeviceDepthStencilResolveProperties
-> PhysicalDeviceDepthStencilResolveProperties -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceDepthStencilResolveProperties
p PhysicalDeviceDepthStencilResolveProperties{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_STENCIL_RESOLVE_PROPERTIES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ResolveModeFlags)) (ResolveModeFlags
supportedDepthResolveModes)
    Ptr ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ResolveModeFlags)) (ResolveModeFlags
supportedStencilResolveModes)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
independentResolveNone))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
independentResolve))
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceDepthStencilResolveProperties -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceDepthStencilResolveProperties
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_STENCIL_RESOLVE_PROPERTIES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ResolveModeFlags)) (ResolveModeFlags
forall a. Zero a => a
zero)
    Ptr ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ResolveModeFlags)) (ResolveModeFlags
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceDepthStencilResolveProperties where
  peekCStruct :: Ptr PhysicalDeviceDepthStencilResolveProperties
-> IO PhysicalDeviceDepthStencilResolveProperties
peekCStruct p :: Ptr PhysicalDeviceDepthStencilResolveProperties
p = do
    ResolveModeFlags
supportedDepthResolveModes <- Ptr ResolveModeFlags -> IO ResolveModeFlags
forall a. Storable a => Ptr a -> IO a
peek @ResolveModeFlags ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ResolveModeFlags))
    ResolveModeFlags
supportedStencilResolveModes <- Ptr ResolveModeFlags -> IO ResolveModeFlags
forall a. Storable a => Ptr a -> IO a
peek @ResolveModeFlags ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ResolveModeFlags))
    Bool32
independentResolveNone <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    Bool32
independentResolve <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDepthStencilResolveProperties
p Ptr PhysicalDeviceDepthStencilResolveProperties
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32))
    PhysicalDeviceDepthStencilResolveProperties
-> IO PhysicalDeviceDepthStencilResolveProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceDepthStencilResolveProperties
 -> IO PhysicalDeviceDepthStencilResolveProperties)
-> PhysicalDeviceDepthStencilResolveProperties
-> IO PhysicalDeviceDepthStencilResolveProperties
forall a b. (a -> b) -> a -> b
$ ResolveModeFlags
-> ResolveModeFlags
-> Bool
-> Bool
-> PhysicalDeviceDepthStencilResolveProperties
PhysicalDeviceDepthStencilResolveProperties
             ResolveModeFlags
supportedDepthResolveModes ResolveModeFlags
supportedStencilResolveModes (Bool32 -> Bool
bool32ToBool Bool32
independentResolveNone) (Bool32 -> Bool
bool32ToBool Bool32
independentResolve)

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

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


-- | VkSubpassDescriptionDepthStencilResolve - Structure specifying
-- depth\/stencil resolve operations for a subpass
--
-- == Valid Usage
--
-- -   If @pDepthStencilResolveAttachment@ is not @NULL@ and does not have
--     the value 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED',
--     @pDepthStencilAttachment@ /must/ not have the value
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED'
--
-- -   If @pDepthStencilResolveAttachment@ is not @NULL@ and does not have
--     the value 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED',
--     @depthResolveMode@ and @stencilResolveMode@ /must/ not both be
--     'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_NONE'
--
-- -   If @pDepthStencilResolveAttachment@ is not @NULL@ and does not have
--     the value 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED',
--     @pDepthStencilAttachment@ /must/ not have a sample count of
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'
--
-- -   If @pDepthStencilResolveAttachment@ is not @NULL@ and does not have
--     the value 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED',
--     @pDepthStencilResolveAttachment@ /must/ have a sample count of
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'
--
-- -   If @pDepthStencilResolveAttachment@ is not @NULL@ and does not have
--     the value 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' then it
--     /must/ have a format whose features contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   If the 'Vulkan.Core10.Enums.Format.Format' of
--     @pDepthStencilResolveAttachment@ has a depth component, then the
--     'Vulkan.Core10.Enums.Format.Format' of @pDepthStencilAttachment@
--     /must/ have a depth component with the same number of bits and
--     numerical type
--
-- -   If the 'Vulkan.Core10.Enums.Format.Format' of
--     @pDepthStencilResolveAttachment@ has a stencil component, then the
--     'Vulkan.Core10.Enums.Format.Format' of @pDepthStencilAttachment@
--     /must/ have a stencil component with the same number of bits and
--     numerical type
--
-- -   The value of @depthResolveMode@ /must/ be one of the bits set in
--     'PhysicalDeviceDepthStencilResolveProperties'::@supportedDepthResolveModes@
--     or 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_NONE'
--
-- -   The value of @stencilResolveMode@ /must/ be one of the bits set in
--     'PhysicalDeviceDepthStencilResolveProperties'::@supportedStencilResolveModes@
--     or 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_NONE'
--
-- -   If the 'Vulkan.Core10.Enums.Format.Format' of
--     @pDepthStencilResolveAttachment@ has both depth and stencil
--     components,
--     'PhysicalDeviceDepthStencilResolveProperties'::@independentResolve@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', and
--     'PhysicalDeviceDepthStencilResolveProperties'::@independentResolveNone@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', then the values of
--     @depthResolveMode@ and @stencilResolveMode@ /must/ be identical
--
-- -   If the 'Vulkan.Core10.Enums.Format.Format' of
--     @pDepthStencilResolveAttachment@ has both depth and stencil
--     components,
--     'PhysicalDeviceDepthStencilResolveProperties'::@independentResolve@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE' and
--     'PhysicalDeviceDepthStencilResolveProperties'::@independentResolveNone@
--     is 'Vulkan.Core10.FundamentalTypes.TRUE', then the values of
--     @depthResolveMode@ and @stencilResolveMode@ /must/ be identical or
--     one of them /must/ be
--     'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_NONE'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SUBPASS_DESCRIPTION_DEPTH_STENCIL_RESOLVE'
--
-- -   @depthResolveMode@ /must/ be a valid
--     'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlagBits' value
--
-- -   @stencilResolveMode@ /must/ be a valid
--     'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlagBits' value
--
-- -   If @pDepthStencilResolveAttachment@ is not @NULL@,
--     @pDepthStencilResolveAttachment@ /must/ be a valid pointer to a
--     valid
--     'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.AttachmentReference2'
--     structure
--
-- = See Also
--
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.AttachmentReference2',
-- 'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlagBits',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data SubpassDescriptionDepthStencilResolve = SubpassDescriptionDepthStencilResolve
  { -- | @depthResolveMode@ is a bitmask of
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlagBits' describing
    -- the depth resolve mode.
    SubpassDescriptionDepthStencilResolve -> ResolveModeFlags
depthResolveMode :: ResolveModeFlagBits
  , -- | @stencilResolveMode@ is a bitmask of
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlagBits' describing
    -- the stencil resolve mode.
    SubpassDescriptionDepthStencilResolve -> ResolveModeFlags
stencilResolveMode :: ResolveModeFlagBits
  , -- | @pDepthStencilResolveAttachment@ is an optional
    -- 'Vulkan.Core10.Pass.AttachmentReference' structure defining the
    -- depth\/stencil resolve attachment for this subpass and its layout.
    SubpassDescriptionDepthStencilResolve
-> Maybe (SomeStruct AttachmentReference2)
depthStencilResolveAttachment :: Maybe (SomeStruct AttachmentReference2)
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SubpassDescriptionDepthStencilResolve)
#endif
deriving instance Show SubpassDescriptionDepthStencilResolve

instance ToCStruct SubpassDescriptionDepthStencilResolve where
  withCStruct :: SubpassDescriptionDepthStencilResolve
-> (Ptr SubpassDescriptionDepthStencilResolve -> IO b) -> IO b
withCStruct x :: SubpassDescriptionDepthStencilResolve
x f :: Ptr SubpassDescriptionDepthStencilResolve -> IO b
f = Int
-> Int
-> (Ptr SubpassDescriptionDepthStencilResolve -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr SubpassDescriptionDepthStencilResolve -> IO b) -> IO b)
-> (Ptr SubpassDescriptionDepthStencilResolve -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SubpassDescriptionDepthStencilResolve
p -> Ptr SubpassDescriptionDepthStencilResolve
-> SubpassDescriptionDepthStencilResolve -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SubpassDescriptionDepthStencilResolve
p SubpassDescriptionDepthStencilResolve
x (Ptr SubpassDescriptionDepthStencilResolve -> IO b
f Ptr SubpassDescriptionDepthStencilResolve
p)
  pokeCStruct :: Ptr SubpassDescriptionDepthStencilResolve
-> SubpassDescriptionDepthStencilResolve -> IO b -> IO b
pokeCStruct p :: Ptr SubpassDescriptionDepthStencilResolve
p SubpassDescriptionDepthStencilResolve{..} 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 SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_DESCRIPTION_DEPTH_STENCIL_RESOLVE)
    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 SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve -> 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 ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ResolveModeFlagBits)) (ResolveModeFlags
depthResolveMode)
    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 ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ResolveModeFlagBits)) (ResolveModeFlags
stencilResolveMode)
    Ptr (AttachmentReference2 '[])
pDepthStencilResolveAttachment'' <- case (Maybe (SomeStruct AttachmentReference2)
depthStencilResolveAttachment) of
      Nothing -> Ptr (AttachmentReference2 '[])
-> ContT b IO (Ptr (AttachmentReference2 '[]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr (AttachmentReference2 '[])
forall a. Ptr a
nullPtr
      Just j :: SomeStruct AttachmentReference2
j -> ((Ptr (AttachmentReference2 '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 '[]))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (AttachmentReference2 '[])) (((Ptr (AttachmentReference2 '[]) -> IO b) -> IO b)
 -> ContT b IO (Ptr (AttachmentReference2 '[])))
-> ((Ptr (AttachmentReference2 '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 '[]))
forall a b. (a -> b) -> a -> b
$ \cont :: Ptr (AttachmentReference2 '[]) -> IO b
cont -> SomeStruct AttachmentReference2
-> (forall (es :: [*]).
    (Extendss AttachmentReference2 es, PokeChain es) =>
    Ptr (AttachmentReference2 es) -> IO b)
-> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
SomeStruct a
-> (forall (es :: [*]).
    (Extendss a es, PokeChain es) =>
    Ptr (a es) -> IO b)
-> IO b
withSomeCStruct @AttachmentReference2 (SomeStruct AttachmentReference2
j) (Ptr (AttachmentReference2 '[]) -> IO b
cont (Ptr (AttachmentReference2 '[]) -> IO b)
-> (Ptr (AttachmentReference2 es)
    -> Ptr (AttachmentReference2 '[]))
-> Ptr (AttachmentReference2 es)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (AttachmentReference2 es) -> Ptr (AttachmentReference2 '[])
forall a b. Ptr a -> Ptr b
castPtr)
    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 (AttachmentReference2 '[]))
-> Ptr (AttachmentReference2 '[]) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (AttachmentReference2 _)))) Ptr (AttachmentReference2 '[])
pDepthStencilResolveAttachment''
    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 SubpassDescriptionDepthStencilResolve -> IO b -> IO b
pokeZeroCStruct p :: Ptr SubpassDescriptionDepthStencilResolve
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_DESCRIPTION_DEPTH_STENCIL_RESOLVE)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ResolveModeFlagBits)) (ResolveModeFlags
forall a. Zero a => a
zero)
    Ptr ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ResolveModeFlagBits)) (ResolveModeFlags
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct SubpassDescriptionDepthStencilResolve where
  peekCStruct :: Ptr SubpassDescriptionDepthStencilResolve
-> IO SubpassDescriptionDepthStencilResolve
peekCStruct p :: Ptr SubpassDescriptionDepthStencilResolve
p = do
    ResolveModeFlags
depthResolveMode <- Ptr ResolveModeFlags -> IO ResolveModeFlags
forall a. Storable a => Ptr a -> IO a
peek @ResolveModeFlagBits ((Ptr SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ResolveModeFlagBits))
    ResolveModeFlags
stencilResolveMode <- Ptr ResolveModeFlags -> IO ResolveModeFlags
forall a. Storable a => Ptr a -> IO a
peek @ResolveModeFlagBits ((Ptr SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve
-> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ResolveModeFlagBits))
    Ptr (AttachmentReference2 Any)
pDepthStencilResolveAttachment <- Ptr (Ptr (AttachmentReference2 Any))
-> IO (Ptr (AttachmentReference2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentReference2 _)) ((Ptr SubpassDescriptionDepthStencilResolve
p Ptr SubpassDescriptionDepthStencilResolve
-> Int -> Ptr (Ptr (AttachmentReference2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (AttachmentReference2 a))))
    Maybe (SomeStruct AttachmentReference2)
pDepthStencilResolveAttachment' <- (Ptr (AttachmentReference2 Any)
 -> IO (SomeStruct AttachmentReference2))
-> Ptr (AttachmentReference2 Any)
-> IO (Maybe (SomeStruct AttachmentReference2))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr (AttachmentReference2 Any)
j -> Ptr (SomeStruct AttachmentReference2)
-> IO (SomeStruct AttachmentReference2)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
j))) Ptr (AttachmentReference2 Any)
pDepthStencilResolveAttachment
    SubpassDescriptionDepthStencilResolve
-> IO SubpassDescriptionDepthStencilResolve
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassDescriptionDepthStencilResolve
 -> IO SubpassDescriptionDepthStencilResolve)
-> SubpassDescriptionDepthStencilResolve
-> IO SubpassDescriptionDepthStencilResolve
forall a b. (a -> b) -> a -> b
$ ResolveModeFlags
-> ResolveModeFlags
-> Maybe (SomeStruct AttachmentReference2)
-> SubpassDescriptionDepthStencilResolve
SubpassDescriptionDepthStencilResolve
             ResolveModeFlags
depthResolveMode ResolveModeFlags
stencilResolveMode Maybe (SomeStruct AttachmentReference2)
pDepthStencilResolveAttachment'

instance Zero SubpassDescriptionDepthStencilResolve where
  zero :: SubpassDescriptionDepthStencilResolve
zero = ResolveModeFlags
-> ResolveModeFlags
-> Maybe (SomeStruct AttachmentReference2)
-> SubpassDescriptionDepthStencilResolve
SubpassDescriptionDepthStencilResolve
           ResolveModeFlags
forall a. Zero a => a
zero
           ResolveModeFlags
forall a. Zero a => a
zero
           Maybe (SomeStruct AttachmentReference2)
forall a. Maybe a
Nothing