{-# language CPP #-}
-- | = Name
--
-- VK_QCOM_image_processing - device extension
--
-- == VK_QCOM_image_processing
--
-- [__Name String__]
--     @VK_QCOM_image_processing@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     441
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_KHR_format_feature_flags2@ to be enabled for any
--         device-level functionality
--
-- [__Contact__]
--
--     -   Jeff Leger
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_QCOM_image_processing] @jackohound%0A*Here describe the issue or question you have about the VK_QCOM_image_processing extension* >
--
-- [__Extension Proposal__]
--     <https://github.com/KhronosGroup/Vulkan-Docs/tree/main/proposals/VK_QCOM_image_processing.adoc VK_QCOM_image_processing>
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2022-07-08
--
-- [__Interactions and External Dependencies__]
--
--     -   This extension requires
--         <https://htmlpreview.github.io/?https://github.com/KhronosGroup/SPIRV-Registry/blob/master/extensions/QCOM/SPV_QCOM_image_processing.html SPV_QCOM_image_processing>
--
--     -   This extension provides API support for
--         <https://github.com/KhronosGroup/GLSL/blob/master/extensions/qcom/GLSL_QCOM_image_processing.txt GL_QCOM_image_processing>
--
-- [__Contributors__]
--
--     -   Jeff Leger, Qualcomm Technologies, Inc.
--
--     -   Ruihao Zhang, Qualcomm Technologies, Inc.
--
-- == Description
--
-- GPUs are commonly used to process images for various applications from
-- 3D graphics to UI and from composition to compute applications. Simple
-- scaling and filtering can be done with bilinear filtering, which comes
-- for free during texture sampling. However, as screen sizes get larger
-- and more use-cases rely on GPU such as camera and video post-processing
-- needs, there is increasing demand for GPU to support higher order
-- filtering and other advanced image processing.
--
-- This extension introduces a new set of SPIR-V built-in functions for
-- image processing. It exposes the following new imaging operations
--
-- -   The @OpImageSampleWeightedQCOM@ instruction takes 3 operands:
--     /sampled image/, /weight image/, and texture coordinates. The
--     instruction computes a weighted average of an MxN region of texels
--     in the /sampled image/, using a set of MxN weights in the /weight
--     image/.
--
-- -   The @OpImageBoxFilterQCOM@ instruction takes 3 operands: /sampled
--     image/, /box size/, and texture coordinates. Note that /box size/
--     specifies a floating point width and height in texels. The
--     instruction computes a weighted average of all texels in the
--     /sampled image/ that are covered (either partially or fully) by a
--     box with the specified size and centered at the specified texture
--     coordinates.
--
-- -   The @OpImageBlockMatchSADQCOM@ and @OpImageBlockMatchSSDQCOM@
--     instructions each takes 5 operands: /target image/, /target
--     coordinates/, /reference image/, /reference coordinates/, and /block
--     size/. Each 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 error
--     metric is computed per-component. @OpImageBlockMatchSADQCOM@
--     computes \"Sum Of Absolute Difference\" and
--     @OpImageBlockMatchSSDQCOM@ computes \"Sum of Squared Difference\".
--
-- Each of the image processing instructions operate only on 2D images. The
-- instructions do not-support sampling of mipmap, multi-plane,
-- multi-layer, multi-sampled, or depth\/stencil images. The instructions
-- can be used in any shader stage.
--
-- Implementations of this this extension should support these operations
-- natively at the HW instruction level, offering potential performance
-- gains as well as ease of development.
--
-- == New Structures
--
-- -   Extending 'Vulkan.Core10.ImageView.ImageViewCreateInfo':
--
--     -   'ImageViewSampleWeightCreateInfoQCOM'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceImageProcessingFeaturesQCOM'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceImageProcessingPropertiesQCOM'
--
-- == New Enum Constants
--
-- -   'QCOM_IMAGE_PROCESSING_EXTENSION_NAME'
--
-- -   'QCOM_IMAGE_PROCESSING_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.DescriptorType.DescriptorType':
--
--     -   'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_BLOCK_MATCH_IMAGE_QCOM'
--
--     -   'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLE_WEIGHT_IMAGE_QCOM'
--
-- -   Extending
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlagBits':
--
--     -   'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLE_BLOCK_MATCH_BIT_QCOM'
--
--     -   'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLE_WEIGHT_BIT_QCOM'
--
-- -   Extending
--     'Vulkan.Core10.Enums.SamplerCreateFlagBits.SamplerCreateFlagBits':
--
--     -   'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_IMAGE_VIEW_SAMPLE_WEIGHT_CREATE_INFO_QCOM'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_FEATURES_QCOM'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_PROPERTIES_QCOM'
--
-- If
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_format_feature_flags2 VK_KHR_format_feature_flags2>
-- is supported:
--
-- -   Extending
--     'Vulkan.Core13.Enums.FormatFeatureFlags2.FormatFeatureFlagBits2':
--
--     -   'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM'
--
--     -   'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BOX_FILTER_SAMPLED_BIT_QCOM'
--
--     -   'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_IMAGE_BIT_QCOM'
--
--     -   'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_SAMPLED_IMAGE_BIT_QCOM'
--
-- == Version History
--
-- -   Revision 1, 2022-07-08 (Jeff Leger)
--
-- == See Also
--
-- 'ImageViewSampleWeightCreateInfoQCOM',
-- 'PhysicalDeviceImageProcessingFeaturesQCOM',
-- 'PhysicalDeviceImageProcessingPropertiesQCOM'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_QCOM_image_processing 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_processing  ( ImageViewSampleWeightCreateInfoQCOM(..)
                                                   , PhysicalDeviceImageProcessingFeaturesQCOM(..)
                                                   , PhysicalDeviceImageProcessingPropertiesQCOM(..)
                                                   , QCOM_IMAGE_PROCESSING_SPEC_VERSION
                                                   , pattern QCOM_IMAGE_PROCESSING_SPEC_VERSION
                                                   , QCOM_IMAGE_PROCESSING_EXTENSION_NAME
                                                   , pattern QCOM_IMAGE_PROCESSING_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.FundamentalTypes (Extent2D)
import Vulkan.Core10.FundamentalTypes (Offset2D)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_VIEW_SAMPLE_WEIGHT_CREATE_INFO_QCOM))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_FEATURES_QCOM))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_PROPERTIES_QCOM))
-- | VkImageViewSampleWeightCreateInfoQCOM - Structure describing weight
-- sampling parameters for image view
--
-- = Description
--
-- The @filterCenter@ specifies the origin or center of the filter kernel,
-- as described in
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#textures-weightimage-filteroperation Weight Sampling Operation>.
-- The @numPhases@ describes the number of sub-pixel filter phases as
-- described in
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#textures-weightimage-filterphases Weight Sampling Phases>.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_QCOM_image_processing VK_QCOM_image_processing>,
-- 'Vulkan.Core10.FundamentalTypes.Extent2D',
-- 'Vulkan.Core10.FundamentalTypes.Offset2D',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data ImageViewSampleWeightCreateInfoQCOM = ImageViewSampleWeightCreateInfoQCOM
  { -- | @filterCenter@ is a 'Vulkan.Core10.FundamentalTypes.Offset2D' describing
    -- the location of the weight filter origin.
    ImageViewSampleWeightCreateInfoQCOM -> Offset2D
filterCenter :: Offset2D
  , -- | @filterSize@ is a 'Vulkan.Core10.FundamentalTypes.Extent2D' specifying
    -- weight filter dimensions.
    ImageViewSampleWeightCreateInfoQCOM -> Extent2D
filterSize :: Extent2D
  , -- | @numPhases@ is number of sub-pixel filter phases.
    --
    -- #VUID-VkImageViewSampleWeightCreateInfoQCOM-numPhases-06962# @numPhases@
    -- /must/ be a power of two squared value (i.e., 1, 4, 16, 64, 256, etc.)
    --
    -- #VUID-VkImageViewSampleWeightCreateInfoQCOM-numPhases-06963# @numPhases@
    -- /must/ be less than or equal to
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-weightfilter-phases ::maxWeightFilterPhases>
    ImageViewSampleWeightCreateInfoQCOM -> Word32
numPhases :: Word32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageViewSampleWeightCreateInfoQCOM)
#endif
deriving instance Show ImageViewSampleWeightCreateInfoQCOM

instance ToCStruct ImageViewSampleWeightCreateInfoQCOM where
  withCStruct :: forall b.
ImageViewSampleWeightCreateInfoQCOM
-> (Ptr ImageViewSampleWeightCreateInfoQCOM -> IO b) -> IO b
withCStruct ImageViewSampleWeightCreateInfoQCOM
x Ptr ImageViewSampleWeightCreateInfoQCOM -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \Ptr ImageViewSampleWeightCreateInfoQCOM
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageViewSampleWeightCreateInfoQCOM
p ImageViewSampleWeightCreateInfoQCOM
x (Ptr ImageViewSampleWeightCreateInfoQCOM -> IO b
f Ptr ImageViewSampleWeightCreateInfoQCOM
p)
  pokeCStruct :: forall b.
Ptr ImageViewSampleWeightCreateInfoQCOM
-> ImageViewSampleWeightCreateInfoQCOM -> IO b -> IO b
pokeCStruct Ptr ImageViewSampleWeightCreateInfoQCOM
p ImageViewSampleWeightCreateInfoQCOM{Word32
Offset2D
Extent2D
numPhases :: Word32
filterSize :: Extent2D
filterCenter :: Offset2D
$sel:numPhases:ImageViewSampleWeightCreateInfoQCOM :: ImageViewSampleWeightCreateInfoQCOM -> Word32
$sel:filterSize:ImageViewSampleWeightCreateInfoQCOM :: ImageViewSampleWeightCreateInfoQCOM -> Extent2D
$sel:filterCenter:ImageViewSampleWeightCreateInfoQCOM :: ImageViewSampleWeightCreateInfoQCOM -> Offset2D
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_SAMPLE_WEIGHT_CREATE_INFO_QCOM)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewSampleWeightCreateInfoQCOM
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 ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Offset2D)) (Offset2D
filterCenter)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Extent2D)) (Extent2D
filterSize)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32)) (Word32
numPhases)
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr ImageViewSampleWeightCreateInfoQCOM -> IO b -> IO b
pokeZeroCStruct Ptr ImageViewSampleWeightCreateInfoQCOM
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_SAMPLE_WEIGHT_CREATE_INFO_QCOM)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewSampleWeightCreateInfoQCOM
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 ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Offset2D)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Extent2D)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ImageViewSampleWeightCreateInfoQCOM where
  peekCStruct :: Ptr ImageViewSampleWeightCreateInfoQCOM
-> IO ImageViewSampleWeightCreateInfoQCOM
peekCStruct Ptr ImageViewSampleWeightCreateInfoQCOM
p = do
    Offset2D
filterCenter <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset2D ((Ptr ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Offset2D))
    Extent2D
filterSize <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D ((Ptr ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Extent2D))
    Word32
numPhases <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageViewSampleWeightCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Offset2D
-> Extent2D -> Word32 -> ImageViewSampleWeightCreateInfoQCOM
ImageViewSampleWeightCreateInfoQCOM
             Offset2D
filterCenter Extent2D
filterSize Word32
numPhases

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

instance Zero ImageViewSampleWeightCreateInfoQCOM where
  zero :: ImageViewSampleWeightCreateInfoQCOM
zero = Offset2D
-> Extent2D -> Word32 -> ImageViewSampleWeightCreateInfoQCOM
ImageViewSampleWeightCreateInfoQCOM
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkPhysicalDeviceImageProcessingFeaturesQCOM - Structure describing image
-- processing features that can be supported by an implementation
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceImageProcessingFeaturesQCOM' 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. 'PhysicalDeviceImageProcessingFeaturesQCOM' /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_processing VK_QCOM_image_processing>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceImageProcessingFeaturesQCOM = PhysicalDeviceImageProcessingFeaturesQCOM
  { -- | #features-textureSampleWeighted# @textureSampleWeighted@ indicates that
    -- the implementation supports shader modules that declare the
    -- @TextureSampleWeightedQCOM@ capability.
    PhysicalDeviceImageProcessingFeaturesQCOM -> Bool
textureSampleWeighted :: Bool
  , -- | #features-textureBoxFilter# @textureBoxFilter@ indicates that the
    -- implementation supports shader modules that declare the
    -- @TextureBoxFilterQCOM@ capability.
    PhysicalDeviceImageProcessingFeaturesQCOM -> Bool
textureBoxFilter :: Bool
  , -- | #features-textureBlockMatch# @textureBlockMatch@ indicates that the
    -- implementation supports shader modules that declare the
    -- @TextureBlockMatchQCOM@ capability.
    PhysicalDeviceImageProcessingFeaturesQCOM -> Bool
textureBlockMatch :: Bool
  }
  deriving (Typeable, PhysicalDeviceImageProcessingFeaturesQCOM
-> PhysicalDeviceImageProcessingFeaturesQCOM -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceImageProcessingFeaturesQCOM
-> PhysicalDeviceImageProcessingFeaturesQCOM -> Bool
$c/= :: PhysicalDeviceImageProcessingFeaturesQCOM
-> PhysicalDeviceImageProcessingFeaturesQCOM -> Bool
== :: PhysicalDeviceImageProcessingFeaturesQCOM
-> PhysicalDeviceImageProcessingFeaturesQCOM -> Bool
$c== :: PhysicalDeviceImageProcessingFeaturesQCOM
-> PhysicalDeviceImageProcessingFeaturesQCOM -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceImageProcessingFeaturesQCOM)
#endif
deriving instance Show PhysicalDeviceImageProcessingFeaturesQCOM

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

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

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


-- | VkPhysicalDeviceImageProcessingPropertiesQCOM - Structure containing
-- image processing properties
--
-- = Members
--
-- -   @sType@ is the type of this structure.
--
-- -   @pNext@ is @NULL@ or a pointer to a structure extending this
--     structure.
--
-- -   #limits-weightfilter-phases#@maxWeightFilterPhases@ is the maximum
--     value that /can/ be specified for
--     'ImageViewSampleWeightCreateInfoQCOM'::@numPhases@. in
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#textures-weightimage-filterphases weight image sampling>
--     operations.
--
-- -   #limits-weightfilter-maxdimension#@maxWeightFilterDimension@ is a
--     'Vulkan.Core10.FundamentalTypes.Extent2D' describing the largest
--     dimensions (@width@ and @height@) that /can/ be specified for
--     'ImageViewSampleWeightCreateInfoQCOM'::@filterSize@.
--
-- -   #limits-blockmatch-maxblocksize#@maxBlockMatchRegion@ is a
--     'Vulkan.Core10.FundamentalTypes.Extent2D' describing the largest
--     dimensions (@width@ and @height@) that /can/ be specified for
--     @blockSize@ in
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#textures-blockmatch block matching>
--     operations.
--
-- -   #limits-boxfilter-maxblocksize#@maxBoxFilterBlockSize@ is a
--     'Vulkan.Core10.FundamentalTypes.Extent2D' describing the the maximum
--     dimensions (@width@ and @height@) that /can/ be specified for
--     @blocksize@ in
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#textures-boxfilter box filter sampling>
--     operations.
--
-- = Description
--
-- If the 'PhysicalDeviceImageProcessingPropertiesQCOM' 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 processing information of a physical
-- device.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_QCOM_image_processing VK_QCOM_image_processing>,
-- 'Vulkan.Core10.FundamentalTypes.Extent2D',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceImageProcessingPropertiesQCOM = PhysicalDeviceImageProcessingPropertiesQCOM
  { -- No documentation found for Nested "VkPhysicalDeviceImageProcessingPropertiesQCOM" "maxWeightFilterPhases"
    PhysicalDeviceImageProcessingPropertiesQCOM -> Word32
maxWeightFilterPhases :: Word32
  , -- No documentation found for Nested "VkPhysicalDeviceImageProcessingPropertiesQCOM" "maxWeightFilterDimension"
    PhysicalDeviceImageProcessingPropertiesQCOM -> Extent2D
maxWeightFilterDimension :: Extent2D
  , -- No documentation found for Nested "VkPhysicalDeviceImageProcessingPropertiesQCOM" "maxBlockMatchRegion"
    PhysicalDeviceImageProcessingPropertiesQCOM -> Extent2D
maxBlockMatchRegion :: Extent2D
  , -- No documentation found for Nested "VkPhysicalDeviceImageProcessingPropertiesQCOM" "maxBoxFilterBlockSize"
    PhysicalDeviceImageProcessingPropertiesQCOM -> Extent2D
maxBoxFilterBlockSize :: Extent2D
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceImageProcessingPropertiesQCOM)
#endif
deriving instance Show PhysicalDeviceImageProcessingPropertiesQCOM

instance ToCStruct PhysicalDeviceImageProcessingPropertiesQCOM where
  withCStruct :: forall b.
PhysicalDeviceImageProcessingPropertiesQCOM
-> (Ptr PhysicalDeviceImageProcessingPropertiesQCOM -> IO b)
-> IO b
withCStruct PhysicalDeviceImageProcessingPropertiesQCOM
x Ptr PhysicalDeviceImageProcessingPropertiesQCOM -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p PhysicalDeviceImageProcessingPropertiesQCOM
x (Ptr PhysicalDeviceImageProcessingPropertiesQCOM -> IO b
f Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceImageProcessingPropertiesQCOM
-> PhysicalDeviceImageProcessingPropertiesQCOM -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p PhysicalDeviceImageProcessingPropertiesQCOM{Word32
Extent2D
maxBoxFilterBlockSize :: Extent2D
maxBlockMatchRegion :: Extent2D
maxWeightFilterDimension :: Extent2D
maxWeightFilterPhases :: Word32
$sel:maxBoxFilterBlockSize:PhysicalDeviceImageProcessingPropertiesQCOM :: PhysicalDeviceImageProcessingPropertiesQCOM -> Extent2D
$sel:maxBlockMatchRegion:PhysicalDeviceImageProcessingPropertiesQCOM :: PhysicalDeviceImageProcessingPropertiesQCOM -> Extent2D
$sel:maxWeightFilterDimension:PhysicalDeviceImageProcessingPropertiesQCOM :: PhysicalDeviceImageProcessingPropertiesQCOM -> Extent2D
$sel:maxWeightFilterPhases:PhysicalDeviceImageProcessingPropertiesQCOM :: PhysicalDeviceImageProcessingPropertiesQCOM -> Word32
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_PROPERTIES_QCOM)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
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 PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
maxWeightFilterPhases)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Extent2D)) (Extent2D
maxWeightFilterDimension)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Extent2D)) (Extent2D
maxBlockMatchRegion)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Extent2D)) (Extent2D
maxBoxFilterBlockSize)
    IO b
f
  cStructSize :: Int
cStructSize = Int
48
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceImageProcessingPropertiesQCOM -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_PROPERTIES_QCOM)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct PhysicalDeviceImageProcessingPropertiesQCOM where
  peekCStruct :: Ptr PhysicalDeviceImageProcessingPropertiesQCOM
-> IO PhysicalDeviceImageProcessingPropertiesQCOM
peekCStruct Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p = do
    Word32
maxWeightFilterPhases <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Extent2D
maxWeightFilterDimension <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Extent2D))
    Extent2D
maxBlockMatchRegion <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Extent2D))
    Extent2D
maxBoxFilterBlockSize <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D ((Ptr PhysicalDeviceImageProcessingPropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Extent2D))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32
-> Extent2D
-> Extent2D
-> Extent2D
-> PhysicalDeviceImageProcessingPropertiesQCOM
PhysicalDeviceImageProcessingPropertiesQCOM
             Word32
maxWeightFilterPhases
             Extent2D
maxWeightFilterDimension
             Extent2D
maxBlockMatchRegion
             Extent2D
maxBoxFilterBlockSize

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

instance Zero PhysicalDeviceImageProcessingPropertiesQCOM where
  zero :: PhysicalDeviceImageProcessingPropertiesQCOM
zero = Word32
-> Extent2D
-> Extent2D
-> Extent2D
-> PhysicalDeviceImageProcessingPropertiesQCOM
PhysicalDeviceImageProcessingPropertiesQCOM
           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 QCOM_IMAGE_PROCESSING_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_QCOM_IMAGE_PROCESSING_SPEC_VERSION"
pattern QCOM_IMAGE_PROCESSING_SPEC_VERSION :: forall a . Integral a => a
pattern $bQCOM_IMAGE_PROCESSING_SPEC_VERSION :: forall a. Integral a => a
$mQCOM_IMAGE_PROCESSING_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
QCOM_IMAGE_PROCESSING_SPEC_VERSION = 1


type QCOM_IMAGE_PROCESSING_EXTENSION_NAME = "VK_QCOM_image_processing"

-- No documentation found for TopLevel "VK_QCOM_IMAGE_PROCESSING_EXTENSION_NAME"
pattern QCOM_IMAGE_PROCESSING_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bQCOM_IMAGE_PROCESSING_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mQCOM_IMAGE_PROCESSING_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
QCOM_IMAGE_PROCESSING_EXTENSION_NAME = "VK_QCOM_image_processing"