{-# language CPP #-}
-- | = Name
--
-- VK_EXT_fragment_density_map2 - device extension
--
-- == VK_EXT_fragment_density_map2
--
-- [__Name String__]
--     @VK_EXT_fragment_density_map2@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     333
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_EXT_fragment_density_map@ to be enabled for any
--         device-level functionality
--
-- [__Contact__]
--
--     -   Matthew Netsch
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_fragment_density_map2] @mnetsch%0A*Here describe the issue or question you have about the VK_EXT_fragment_density_map2 extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2020-06-16
--
-- [__Interactions and External Dependencies__]
--
--     -   Interacts with Vulkan 1.1
--
-- [__Contributors__]
--
--     -   Matthew Netsch, Qualcomm Technologies, Inc.
--
--     -   Jonathan Tinkham, Qualcomm Technologies, Inc.
--
--     -   Jonathan Wicks, Qualcomm Technologies, Inc.
--
--     -   Jan-Harald Fredriksen, ARM
--
-- == Description
--
-- This extension adds additional features and properties to
-- @VK_EXT_fragment_density_map@ in order to reduce fragment density map
-- host latency as well as improved queries for subsampled sampler
-- implementation-dependent behavior.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceFragmentDensityMap2FeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceFragmentDensityMap2PropertiesEXT'
--
-- == New Enum Constants
--
-- -   'EXT_FRAGMENT_DENSITY_MAP_2_EXTENSION_NAME'
--
-- -   'EXT_FRAGMENT_DENSITY_MAP_2_SPEC_VERSION'
--
-- -   Extending
--     'Vulkan.Core10.Enums.ImageViewCreateFlagBits.ImageViewCreateFlagBits':
--
--     -   'Vulkan.Core10.Enums.ImageViewCreateFlagBits.IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_2_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_2_PROPERTIES_EXT'
--
-- == Version History
--
-- -   Revision 1, 2020-06-16 (Matthew Netsch)
--
--     -   Initial version
--
-- == See Also
--
-- 'PhysicalDeviceFragmentDensityMap2FeaturesEXT',
-- 'PhysicalDeviceFragmentDensityMap2PropertiesEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_fragment_density_map2 Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_EXT_fragment_density_map2  ( PhysicalDeviceFragmentDensityMap2FeaturesEXT(..)
                                                       , PhysicalDeviceFragmentDensityMap2PropertiesEXT(..)
                                                       , EXT_FRAGMENT_DENSITY_MAP_2_SPEC_VERSION
                                                       , pattern EXT_FRAGMENT_DENSITY_MAP_2_SPEC_VERSION
                                                       , EXT_FRAGMENT_DENSITY_MAP_2_EXTENSION_NAME
                                                       , pattern EXT_FRAGMENT_DENSITY_MAP_2_EXTENSION_NAME
                                                       ) 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.String (IsString)
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 Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_2_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_2_PROPERTIES_EXT))
-- | VkPhysicalDeviceFragmentDensityMap2FeaturesEXT - Structure describing
-- additional fragment density map features that can be supported by an
-- implementation
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceFragmentDensityMap2FeaturesEXT' 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. 'PhysicalDeviceFragmentDensityMap2FeaturesEXT' /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_EXT_fragment_density_map2 VK_EXT_fragment_density_map2>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceFragmentDensityMap2FeaturesEXT = PhysicalDeviceFragmentDensityMap2FeaturesEXT
  { -- | #features-fragmentDensityMapDeferred# @fragmentDensityMapDeferred@
    -- specifies whether the implementation supports deferred reads of fragment
    -- density map image views. If this feature is not enabled,
    -- 'Vulkan.Core10.Enums.ImageViewCreateFlagBits.IMAGE_VIEW_CREATE_FRAGMENT_DENSITY_MAP_DEFERRED_BIT_EXT'
    -- /must/ not be included in
    -- 'Vulkan.Core10.ImageView.ImageViewCreateInfo'::@flags@.
    PhysicalDeviceFragmentDensityMap2FeaturesEXT -> Bool
fragmentDensityMapDeferred :: Bool }
  deriving (Typeable, PhysicalDeviceFragmentDensityMap2FeaturesEXT
-> PhysicalDeviceFragmentDensityMap2FeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceFragmentDensityMap2FeaturesEXT
-> PhysicalDeviceFragmentDensityMap2FeaturesEXT -> Bool
$c/= :: PhysicalDeviceFragmentDensityMap2FeaturesEXT
-> PhysicalDeviceFragmentDensityMap2FeaturesEXT -> Bool
== :: PhysicalDeviceFragmentDensityMap2FeaturesEXT
-> PhysicalDeviceFragmentDensityMap2FeaturesEXT -> Bool
$c== :: PhysicalDeviceFragmentDensityMap2FeaturesEXT
-> PhysicalDeviceFragmentDensityMap2FeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceFragmentDensityMap2FeaturesEXT)
#endif
deriving instance Show PhysicalDeviceFragmentDensityMap2FeaturesEXT

instance ToCStruct PhysicalDeviceFragmentDensityMap2FeaturesEXT where
  withCStruct :: forall b.
PhysicalDeviceFragmentDensityMap2FeaturesEXT
-> (Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceFragmentDensityMap2FeaturesEXT
x Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
p PhysicalDeviceFragmentDensityMap2FeaturesEXT
x (Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT -> IO b
f Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
-> PhysicalDeviceFragmentDensityMap2FeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
p PhysicalDeviceFragmentDensityMap2FeaturesEXT{Bool
fragmentDensityMapDeferred :: Bool
$sel:fragmentDensityMapDeferred:PhysicalDeviceFragmentDensityMap2FeaturesEXT :: PhysicalDeviceFragmentDensityMap2FeaturesEXT -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_2_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
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 PhysicalDeviceFragmentDensityMap2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
fragmentDensityMapDeferred))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_2_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
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 PhysicalDeviceFragmentDensityMap2FeaturesEXT
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 PhysicalDeviceFragmentDensityMap2FeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
-> IO PhysicalDeviceFragmentDensityMap2FeaturesEXT
peekCStruct Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
p = do
    Bool32
fragmentDensityMapDeferred <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceFragmentDensityMap2FeaturesEXT
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 -> PhysicalDeviceFragmentDensityMap2FeaturesEXT
PhysicalDeviceFragmentDensityMap2FeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
fragmentDensityMapDeferred)

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

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


-- | VkPhysicalDeviceFragmentDensityMap2PropertiesEXT - Structure describing
-- additional fragment density map properties that can be supported by an
-- implementation
--
-- = Description
--
-- If the 'PhysicalDeviceFragmentDensityMap2PropertiesEXT' 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_EXT_fragment_density_map2 VK_EXT_fragment_density_map2>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceFragmentDensityMap2PropertiesEXT = PhysicalDeviceFragmentDensityMap2PropertiesEXT
  { -- | #limits-subsampledLoads# @subsampledLoads@ specifies if performing image
    -- data read with load operations on subsampled attachments will be
    -- resampled to the fragment density of the render pass
    PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Bool
subsampledLoads :: Bool
  , -- | #limits-subsampledCoarseReconstructionEarlyAccess#
    -- @subsampledCoarseReconstructionEarlyAccess@ specifies if performing
    -- image data read with samplers created with @flags@ containing
    -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_SUBSAMPLED_COARSE_RECONSTRUCTION_BIT_EXT'
    -- in fragment shader will trigger additional reads during
    -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_VERTEX_SHADER_BIT'
    PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Bool
subsampledCoarseReconstructionEarlyAccess :: Bool
  , -- | #limits-maxSubsampledArrayLayers# @maxSubsampledArrayLayers@ is the
    -- maximum number of 'Vulkan.Core10.Handles.ImageView' array layers for
    -- usages supporting subsampled samplers
    PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Word32
maxSubsampledArrayLayers :: Word32
  , -- | #limits-maxDescriptorSetSubsampledSamplers#
    -- @maxDescriptorSetSubsampledSamplers@ is the maximum number of subsampled
    -- samplers that /can/ be included in a
    -- 'Vulkan.Core10.Handles.PipelineLayout'
    PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Word32
maxDescriptorSetSubsampledSamplers :: Word32
  }
  deriving (Typeable, PhysicalDeviceFragmentDensityMap2PropertiesEXT
-> PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceFragmentDensityMap2PropertiesEXT
-> PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Bool
$c/= :: PhysicalDeviceFragmentDensityMap2PropertiesEXT
-> PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Bool
== :: PhysicalDeviceFragmentDensityMap2PropertiesEXT
-> PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Bool
$c== :: PhysicalDeviceFragmentDensityMap2PropertiesEXT
-> PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceFragmentDensityMap2PropertiesEXT)
#endif
deriving instance Show PhysicalDeviceFragmentDensityMap2PropertiesEXT

instance ToCStruct PhysicalDeviceFragmentDensityMap2PropertiesEXT where
  withCStruct :: forall b.
PhysicalDeviceFragmentDensityMap2PropertiesEXT
-> (Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceFragmentDensityMap2PropertiesEXT
x Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p PhysicalDeviceFragmentDensityMap2PropertiesEXT
x (Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT -> IO b
f Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
-> PhysicalDeviceFragmentDensityMap2PropertiesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p PhysicalDeviceFragmentDensityMap2PropertiesEXT{Bool
Word32
maxDescriptorSetSubsampledSamplers :: Word32
maxSubsampledArrayLayers :: Word32
subsampledCoarseReconstructionEarlyAccess :: Bool
subsampledLoads :: Bool
$sel:maxDescriptorSetSubsampledSamplers:PhysicalDeviceFragmentDensityMap2PropertiesEXT :: PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Word32
$sel:maxSubsampledArrayLayers:PhysicalDeviceFragmentDensityMap2PropertiesEXT :: PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Word32
$sel:subsampledCoarseReconstructionEarlyAccess:PhysicalDeviceFragmentDensityMap2PropertiesEXT :: PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Bool
$sel:subsampledLoads:PhysicalDeviceFragmentDensityMap2PropertiesEXT :: PhysicalDeviceFragmentDensityMap2PropertiesEXT -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_2_PROPERTIES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
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 PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
subsampledLoads))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
subsampledCoarseReconstructionEarlyAccess))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (Word32
maxSubsampledArrayLayers)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32)) (Word32
maxDescriptorSetSubsampledSamplers)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_2_PROPERTIES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
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 PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceFragmentDensityMap2PropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
-> IO PhysicalDeviceFragmentDensityMap2PropertiesEXT
peekCStruct Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p = do
    Bool32
subsampledLoads <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    Bool32
subsampledCoarseReconstructionEarlyAccess <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    Word32
maxSubsampledArrayLayers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
    Word32
maxDescriptorSetSubsampledSamplers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceFragmentDensityMap2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Word32
-> Word32
-> PhysicalDeviceFragmentDensityMap2PropertiesEXT
PhysicalDeviceFragmentDensityMap2PropertiesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
subsampledLoads)
             (Bool32 -> Bool
bool32ToBool Bool32
subsampledCoarseReconstructionEarlyAccess)
             Word32
maxSubsampledArrayLayers
             Word32
maxDescriptorSetSubsampledSamplers

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

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


type EXT_FRAGMENT_DENSITY_MAP_2_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_FRAGMENT_DENSITY_MAP_2_SPEC_VERSION"
pattern EXT_FRAGMENT_DENSITY_MAP_2_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_FRAGMENT_DENSITY_MAP_2_SPEC_VERSION :: forall a. Integral a => a
$mEXT_FRAGMENT_DENSITY_MAP_2_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_FRAGMENT_DENSITY_MAP_2_SPEC_VERSION = 1


type EXT_FRAGMENT_DENSITY_MAP_2_EXTENSION_NAME = "VK_EXT_fragment_density_map2"

-- No documentation found for TopLevel "VK_EXT_FRAGMENT_DENSITY_MAP_2_EXTENSION_NAME"
pattern EXT_FRAGMENT_DENSITY_MAP_2_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_FRAGMENT_DENSITY_MAP_2_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_FRAGMENT_DENSITY_MAP_2_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_FRAGMENT_DENSITY_MAP_2_EXTENSION_NAME = "VK_EXT_fragment_density_map2"