{-# language CPP #-}
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))
data PhysicalDeviceImageProcessing2FeaturesQCOM = PhysicalDeviceImageProcessing2FeaturesQCOM
{
PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
textureBlockMatch2 :: Bool }
deriving (Typeable, PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
(PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool)
-> (PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool)
-> Eq PhysicalDeviceImageProcessing2FeaturesQCOM
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
== :: PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
$c/= :: PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
/= :: 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 = Int
-> (Ptr PhysicalDeviceImageProcessing2FeaturesQCOM -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceImageProcessing2FeaturesQCOM -> IO b) -> IO b)
-> (Ptr PhysicalDeviceImageProcessing2FeaturesQCOM -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
p -> Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> IO b -> IO b
forall b.
Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> IO b -> IO b
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
$sel:textureBlockMatch2:PhysicalDeviceImageProcessing2FeaturesQCOM :: PhysicalDeviceImageProcessing2FeaturesQCOM -> Bool
textureBlockMatch2 :: Bool
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
p Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_FEATURES_QCOM)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
p Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
p Ptr PhysicalDeviceImageProcessing2FeaturesQCOM -> Int -> Ptr Bool32
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
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
p Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_FEATURES_QCOM)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
p Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
p Ptr PhysicalDeviceImageProcessing2FeaturesQCOM -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
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 Ptr PhysicalDeviceImageProcessing2FeaturesQCOM -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
PhysicalDeviceImageProcessing2FeaturesQCOM
-> IO PhysicalDeviceImageProcessing2FeaturesQCOM
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceImageProcessing2FeaturesQCOM
-> IO PhysicalDeviceImageProcessing2FeaturesQCOM)
-> PhysicalDeviceImageProcessing2FeaturesQCOM
-> IO PhysicalDeviceImageProcessing2FeaturesQCOM
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 = Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
-> IO PhysicalDeviceImageProcessing2FeaturesQCOM
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> IO ()
poke Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
ptr PhysicalDeviceImageProcessing2FeaturesQCOM
poked = Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> IO () -> IO ()
forall b.
Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
-> PhysicalDeviceImageProcessing2FeaturesQCOM -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageProcessing2FeaturesQCOM
ptr PhysicalDeviceImageProcessing2FeaturesQCOM
poked (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceImageProcessing2FeaturesQCOM where
zero :: PhysicalDeviceImageProcessing2FeaturesQCOM
zero = Bool -> PhysicalDeviceImageProcessing2FeaturesQCOM
PhysicalDeviceImageProcessing2FeaturesQCOM
Bool
forall a. Zero a => a
zero
data PhysicalDeviceImageProcessing2PropertiesQCOM = PhysicalDeviceImageProcessing2PropertiesQCOM
{
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 = Int
-> (Ptr PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b)
-> IO b)
-> (Ptr PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p -> Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b -> IO b
forall b.
Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b -> IO b
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
$sel:maxBlockMatchWindow:PhysicalDeviceImageProcessing2PropertiesQCOM :: PhysicalDeviceImageProcessing2PropertiesQCOM -> Extent2D
maxBlockMatchWindow :: Extent2D
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_PROPERTIES_QCOM)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Extent2D -> Extent2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> Int -> Ptr Extent2D
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
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_PROCESSING_2_PROPERTIES_QCOM)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
p Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (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 Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> Int -> Ptr Extent2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D))
PhysicalDeviceImageProcessing2PropertiesQCOM
-> IO PhysicalDeviceImageProcessing2PropertiesQCOM
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceImageProcessing2PropertiesQCOM
-> IO PhysicalDeviceImageProcessing2PropertiesQCOM)
-> PhysicalDeviceImageProcessing2PropertiesQCOM
-> IO PhysicalDeviceImageProcessing2PropertiesQCOM
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 = Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> IO PhysicalDeviceImageProcessing2PropertiesQCOM
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> PhysicalDeviceImageProcessing2PropertiesQCOM -> IO ()
poke Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
ptr PhysicalDeviceImageProcessing2PropertiesQCOM
poked = Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> PhysicalDeviceImageProcessing2PropertiesQCOM -> IO () -> IO ()
forall b.
Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
-> PhysicalDeviceImageProcessing2PropertiesQCOM -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageProcessing2PropertiesQCOM
ptr PhysicalDeviceImageProcessing2PropertiesQCOM
poked (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceImageProcessing2PropertiesQCOM where
zero :: PhysicalDeviceImageProcessing2PropertiesQCOM
zero = Extent2D -> PhysicalDeviceImageProcessing2PropertiesQCOM
PhysicalDeviceImageProcessing2PropertiesQCOM
Extent2D
forall a. Zero a => a
zero
data SamplerBlockMatchWindowCreateInfoQCOM = SamplerBlockMatchWindowCreateInfoQCOM
{
SamplerBlockMatchWindowCreateInfoQCOM -> Extent2D
windowExtent :: Extent2D
,
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 = Int -> (Ptr SamplerBlockMatchWindowCreateInfoQCOM -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr SamplerBlockMatchWindowCreateInfoQCOM -> IO b) -> IO b)
-> (Ptr SamplerBlockMatchWindowCreateInfoQCOM -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr SamplerBlockMatchWindowCreateInfoQCOM
p -> Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> SamplerBlockMatchWindowCreateInfoQCOM -> IO b -> IO b
forall b.
Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> SamplerBlockMatchWindowCreateInfoQCOM -> IO b -> IO b
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
$sel:windowExtent:SamplerBlockMatchWindowCreateInfoQCOM :: SamplerBlockMatchWindowCreateInfoQCOM -> Extent2D
$sel:windowCompareMode:SamplerBlockMatchWindowCreateInfoQCOM :: SamplerBlockMatchWindowCreateInfoQCOM
-> BlockMatchWindowCompareModeQCOM
windowExtent :: Extent2D
windowCompareMode :: BlockMatchWindowCompareModeQCOM
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SAMPLER_BLOCK_MATCH_WINDOW_CREATE_INFO_QCOM)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p Ptr SamplerBlockMatchWindowCreateInfoQCOM -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Extent2D -> Extent2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p Ptr SamplerBlockMatchWindowCreateInfoQCOM -> Int -> Ptr Extent2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D)) (Extent2D
windowExtent)
Ptr BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> Int -> Ptr BlockMatchWindowCompareModeQCOM
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
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SAMPLER_BLOCK_MATCH_WINDOW_CREATE_INFO_QCOM)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p Ptr SamplerBlockMatchWindowCreateInfoQCOM -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Extent2D -> Extent2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p Ptr SamplerBlockMatchWindowCreateInfoQCOM -> Int -> Ptr Extent2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D)) (Extent2D
forall a. Zero a => a
zero)
Ptr BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerBlockMatchWindowCreateInfoQCOM
p Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> Int -> Ptr BlockMatchWindowCompareModeQCOM
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BlockMatchWindowCompareModeQCOM)) (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 Ptr SamplerBlockMatchWindowCreateInfoQCOM -> Int -> Ptr Extent2D
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 Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> Int -> Ptr BlockMatchWindowCompareModeQCOM
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BlockMatchWindowCompareModeQCOM))
SamplerBlockMatchWindowCreateInfoQCOM
-> IO SamplerBlockMatchWindowCreateInfoQCOM
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SamplerBlockMatchWindowCreateInfoQCOM
-> IO SamplerBlockMatchWindowCreateInfoQCOM)
-> SamplerBlockMatchWindowCreateInfoQCOM
-> IO SamplerBlockMatchWindowCreateInfoQCOM
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 = Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> IO SamplerBlockMatchWindowCreateInfoQCOM
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> SamplerBlockMatchWindowCreateInfoQCOM -> IO ()
poke Ptr SamplerBlockMatchWindowCreateInfoQCOM
ptr SamplerBlockMatchWindowCreateInfoQCOM
poked = Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> SamplerBlockMatchWindowCreateInfoQCOM -> IO () -> IO ()
forall b.
Ptr SamplerBlockMatchWindowCreateInfoQCOM
-> SamplerBlockMatchWindowCreateInfoQCOM -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SamplerBlockMatchWindowCreateInfoQCOM
ptr SamplerBlockMatchWindowCreateInfoQCOM
poked (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SamplerBlockMatchWindowCreateInfoQCOM where
zero :: SamplerBlockMatchWindowCreateInfoQCOM
zero = Extent2D
-> BlockMatchWindowCompareModeQCOM
-> SamplerBlockMatchWindowCreateInfoQCOM
SamplerBlockMatchWindowCreateInfoQCOM
Extent2D
forall a. Zero a => a
zero
BlockMatchWindowCompareModeQCOM
forall a. Zero a => a
zero
newtype BlockMatchWindowCompareModeQCOM = BlockMatchWindowCompareModeQCOM Int32
deriving newtype (BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
(BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool)
-> (BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool)
-> Eq BlockMatchWindowCompareModeQCOM
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
== :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
$c/= :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
/= :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
Eq, Eq BlockMatchWindowCompareModeQCOM
Eq BlockMatchWindowCompareModeQCOM =>
(BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Ordering)
-> (BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool)
-> (BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool)
-> (BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool)
-> (BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool)
-> (BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM)
-> (BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM)
-> Ord 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
$ccompare :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Ordering
compare :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Ordering
$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
>= :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> Bool
$cmax :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
max :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
$cmin :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
min :: BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM
Ord, Ptr BlockMatchWindowCompareModeQCOM
-> IO BlockMatchWindowCompareModeQCOM
Ptr BlockMatchWindowCompareModeQCOM
-> Int -> IO BlockMatchWindowCompareModeQCOM
Ptr BlockMatchWindowCompareModeQCOM
-> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
Ptr BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> IO ()
BlockMatchWindowCompareModeQCOM -> Int
(BlockMatchWindowCompareModeQCOM -> Int)
-> (BlockMatchWindowCompareModeQCOM -> Int)
-> (Ptr BlockMatchWindowCompareModeQCOM
-> Int -> IO BlockMatchWindowCompareModeQCOM)
-> (Ptr BlockMatchWindowCompareModeQCOM
-> Int -> BlockMatchWindowCompareModeQCOM -> IO ())
-> (forall b. Ptr b -> Int -> IO BlockMatchWindowCompareModeQCOM)
-> (forall b.
Ptr b -> Int -> BlockMatchWindowCompareModeQCOM -> IO ())
-> (Ptr BlockMatchWindowCompareModeQCOM
-> IO BlockMatchWindowCompareModeQCOM)
-> (Ptr BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> IO ())
-> Storable BlockMatchWindowCompareModeQCOM
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
$csizeOf :: BlockMatchWindowCompareModeQCOM -> Int
sizeOf :: BlockMatchWindowCompareModeQCOM -> Int
$calignment :: BlockMatchWindowCompareModeQCOM -> Int
alignment :: BlockMatchWindowCompareModeQCOM -> Int
$cpeekElemOff :: Ptr BlockMatchWindowCompareModeQCOM
-> Int -> IO BlockMatchWindowCompareModeQCOM
peekElemOff :: Ptr BlockMatchWindowCompareModeQCOM
-> Int -> IO BlockMatchWindowCompareModeQCOM
$cpokeElemOff :: Ptr BlockMatchWindowCompareModeQCOM
-> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
pokeElemOff :: Ptr BlockMatchWindowCompareModeQCOM
-> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO BlockMatchWindowCompareModeQCOM
peekByteOff :: forall b. Ptr b -> Int -> IO BlockMatchWindowCompareModeQCOM
$cpokeByteOff :: forall b. Ptr b -> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> BlockMatchWindowCompareModeQCOM -> IO ()
$cpeek :: Ptr BlockMatchWindowCompareModeQCOM
-> IO BlockMatchWindowCompareModeQCOM
peek :: Ptr BlockMatchWindowCompareModeQCOM
-> IO BlockMatchWindowCompareModeQCOM
$cpoke :: Ptr BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> IO ()
poke :: Ptr BlockMatchWindowCompareModeQCOM
-> BlockMatchWindowCompareModeQCOM -> IO ()
Storable, BlockMatchWindowCompareModeQCOM
BlockMatchWindowCompareModeQCOM
-> Zero BlockMatchWindowCompareModeQCOM
forall a. a -> Zero a
$czero :: BlockMatchWindowCompareModeQCOM
zero :: BlockMatchWindowCompareModeQCOM
Zero)
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
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 =
String
-> [(BlockMatchWindowCompareModeQCOM, String)]
-> String
-> (BlockMatchWindowCompareModeQCOM -> Int32)
-> (Int32 -> ShowS)
-> Int
-> BlockMatchWindowCompareModeQCOM
-> ShowS
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)
(Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)
instance Read BlockMatchWindowCompareModeQCOM where
readPrec :: ReadPrec BlockMatchWindowCompareModeQCOM
readPrec =
String
-> [(BlockMatchWindowCompareModeQCOM, String)]
-> String
-> (Int32 -> BlockMatchWindowCompareModeQCOM)
-> ReadPrec BlockMatchWindowCompareModeQCOM
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
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"
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"