{-# language CPP #-}
-- | = Name
--
-- VK_EXT_shader_tile_image - device extension
--
-- == VK_EXT_shader_tile_image
--
-- [__Name String__]
--     @VK_EXT_shader_tile_image@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     396
--
-- [__Revision__]
--     1
--
-- [__Ratification Status__]
--     Ratified
--
-- [__Extension and Version Dependencies__]
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#versions-1.3 Version 1.3>
--
-- [__Contact__]
--
--     -   Jan-Harald Fredriksen
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_shader_tile_image] @janharaldfredriksen-arm%0A*Here describe the issue or question you have about the VK_EXT_shader_tile_image extension* >
--
-- [__Extension Proposal__]
--     <https://github.com/KhronosGroup/Vulkan-Docs/tree/main/proposals/VK_EXT_shader_tile_image.adoc VK_EXT_shader_tile_image>
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2023-03-23
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Interactions and External Dependencies__]
--
--     -   This extension requires
--         <https://htmlpreview.github.io/?https://github.com/KhronosGroup/SPIRV-Registry/blob/master/extensions/EXT/SPV_EXT_shader_tile_image.html SPV_EXT_shader_tile_image>
--
--     -   This extension provides API support for
--         <https://raw.githubusercontent.com/KhronosGroup/GLSL/master/extensions/ext/GLSL_EXT_shader_tile_image.txt GL_EXT_shader_tile_image>
--
-- [__Contributors__]
--
--     -   Sandeep Kakarlapudi, Arm
--
--     -   Jan-Harald Fredriksen, Arm
--
--     -   James Fitzpatrick, Imagination
--
--     -   Andrew Garrard, Imagination
--
--     -   Jeff Leger, Qualcomm
--
--     -   Huilong Wang, Huawei
--
--     -   Graeme Leese, Broadcom
--
--     -   Hans-Kristian Arntzen, Valve
--
--     -   Tobias Hector, AMD
--
--     -   Jeff Bolz, NVIDIA
--
--     -   Shahbaz Youssefi, Google
--
-- == Description
--
-- This extension allows fragment shader invocations to read color, depth
-- and stencil values at their pixel location in rasterization order. The
-- functionality is only available when using dynamic render passes
-- introduced by VK_KHR_dynamic_rendering. Example use cases are
-- programmable blending and deferred shading.
--
-- See
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#fragops-shader-tileimage-reads fragment shader tile image reads>
-- for more information.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceShaderTileImageFeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceShaderTileImagePropertiesEXT'
--
-- == New Enum Constants
--
-- -   'EXT_SHADER_TILE_IMAGE_EXTENSION_NAME'
--
-- -   'EXT_SHADER_TILE_IMAGE_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_TILE_IMAGE_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_TILE_IMAGE_PROPERTIES_EXT'
--
-- == Issues
--
-- None.
--
-- == Examples
--
-- Color read example.
--
-- > layout( location = 0 /* aliased to color attachment 0 */ ) tileImageEXT highp attachmentEXT color0;
-- > layout( location = 1 /* aliased to color attachment 1 */ ) tileImageEXT highp attachmentEXT color1;
-- >
-- > layout( location = 0 ) out vec4 fragColor;
-- >
-- > void main()
-- > {
-- >     vec4 value = colorAttachmentReadEXT(color0) + colorAttachmentReadEXT(color1);
-- >     fragColor = value;
-- > }
--
-- Depth & Stencil read example.
--
-- > void main()
-- > {
-- >     // read sample 0: works for non-MSAA or MSAA targets
-- >     highp float last_depth = depthAttachmentReadEXT();
-- >     lowp uint last_stencil = stencilAttachmentReadEXT();
-- >
-- >     //..
-- > }
--
-- == Version History
--
-- -   Revision 1, 2023-03-23 (Sandeep Kakarlapudi)
--
--     -   Initial version
--
-- == See Also
--
-- 'PhysicalDeviceShaderTileImageFeaturesEXT',
-- 'PhysicalDeviceShaderTileImagePropertiesEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_shader_tile_image 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_shader_tile_image  ( PhysicalDeviceShaderTileImageFeaturesEXT(..)
                                                   , PhysicalDeviceShaderTileImagePropertiesEXT(..)
                                                   , EXT_SHADER_TILE_IMAGE_SPEC_VERSION
                                                   , pattern EXT_SHADER_TILE_IMAGE_SPEC_VERSION
                                                   , EXT_SHADER_TILE_IMAGE_EXTENSION_NAME
                                                   , pattern EXT_SHADER_TILE_IMAGE_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.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_SHADER_TILE_IMAGE_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_TILE_IMAGE_PROPERTIES_EXT))
-- | VkPhysicalDeviceShaderTileImageFeaturesEXT - Structure describing tile
-- image features supported by the implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceShaderTileImageFeaturesEXT' structure
-- describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceShaderTileImageFeaturesEXT' 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. 'PhysicalDeviceShaderTileImageFeaturesEXT' /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_shader_tile_image VK_EXT_shader_tile_image>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceShaderTileImageFeaturesEXT = PhysicalDeviceShaderTileImageFeaturesEXT
  { -- | #features-shaderTileImageColorReadAccess#
    -- @shaderTileImageColorReadAccess@ indicates that the implementation
    -- supports the @TileImageColorReadAccessEXT@ SPIR-V capability.
    PhysicalDeviceShaderTileImageFeaturesEXT -> Bool
shaderTileImageColorReadAccess :: Bool
  , -- | #features-shaderTileImageDepthReadAccess#
    -- @shaderTileImageDepthReadAccess@ indicates that the implementation
    -- supports the @TileImageDepthReadAccessEXT@ SPIR-V capability.
    PhysicalDeviceShaderTileImageFeaturesEXT -> Bool
shaderTileImageDepthReadAccess :: Bool
  , -- | #features-shaderTileImageStencilReadAccess#
    -- @shaderTileImageStencilReadAccess@ indicates that the implementation
    -- supports the @TileImageStencilReadAccessEXT@ SPIR-V capability.
    PhysicalDeviceShaderTileImageFeaturesEXT -> Bool
shaderTileImageStencilReadAccess :: Bool
  }
  deriving (Typeable, PhysicalDeviceShaderTileImageFeaturesEXT
-> PhysicalDeviceShaderTileImageFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceShaderTileImageFeaturesEXT
-> PhysicalDeviceShaderTileImageFeaturesEXT -> Bool
$c/= :: PhysicalDeviceShaderTileImageFeaturesEXT
-> PhysicalDeviceShaderTileImageFeaturesEXT -> Bool
== :: PhysicalDeviceShaderTileImageFeaturesEXT
-> PhysicalDeviceShaderTileImageFeaturesEXT -> Bool
$c== :: PhysicalDeviceShaderTileImageFeaturesEXT
-> PhysicalDeviceShaderTileImageFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceShaderTileImageFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceShaderTileImageFeaturesEXT

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

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

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

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


-- | VkPhysicalDeviceShaderTileImagePropertiesEXT - Structure containing
-- information about tile image support for a physical device
--
-- = Description
--
-- If the 'PhysicalDeviceShaderTileImagePropertiesEXT' 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.
--
-- These are properties of the tile image information of a physical device.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_tile_image VK_EXT_shader_tile_image>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceShaderTileImagePropertiesEXT = PhysicalDeviceShaderTileImagePropertiesEXT
  { -- | @shaderTileImageCoherentReadAccelerated@ is a boolean that will be
    -- 'Vulkan.Core10.FundamentalTypes.TRUE' if coherent reads of tile image
    -- data is accelerated.
    PhysicalDeviceShaderTileImagePropertiesEXT -> Bool
shaderTileImageCoherentReadAccelerated :: Bool
  , -- | @shaderTileImageReadSampleFromPixelRateInvocation@ is a boolean that
    -- will be 'Vulkan.Core10.FundamentalTypes.TRUE' if reading from samples
    -- from a pixel rate fragment invocation is supported when
    -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@rasterizationSamples@
    -- > 1.
    PhysicalDeviceShaderTileImagePropertiesEXT -> Bool
shaderTileImageReadSampleFromPixelRateInvocation :: Bool
  , -- | @shaderTileImageReadFromHelperInvocation@ is a boolean that will be
    -- 'Vulkan.Core10.FundamentalTypes.TRUE' if reads of tile image data from
    -- helper fragment invocations result in valid values.
    PhysicalDeviceShaderTileImagePropertiesEXT -> Bool
shaderTileImageReadFromHelperInvocation :: Bool
  }
  deriving (Typeable, PhysicalDeviceShaderTileImagePropertiesEXT
-> PhysicalDeviceShaderTileImagePropertiesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceShaderTileImagePropertiesEXT
-> PhysicalDeviceShaderTileImagePropertiesEXT -> Bool
$c/= :: PhysicalDeviceShaderTileImagePropertiesEXT
-> PhysicalDeviceShaderTileImagePropertiesEXT -> Bool
== :: PhysicalDeviceShaderTileImagePropertiesEXT
-> PhysicalDeviceShaderTileImagePropertiesEXT -> Bool
$c== :: PhysicalDeviceShaderTileImagePropertiesEXT
-> PhysicalDeviceShaderTileImagePropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceShaderTileImagePropertiesEXT)
#endif
deriving instance Show PhysicalDeviceShaderTileImagePropertiesEXT

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

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

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

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


type EXT_SHADER_TILE_IMAGE_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_SHADER_TILE_IMAGE_SPEC_VERSION"
pattern EXT_SHADER_TILE_IMAGE_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_SHADER_TILE_IMAGE_SPEC_VERSION :: forall a. Integral a => a
$mEXT_SHADER_TILE_IMAGE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_SHADER_TILE_IMAGE_SPEC_VERSION = 1


type EXT_SHADER_TILE_IMAGE_EXTENSION_NAME = "VK_EXT_shader_tile_image"

-- No documentation found for TopLevel "VK_EXT_SHADER_TILE_IMAGE_EXTENSION_NAME"
pattern EXT_SHADER_TILE_IMAGE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_SHADER_TILE_IMAGE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_SHADER_TILE_IMAGE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_SHADER_TILE_IMAGE_EXTENSION_NAME = "VK_EXT_shader_tile_image"