{-# language CPP #-}
module Vulkan.Extensions.VK_QCOM_ycbcr_degamma ( PhysicalDeviceYcbcrDegammaFeaturesQCOM(..)
, SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM(..)
, QCOM_YCBCR_DEGAMMA_SPEC_VERSION
, pattern QCOM_YCBCR_DEGAMMA_SPEC_VERSION
, QCOM_YCBCR_DEGAMMA_EXTENSION_NAME
, pattern QCOM_YCBCR_DEGAMMA_EXTENSION_NAME
) where
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_YCBCR_DEGAMMA_FEATURES_QCOM))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SAMPLER_YCBCR_CONVERSION_YCBCR_DEGAMMA_CREATE_INFO_QCOM))
data PhysicalDeviceYcbcrDegammaFeaturesQCOM = PhysicalDeviceYcbcrDegammaFeaturesQCOM
{
PhysicalDeviceYcbcrDegammaFeaturesQCOM -> Bool
ycbcrDegamma :: Bool }
deriving (Typeable, PhysicalDeviceYcbcrDegammaFeaturesQCOM
-> PhysicalDeviceYcbcrDegammaFeaturesQCOM -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceYcbcrDegammaFeaturesQCOM
-> PhysicalDeviceYcbcrDegammaFeaturesQCOM -> Bool
$c/= :: PhysicalDeviceYcbcrDegammaFeaturesQCOM
-> PhysicalDeviceYcbcrDegammaFeaturesQCOM -> Bool
== :: PhysicalDeviceYcbcrDegammaFeaturesQCOM
-> PhysicalDeviceYcbcrDegammaFeaturesQCOM -> Bool
$c== :: PhysicalDeviceYcbcrDegammaFeaturesQCOM
-> PhysicalDeviceYcbcrDegammaFeaturesQCOM -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceYcbcrDegammaFeaturesQCOM)
#endif
deriving instance Show PhysicalDeviceYcbcrDegammaFeaturesQCOM
instance ToCStruct PhysicalDeviceYcbcrDegammaFeaturesQCOM where
withCStruct :: forall b.
PhysicalDeviceYcbcrDegammaFeaturesQCOM
-> (Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM -> IO b) -> IO b
withCStruct PhysicalDeviceYcbcrDegammaFeaturesQCOM
x Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
p PhysicalDeviceYcbcrDegammaFeaturesQCOM
x (Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM -> IO b
f Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
-> PhysicalDeviceYcbcrDegammaFeaturesQCOM -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
p PhysicalDeviceYcbcrDegammaFeaturesQCOM{Bool
ycbcrDegamma :: Bool
$sel:ycbcrDegamma:PhysicalDeviceYcbcrDegammaFeaturesQCOM :: PhysicalDeviceYcbcrDegammaFeaturesQCOM -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_YCBCR_DEGAMMA_FEATURES_QCOM)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
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 PhysicalDeviceYcbcrDegammaFeaturesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
ycbcrDegamma))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_YCBCR_DEGAMMA_FEATURES_QCOM)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
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 PhysicalDeviceYcbcrDegammaFeaturesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceYcbcrDegammaFeaturesQCOM where
peekCStruct :: Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
-> IO PhysicalDeviceYcbcrDegammaFeaturesQCOM
peekCStruct Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
p = do
Bool32
ycbcrDegamma <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceYcbcrDegammaFeaturesQCOM
PhysicalDeviceYcbcrDegammaFeaturesQCOM
(Bool32 -> Bool
bool32ToBool Bool32
ycbcrDegamma)
instance Storable PhysicalDeviceYcbcrDegammaFeaturesQCOM where
sizeOf :: PhysicalDeviceYcbcrDegammaFeaturesQCOM -> Int
sizeOf ~PhysicalDeviceYcbcrDegammaFeaturesQCOM
_ = Int
24
alignment :: PhysicalDeviceYcbcrDegammaFeaturesQCOM -> Int
alignment ~PhysicalDeviceYcbcrDegammaFeaturesQCOM
_ = Int
8
peek :: Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
-> IO PhysicalDeviceYcbcrDegammaFeaturesQCOM
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
-> PhysicalDeviceYcbcrDegammaFeaturesQCOM -> IO ()
poke Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
ptr PhysicalDeviceYcbcrDegammaFeaturesQCOM
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceYcbcrDegammaFeaturesQCOM where
zero :: PhysicalDeviceYcbcrDegammaFeaturesQCOM
zero = Bool -> PhysicalDeviceYcbcrDegammaFeaturesQCOM
PhysicalDeviceYcbcrDegammaFeaturesQCOM
forall a. Zero a => a
zero
data SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM = SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
{
SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Bool
enableYDegamma :: Bool
,
SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Bool
enableCbCrDegamma :: Bool
}
deriving (Typeable, SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Bool
$c/= :: SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Bool
== :: SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Bool
$c== :: SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM)
#endif
deriving instance Show SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
instance ToCStruct SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM where
withCStruct :: forall b.
SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> (Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> IO b)
-> IO b
withCStruct SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
x Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
x (Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> IO b
f Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p)
pokeCStruct :: forall b.
Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> IO b -> IO b
pokeCStruct Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM{Bool
enableCbCrDegamma :: Bool
enableYDegamma :: Bool
$sel:enableCbCrDegamma:SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM :: SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Bool
$sel:enableYDegamma:SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM :: SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SAMPLER_YCBCR_CONVERSION_YCBCR_DEGAMMA_CREATE_INFO_QCOM)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
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 SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
enableYDegamma))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
enableCbCrDegamma))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> IO b -> IO b
pokeZeroCStruct Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SAMPLER_YCBCR_CONVERSION_YCBCR_DEGAMMA_CREATE_INFO_QCOM)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
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 SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
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 SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM where
peekCStruct :: Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> IO SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
peekCStruct Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p = do
Bool32
enableYDegamma <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
enableCbCrDegamma <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
(Bool32 -> Bool
bool32ToBool Bool32
enableYDegamma) (Bool32 -> Bool
bool32ToBool Bool32
enableCbCrDegamma)
instance Storable SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM where
sizeOf :: SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Int
sizeOf ~SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
_ = Int
24
alignment :: SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> Int
alignment ~SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
_ = Int
8
peek :: Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> IO SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
-> SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM -> IO ()
poke Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
ptr SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM where
zero :: SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
zero = Bool -> Bool -> SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
SamplerYcbcrConversionYcbcrDegammaCreateInfoQCOM
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type QCOM_YCBCR_DEGAMMA_SPEC_VERSION = 1
pattern QCOM_YCBCR_DEGAMMA_SPEC_VERSION :: forall a . Integral a => a
pattern $bQCOM_YCBCR_DEGAMMA_SPEC_VERSION :: forall a. Integral a => a
$mQCOM_YCBCR_DEGAMMA_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
QCOM_YCBCR_DEGAMMA_SPEC_VERSION = 1
type QCOM_YCBCR_DEGAMMA_EXTENSION_NAME = "VK_QCOM_ycbcr_degamma"
pattern QCOM_YCBCR_DEGAMMA_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bQCOM_YCBCR_DEGAMMA_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mQCOM_YCBCR_DEGAMMA_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
QCOM_YCBCR_DEGAMMA_EXTENSION_NAME = "VK_QCOM_ycbcr_degamma"