{-# language CPP #-}
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))
data ImageViewSampleWeightCreateInfoQCOM = ImageViewSampleWeightCreateInfoQCOM
  { 
    
    ImageViewSampleWeightCreateInfoQCOM -> Offset2D
filterCenter :: Offset2D
  , 
    
    ImageViewSampleWeightCreateInfoQCOM -> Extent2D
filterSize :: Extent2D
  , 
    
    
    
    
    
    
    
    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
data PhysicalDeviceImageProcessingFeaturesQCOM = PhysicalDeviceImageProcessingFeaturesQCOM
  { 
    
    
    PhysicalDeviceImageProcessingFeaturesQCOM -> Bool
textureSampleWeighted :: Bool
  , 
    
    
    PhysicalDeviceImageProcessingFeaturesQCOM -> Bool
textureBoxFilter :: Bool
  , 
    
    
    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
data PhysicalDeviceImageProcessingPropertiesQCOM = PhysicalDeviceImageProcessingPropertiesQCOM
  { 
    
    
    
    
    PhysicalDeviceImageProcessingPropertiesQCOM -> Word32
maxWeightFilterPhases :: Word32
  , 
    
    
    
    PhysicalDeviceImageProcessingPropertiesQCOM -> Extent2D
maxWeightFilterDimension :: Extent2D
  , 
    
    
    
    
    
    PhysicalDeviceImageProcessingPropertiesQCOM -> Extent2D
maxBlockMatchRegion :: Extent2D
  , 
    
    
    
    
    
    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
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"
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"