{-# language CPP #-}
-- | = Name
--
-- VK_QCOM_image_processing2 - device extension
--
-- == VK_QCOM_image_processing2
--
-- [__Name String__]
--     @VK_QCOM_image_processing2@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     519
--
-- [__Revision__]
--     1
--
-- [__Ratification Status__]
--     Not ratified
--
-- [__Extension and Version Dependencies__]
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_QCOM_image_processing VK_QCOM_image_processing>
--
-- [__Contact__]
--
--     -   Jeff Leger
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_QCOM_image_processing2] @jackohound%0A*Here describe the issue or question you have about the VK_QCOM_image_processing2 extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2023-03-10
--
-- [__Interactions and External Dependencies__]
--
--     -   This extension requires
--         <https://htmlpreview.github.io/?https://github.com/KhronosGroup/SPIRV-Registry/blob/master/extensions/QCOM/SPV_QCOM_image_processing2.html SPV_QCOM_image_processing2>
--
--     -   This extension provides API support for
--         <https://github.com/KhronosGroup/GLSL/blob/master/extensions/qcom/GLSL_QCOM_image_processing2.txt GL_QCOM_image_processing2>
--
-- [__Contributors__]
--
--     -   Jeff Leger, Qualcomm Technologies, Inc.
--
-- == Description
--
-- This extension enables support for the SPIR-V @TextureBlockMatch2QCOM@
-- capability. It builds on the functionality of QCOM_image_processing with
-- the addition of 4 new image processing operations.
--
-- -   The @opImageBlockMatchWindowSADQCOM@\` SPIR-V instruction builds
--     upon the functionality of @opImageBlockMatchSADQCOM@\` by repeatedly
--     performing block match operations across a 2D window. The “2D
--     windowExtent” and “compareMode” are are specified by
--     'SamplerBlockMatchWindowCreateInfoQCOM' in the sampler used to
--     create the /target image/. Like @OpImageBlockMatchSADQCOM@,
--     @opImageBlockMatchWindowSADQCOM@ computes an error metric, that
--     describes whether a block of texels in the /target image/ matches a
--     corresponding block of texels in the /reference image/. Unlike
--     @OpImageBlockMatchSADQCOM@, this instruction computes an error
--     metric at each (X,Y) location within the 2D window and returns
--     either the minimum or maximum error. The instruction only supports
--     single-component formats. Refer to the pseudocode below for details.
--
-- -   The @opImageBlockMatchWindowSSDQCOM@ follows the same pattern,
--     computing the SSD error metric at each location within the 2D
--     window.
--
-- -   The @opImageBlockMatchGatherSADQCOM@ builds upon
--     @OpImageBlockMatchSADQCOM@. This instruction computes an error
--     metric, that describes whether a block of texels in the /target
--     image/ matches a corresponding block of texels in the /reference
--     image/. The instruction computes the SAD error metric at 4 texel
--     offsets and returns the error metric for each offset in the
--     X,Y,Z,and W components. The instruction only supports
--     single-component texture formats. Refer to the pseudocode below for
--     details.
--
-- -   The @opImageBlockMatchGatherSSDQCOM@ follows the same pattern,
--     computing the SSD error metric for 4 offsets.
--
-- Each of the above 4 image processing instructions are limited to
-- single-component formats.
--
-- Below is the pseudocode for GLSL built-in function
-- @textureWindowBlockMatchSADQCOM@. The pseudocode for
-- @textureWindowBlockMatchSSD@ is identical other than replacing all
-- instances of @\"SAD\"@ with @\"SSD\"@.
--
-- > vec4 textureBlockMatchWindowSAD( sampler2D target,
-- >                                  uvec2 targetCoord,
-- >                                  samler2D reference,
-- >                                  uvec2 refCoord,
-- >                                  uvec2 blocksize) {
-- >     // compareMode (MIN or MAX) comes from the vkSampler associated with `target`
-- >     // uvec2 window  comes from the vkSampler associated with `target`
-- >     minSAD = INF;
-- >     maxSAD = -INF;
-- >     uvec2 minCoord;
-- >     uvec2 maxCoord;
-- >
-- >     for (uint x=0, x < window.width; x++) {
-- >         for (uint y=0; y < window.height; y++) {
-- >             float SAD = textureBlockMatchSAD(target,
-- >                                             targetCoord + uvec2(x, y),
-- >                                             reference,
-- >                                             refCoord,
-- >                                             blocksize).x;
-- >             // Note: the below comparison operator will produce undefined results
-- >             // if SAD is a denorm value.
-- >             if (SAD < minSAD) {
-- >                 minSAD = SAD;
-- >                 minCoord = uvec2(x,y);
-- >             }
-- >             if (SAD > maxSAD) {
-- >                 maxSAD = SAD;
-- >                 maxCoord = uvec2(x,y);
-- >             }
-- >         }
-- >     }
-- >     if (compareMode=MIN) {
-- >         return vec4(minSAD, minCoord.x, minCoord.y, 0.0);
-- >     } else {
-- >         return vec4(maxSAD, maxCoord.x, maxCoord.y, 0.0);
-- >     }
-- > }
--
-- Below is the pseudocode for @textureBlockMatchGatherSADQCOM@. The
-- pseudocode for @textureBlockMatchGatherSSD@ follows an identical
-- pattern.
--
-- > vec4 textureBlockMatchGatherSAD( sampler2D target,
-- >                                  uvec2 targetCoord,
-- >                                  samler2D reference,
-- >                                  uvec2 refCoord,
-- >                                  uvec2 blocksize) {
-- >     vec4 out;
-- >     for (uint x=0, x<4; x++) {
-- >             float SAD = textureBlockMatchSAD(target,
-- >                                             targetCoord + uvec2(x, 0),
-- >                                             reference,
-- >                                             refCoord,
-- >                                             blocksize).x;
-- >             out[x] = SAD;
-- >     }
-- >     return out;
-- > }
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceImageProcessing2FeaturesQCOM'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceImageProcessing2PropertiesQCOM'
--
-- -   Extending 'Vulkan.Core10.Sampler.SamplerCreateInfo':
--
--     -   'SamplerBlockMatchWindowCreateInfoQCOM'
--
-- == New Enums
--
-- -   'BlockMatchWindowCompareModeQCOM'
--
-- == New Enum Constants
--
-- -   'QCOM_IMAGE_PROCESSING_2_EXTENSION_NAME'
--
-- -   'QCOM_IMAGE_PROCESSING_2_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_FEATURES_QCOM'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_PROPERTIES_QCOM'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SAMPLER_BLOCK_MATCH_WINDOW_CREATE_INFO_QCOM'
--
-- == Issues
--
-- 1) What is the precision of the min\/max comparison checks?
--
-- __RESOLVED__: Intermediate computations for the new operations are
-- performed at 16-bit floating point precision. If the value of
-- @\"float SAD\"@ in the above code sample is a 16-bit denorm value, then
-- behavior of the MIN\/MAX comparison is undefined.
--
-- == Version History
--
-- -   Revision 1, 2023-03-10 (Jeff Leger)
--
-- == See Also
--
-- 'BlockMatchWindowCompareModeQCOM',
-- 'PhysicalDeviceImageProcessing2FeaturesQCOM',
-- 'PhysicalDeviceImageProcessing2PropertiesQCOM',
-- 'SamplerBlockMatchWindowCreateInfoQCOM'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_QCOM_image_processing2 Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_QCOM_image_processing2  ( PhysicalDeviceImageProcessing2FeaturesQCOM(..)
                                                    , PhysicalDeviceImageProcessing2PropertiesQCOM(..)
                                                    , SamplerBlockMatchWindowCreateInfoQCOM(..)
                                                    , BlockMatchWindowCompareModeQCOM( BLOCK_MATCH_WINDOW_COMPARE_MODE_MIN_QCOM
                                                                                     , BLOCK_MATCH_WINDOW_COMPARE_MODE_MAX_QCOM
                                                                                     , ..
                                                                                     )
                                                    , QCOM_IMAGE_PROCESSING_2_SPEC_VERSION
                                                    , pattern QCOM_IMAGE_PROCESSING_2_SPEC_VERSION
                                                    , QCOM_IMAGE_PROCESSING_2_EXTENSION_NAME
                                                    , pattern QCOM_IMAGE_PROCESSING_2_EXTENSION_NAME
                                                    ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showsPrec)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
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 Data.Int (Int32)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (Extent2D)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_FEATURES_QCOM))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_PROPERTIES_QCOM))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SAMPLER_BLOCK_MATCH_WINDOW_CREATE_INFO_QCOM))
-- | VkPhysicalDeviceImageProcessing2FeaturesQCOM - Structure describing
-- image processing features that can be supported by an implementation
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceImageProcessing2FeaturesQCOM' 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. 'PhysicalDeviceImageProcessing2FeaturesQCOM' /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_QCOM_image_processing2 VK_QCOM_image_processing2>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceImageProcessing2FeaturesQCOM = PhysicalDeviceImageProcessing2FeaturesQCOM
  { -- | #features-textureBlockMatch2# @textureBlockMatch2@ indicates that the
    -- implementation supports shader modules that declare the
    -- @TextureBlockMatch2QCOM@ capability.
    PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
textureBlockMatch2 :: Bool }
  deriving (Typeable, PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
$c/= :: PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
== :: PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
$c== :: PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceImageProcessing2FeaturesQCOM)
#endif
deriving instance Show PhysicalDeviceImageProcessing2FeaturesQCOM

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

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

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


-- | VkPhysicalDeviceImageProcessing2PropertiesQCOM - Structure containing
-- image processing2 properties
--
-- = Description
--
-- -   #limits-blockmatch-maxWindowExtent#@maxBlockMatchWindow@ is a
--     'Vulkan.Core10.FundamentalTypes.Extent2D' describing the largest
--     dimensions (@width@ and @height@) that /can/ be specified for the
--     block match window.
--
-- If the 'PhysicalDeviceImageProcessing2PropertiesQCOM' 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 image processing2 information of a physical
-- device.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkPhysicalDeviceImageProcessing2PropertiesQCOM-sType-sType#
--     @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_PROPERTIES_QCOM'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_QCOM_image_processing2 VK_QCOM_image_processing2>,
-- 'Vulkan.Core10.FundamentalTypes.Extent2D',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceImageProcessing2PropertiesQCOM = PhysicalDeviceImageProcessing2PropertiesQCOM
  { -- No documentation found for Nested "VkPhysicalDeviceImageProcessing2PropertiesQCOM" "maxBlockMatchWindow"
    PhysicalDeviceImageProcessing2PropertiesQCOM -> Extent2D
maxBlockMatchWindow :: Extent2D }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceImageProcessing2PropertiesQCOM)
#endif
deriving instance Show PhysicalDeviceImageProcessing2PropertiesQCOM

instance ToCStruct PhysicalDeviceImageProcessing2PropertiesQCOM where
  withCStruct :: forall b.
PhysicalDeviceImageProcessing2PropertiesQCOM
-> (Ptr PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b)
-> IO b
withCStruct PhysicalDeviceImageProcessing2PropertiesQCOM
x Ptr PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p PhysicalDeviceImageProcessing2PropertiesQCOM
x (Ptr PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b
f Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p PhysicalDeviceImageProcessing2PropertiesQCOM{Extent2D
maxBlockMatchWindow :: Extent2D
$sel:maxBlockMatchWindow:PhysicalDeviceImageProcessing2PropertiesQCOM :: PhysicalDeviceImageProcessing2PropertiesQCOM -> Extent2D
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_PROPERTIES_QCOM)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
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 PhysicalDeviceImageProcessing2PropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D)) (Extent2D
maxBlockMatchWindow)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_PROPERTIES_QCOM)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct PhysicalDeviceImageProcessing2PropertiesQCOM where
  peekCStruct :: Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> IO PhysicalDeviceImageProcessing2PropertiesQCOM
peekCStruct Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p = do
    Extent2D
maxBlockMatchWindow <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Extent2D -> PhysicalDeviceImageProcessing2PropertiesQCOM
PhysicalDeviceImageProcessing2PropertiesQCOM
             Extent2D
maxBlockMatchWindow

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

instance Zero PhysicalDeviceImageProcessing2PropertiesQCOM where
  zero :: PhysicalDeviceImageProcessing2PropertiesQCOM
zero = Extent2D -> PhysicalDeviceImageProcessing2PropertiesQCOM
PhysicalDeviceImageProcessing2PropertiesQCOM
           forall a. Zero a => a
zero


-- | VkSamplerBlockMatchWindowCreateInfoQCOM - Structure specifying the block
-- match window parameters
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_QCOM_image_processing2 VK_QCOM_image_processing2>,
-- 'BlockMatchWindowCompareModeQCOM',
-- 'Vulkan.Core10.FundamentalTypes.Extent2D',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data SamplerBlockMatchWindowCreateInfoQCOM = SamplerBlockMatchWindowCreateInfoQCOM
  { -- | @windowExtent@ is a 'Vulkan.Core10.FundamentalTypes.Extent2D' specifying
    -- a the width and height of the block match window.
    SamplerBlockMatchWindowCreateInfoQCOM -> Extent2D
windowExtent :: Extent2D
  , -- | @windowCompareMode@ is a 'BlockMatchWindowCompareModeQCOM' specifying
    -- the compare mode.
    --
    -- #VUID-VkSamplerBlockMatchWindowCreateInfoQCOM-windowCompareMode-parameter#
    -- @windowCompareMode@ /must/ be a valid 'BlockMatchWindowCompareModeQCOM'
    -- value
    SamplerBlockMatchWindowCreateInfoQCOM
-> BlockMatchWindowCompareModeQCOM
windowCompareMode :: BlockMatchWindowCompareModeQCOM
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SamplerBlockMatchWindowCreateInfoQCOM)
#endif
deriving instance Show SamplerBlockMatchWindowCreateInfoQCOM

instance ToCStruct SamplerBlockMatchWindowCreateInfoQCOM where
  withCStruct :: forall b.
SamplerBlockMatchWindowCreateInfoQCOM
-> (Ptr SamplerBlockMatchWindowCreateInfoQCOM -> IO b) -> IO b
withCStruct SamplerBlockMatchWindowCreateInfoQCOM
x Ptr SamplerBlockMatchWindowCreateInfoQCOM -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr SamplerBlockMatchWindowCreateInfoQCOM
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SamplerBlockMatchWindowCreateInfoQCOM
p SamplerBlockMatchWindowCreateInfoQCOM
x (Ptr SamplerBlockMatchWindowCreateInfoQCOM -> IO b
f Ptr SamplerBlockMatchWindowCreateInfoQCOM
p)
  pokeCStruct :: forall b.
Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> SamplerBlockMatchWindowCreateInfoQCOM -> IO b -> IO b
pokeCStruct Ptr SamplerBlockMatchWindowCreateInfoQCOM
p SamplerBlockMatchWindowCreateInfoQCOM{Extent2D
BlockMatchWindowCompareModeQCOM
windowCompareMode :: BlockMatchWindowCompareModeQCOM
windowExtent :: Extent2D
$sel:windowCompareMode:SamplerBlockMatchWindowCreateInfoQCOM :: SamplerBlockMatchWindowCreateInfoQCOM
-> BlockMatchWindowCompareModeQCOM
$sel:windowExtent:SamplerBlockMatchWindowCreateInfoQCOM :: SamplerBlockMatchWindowCreateInfoQCOM -> Extent2D
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SAMPLER_BLOCK_MATCH_WINDOW_CREATE_INFO_QCOM)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
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 SamplerBlockMatchWindowCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D)) (Extent2D
windowExtent)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BlockMatchWindowCompareModeQCOM)) (BlockMatchWindowCompareModeQCOM
windowCompareMode)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr SamplerBlockMatchWindowCreateInfoQCOM -> IO b -> IO b
pokeZeroCStruct Ptr SamplerBlockMatchWindowCreateInfoQCOM
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SAMPLER_BLOCK_MATCH_WINDOW_CREATE_INFO_QCOM)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
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 SamplerBlockMatchWindowCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BlockMatchWindowCompareModeQCOM)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct SamplerBlockMatchWindowCreateInfoQCOM where
  peekCStruct :: Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> IO SamplerBlockMatchWindowCreateInfoQCOM
peekCStruct Ptr SamplerBlockMatchWindowCreateInfoQCOM
p = do
    Extent2D
windowExtent <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D))
    BlockMatchWindowCompareModeQCOM
windowCompareMode <- forall a. Storable a => Ptr a -> IO a
peek @BlockMatchWindowCompareModeQCOM ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BlockMatchWindowCompareModeQCOM))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Extent2D
-> BlockMatchWindowCompareModeQCOM
-> SamplerBlockMatchWindowCreateInfoQCOM
SamplerBlockMatchWindowCreateInfoQCOM
             Extent2D
windowExtent BlockMatchWindowCompareModeQCOM
windowCompareMode

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

instance Zero SamplerBlockMatchWindowCreateInfoQCOM where
  zero :: SamplerBlockMatchWindowCreateInfoQCOM
zero = Extent2D
-> BlockMatchWindowCompareModeQCOM
-> SamplerBlockMatchWindowCreateInfoQCOM
SamplerBlockMatchWindowCreateInfoQCOM
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkBlockMatchWindowCompareModeQCOM - Block match window compare modes
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_QCOM_image_processing2 VK_QCOM_image_processing2>,
-- 'SamplerBlockMatchWindowCreateInfoQCOM'
newtype BlockMatchWindowCompareModeQCOM = BlockMatchWindowCompareModeQCOM Int32
  deriving newtype (BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
$c/= :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
== :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
$c== :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
Eq, Eq BlockMatchWindowCompareModeQCOM
BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Ordering
BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
$cmin :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
max :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
$cmax :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
>= :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
$c>= :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
> :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
$c> :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
<= :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
$c<= :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
< :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
$c< :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
compare :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Ordering
$ccompare :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Ordering
Ord, Ptr BlockMatchWindowCompareModeQCOM
-> IO BlockMatchWindowCompareModeQCOM
Ptr BlockMatchWindowCompareModeQCOM
-> Int -> IO BlockMatchWindowCompareModeQCOM
Ptr BlockMatchWindowCompareModeQCOM
-> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
Ptr BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> IO ()
BlockMatchWindowCompareModeQCOM -> Int
forall b. Ptr b -> Int -> IO BlockMatchWindowCompareModeQCOM
forall b. Ptr b -> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> IO ()
$cpoke :: Ptr BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> IO ()
peek :: Ptr BlockMatchWindowCompareModeQCOM
-> IO BlockMatchWindowCompareModeQCOM
$cpeek :: Ptr BlockMatchWindowCompareModeQCOM
-> IO BlockMatchWindowCompareModeQCOM
pokeByteOff :: forall b. Ptr b -> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO BlockMatchWindowCompareModeQCOM
$cpeekByteOff :: forall b. Ptr b -> Int -> IO BlockMatchWindowCompareModeQCOM
pokeElemOff :: Ptr BlockMatchWindowCompareModeQCOM
-> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
$cpokeElemOff :: Ptr BlockMatchWindowCompareModeQCOM
-> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
peekElemOff :: Ptr BlockMatchWindowCompareModeQCOM
-> Int -> IO BlockMatchWindowCompareModeQCOM
$cpeekElemOff :: Ptr BlockMatchWindowCompareModeQCOM
-> Int -> IO BlockMatchWindowCompareModeQCOM
alignment :: BlockMatchWindowCompareModeQCOM -> Int
$calignment :: BlockMatchWindowCompareModeQCOM -> Int
sizeOf :: BlockMatchWindowCompareModeQCOM -> Int
$csizeOf :: BlockMatchWindowCompareModeQCOM -> Int
Storable, BlockMatchWindowCompareModeQCOM
forall a. a -> Zero a
zero :: BlockMatchWindowCompareModeQCOM
$czero :: BlockMatchWindowCompareModeQCOM
Zero)

-- | 'BLOCK_MATCH_WINDOW_COMPARE_MODE_MIN_QCOM' specifies that windowed block
-- match operations return the minimum error within the window.
pattern $bBLOCK_MATCH_WINDOW_COMPARE_MODE_MIN_QCOM :: BlockMatchWindowCompareModeQCOM
$mBLOCK_MATCH_WINDOW_COMPARE_MODE_MIN_QCOM :: forall {r}.
BlockMatchWindowCompareModeQCOM
-> ((# #) -> r) -> ((# #) -> r) -> r
BLOCK_MATCH_WINDOW_COMPARE_MODE_MIN_QCOM = BlockMatchWindowCompareModeQCOM 0

-- | 'BLOCK_MATCH_WINDOW_COMPARE_MODE_MAX_QCOM' specifies that windowed block
-- match operations return the maximum error within the window.
pattern $bBLOCK_MATCH_WINDOW_COMPARE_MODE_MAX_QCOM :: BlockMatchWindowCompareModeQCOM
$mBLOCK_MATCH_WINDOW_COMPARE_MODE_MAX_QCOM :: forall {r}.
BlockMatchWindowCompareModeQCOM
-> ((# #) -> r) -> ((# #) -> r) -> r
BLOCK_MATCH_WINDOW_COMPARE_MODE_MAX_QCOM = BlockMatchWindowCompareModeQCOM 1

{-# COMPLETE
  BLOCK_MATCH_WINDOW_COMPARE_MODE_MIN_QCOM
  , BLOCK_MATCH_WINDOW_COMPARE_MODE_MAX_QCOM ::
    BlockMatchWindowCompareModeQCOM
  #-}

conNameBlockMatchWindowCompareModeQCOM :: String
conNameBlockMatchWindowCompareModeQCOM :: String
conNameBlockMatchWindowCompareModeQCOM = String
"BlockMatchWindowCompareModeQCOM"

enumPrefixBlockMatchWindowCompareModeQCOM :: String
enumPrefixBlockMatchWindowCompareModeQCOM :: String
enumPrefixBlockMatchWindowCompareModeQCOM = String
"BLOCK_MATCH_WINDOW_COMPARE_MODE_M"

showTableBlockMatchWindowCompareModeQCOM :: [(BlockMatchWindowCompareModeQCOM, String)]
showTableBlockMatchWindowCompareModeQCOM :: [(BlockMatchWindowCompareModeQCOM, String)]
showTableBlockMatchWindowCompareModeQCOM =
  [
    ( BlockMatchWindowCompareModeQCOM
BLOCK_MATCH_WINDOW_COMPARE_MODE_MIN_QCOM
    , String
"IN_QCOM"
    )
  ,
    ( BlockMatchWindowCompareModeQCOM
BLOCK_MATCH_WINDOW_COMPARE_MODE_MAX_QCOM
    , String
"AX_QCOM"
    )
  ]

instance Show BlockMatchWindowCompareModeQCOM where
  showsPrec :: Int -> BlockMatchWindowCompareModeQCOM -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixBlockMatchWindowCompareModeQCOM
      [(BlockMatchWindowCompareModeQCOM, String)]
showTableBlockMatchWindowCompareModeQCOM
      String
conNameBlockMatchWindowCompareModeQCOM
      (\(BlockMatchWindowCompareModeQCOM Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read BlockMatchWindowCompareModeQCOM where
  readPrec :: ReadPrec BlockMatchWindowCompareModeQCOM
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixBlockMatchWindowCompareModeQCOM
      [(BlockMatchWindowCompareModeQCOM, String)]
showTableBlockMatchWindowCompareModeQCOM
      String
conNameBlockMatchWindowCompareModeQCOM
      Int32 -> BlockMatchWindowCompareModeQCOM
BlockMatchWindowCompareModeQCOM

type QCOM_IMAGE_PROCESSING_2_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_QCOM_IMAGE_PROCESSING_2_SPEC_VERSION"
pattern QCOM_IMAGE_PROCESSING_2_SPEC_VERSION :: forall a . Integral a => a
pattern $bQCOM_IMAGE_PROCESSING_2_SPEC_VERSION :: forall a. Integral a => a
$mQCOM_IMAGE_PROCESSING_2_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
QCOM_IMAGE_PROCESSING_2_SPEC_VERSION = 1


type QCOM_IMAGE_PROCESSING_2_EXTENSION_NAME = "VK_QCOM_image_processing2"

-- No documentation found for TopLevel "VK_QCOM_IMAGE_PROCESSING_2_EXTENSION_NAME"
pattern QCOM_IMAGE_PROCESSING_2_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bQCOM_IMAGE_PROCESSING_2_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mQCOM_IMAGE_PROCESSING_2_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
QCOM_IMAGE_PROCESSING_2_EXTENSION_NAME = "VK_QCOM_image_processing2"