{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_portability_subset ( PhysicalDevicePortabilitySubsetFeaturesKHR(..)
, PhysicalDevicePortabilitySubsetPropertiesKHR(..)
, KHR_PORTABILITY_SUBSET_SPEC_VERSION
, pattern KHR_PORTABILITY_SUBSET_SPEC_VERSION
, KHR_PORTABILITY_SUBSET_EXTENSION_NAME
, pattern KHR_PORTABILITY_SUBSET_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.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_PORTABILITY_SUBSET_FEATURES_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_PORTABILITY_SUBSET_PROPERTIES_KHR))
data PhysicalDevicePortabilitySubsetFeaturesKHR = PhysicalDevicePortabilitySubsetFeaturesKHR
{
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
constantAlphaColorBlendFactors :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
events :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
imageViewFormatReinterpretation :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
imageViewFormatSwizzle :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
imageView2DOn3DImage :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
multisampleArrayImage :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
mutableComparisonSamplers :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
pointPolygons :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
samplerMipLodBias :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
separateStencilMaskRef :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
shaderSampleRateInterpolationFunctions :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
tessellationIsolines :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
tessellationPointMode :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
triangleFans :: Bool
,
PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
vertexAttributeAccessBeyondStride :: Bool
}
deriving (Typeable, PhysicalDevicePortabilitySubsetFeaturesKHR
-> PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevicePortabilitySubsetFeaturesKHR
-> PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$c/= :: PhysicalDevicePortabilitySubsetFeaturesKHR
-> PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
== :: PhysicalDevicePortabilitySubsetFeaturesKHR
-> PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$c== :: PhysicalDevicePortabilitySubsetFeaturesKHR
-> PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevicePortabilitySubsetFeaturesKHR)
#endif
deriving instance Show PhysicalDevicePortabilitySubsetFeaturesKHR
instance ToCStruct PhysicalDevicePortabilitySubsetFeaturesKHR where
withCStruct :: forall b.
PhysicalDevicePortabilitySubsetFeaturesKHR
-> (Ptr PhysicalDevicePortabilitySubsetFeaturesKHR -> IO b) -> IO b
withCStruct PhysicalDevicePortabilitySubsetFeaturesKHR
x Ptr PhysicalDevicePortabilitySubsetFeaturesKHR -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
80 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p PhysicalDevicePortabilitySubsetFeaturesKHR
x (Ptr PhysicalDevicePortabilitySubsetFeaturesKHR -> IO b
f Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p)
pokeCStruct :: forall b.
Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
-> PhysicalDevicePortabilitySubsetFeaturesKHR -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p PhysicalDevicePortabilitySubsetFeaturesKHR{Bool
vertexAttributeAccessBeyondStride :: Bool
triangleFans :: Bool
tessellationPointMode :: Bool
tessellationIsolines :: Bool
shaderSampleRateInterpolationFunctions :: Bool
separateStencilMaskRef :: Bool
samplerMipLodBias :: Bool
pointPolygons :: Bool
mutableComparisonSamplers :: Bool
multisampleArrayImage :: Bool
imageView2DOn3DImage :: Bool
imageViewFormatSwizzle :: Bool
imageViewFormatReinterpretation :: Bool
events :: Bool
constantAlphaColorBlendFactors :: Bool
$sel:vertexAttributeAccessBeyondStride:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:triangleFans:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:tessellationPointMode:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:tessellationIsolines:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:shaderSampleRateInterpolationFunctions:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:separateStencilMaskRef:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:samplerMipLodBias:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:pointPolygons:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:mutableComparisonSamplers:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:multisampleArrayImage:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:imageView2DOn3DImage:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:imageViewFormatSwizzle:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:imageViewFormatReinterpretation:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:events:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
$sel:constantAlphaColorBlendFactors:PhysicalDevicePortabilitySubsetFeaturesKHR :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PORTABILITY_SUBSET_FEATURES_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
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 PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
constantAlphaColorBlendFactors))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
events))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
imageViewFormatReinterpretation))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
imageViewFormatSwizzle))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
imageView2DOn3DImage))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multisampleArrayImage))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
mutableComparisonSamplers))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
pointPolygons))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
samplerMipLodBias))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
separateStencilMaskRef))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSampleRateInterpolationFunctions))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
tessellationIsolines))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
tessellationPointMode))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
triangleFans))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
vertexAttributeAccessBeyondStride))
IO b
f
cStructSize :: Int
cStructSize = Int
80
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDevicePortabilitySubsetFeaturesKHR -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PORTABILITY_SUBSET_FEATURES_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
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 PhysicalDevicePortabilitySubsetFeaturesKHR
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 PhysicalDevicePortabilitySubsetFeaturesKHR
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 PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDevicePortabilitySubsetFeaturesKHR where
peekCStruct :: Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
-> IO PhysicalDevicePortabilitySubsetFeaturesKHR
peekCStruct Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p = do
Bool32
constantAlphaColorBlendFactors <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
events <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
imageViewFormatReinterpretation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
Bool32
imageViewFormatSwizzle <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
Bool32
imageView2DOn3DImage <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32))
Bool32
multisampleArrayImage <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32))
Bool32
mutableComparisonSamplers <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32))
Bool32
pointPolygons <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32))
Bool32
samplerMipLodBias <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32))
Bool32
separateStencilMaskRef <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32))
Bool32
shaderSampleRateInterpolationFunctions <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32))
Bool32
tessellationIsolines <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32))
Bool32
tessellationPointMode <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32))
Bool32
triangleFans <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32))
Bool32
vertexAttributeAccessBeyondStride <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDevicePortabilitySubsetFeaturesKHR
PhysicalDevicePortabilitySubsetFeaturesKHR
(Bool32 -> Bool
bool32ToBool Bool32
constantAlphaColorBlendFactors)
(Bool32 -> Bool
bool32ToBool Bool32
events)
(Bool32 -> Bool
bool32ToBool Bool32
imageViewFormatReinterpretation)
(Bool32 -> Bool
bool32ToBool Bool32
imageViewFormatSwizzle)
(Bool32 -> Bool
bool32ToBool Bool32
imageView2DOn3DImage)
(Bool32 -> Bool
bool32ToBool Bool32
multisampleArrayImage)
(Bool32 -> Bool
bool32ToBool Bool32
mutableComparisonSamplers)
(Bool32 -> Bool
bool32ToBool Bool32
pointPolygons)
(Bool32 -> Bool
bool32ToBool Bool32
samplerMipLodBias)
(Bool32 -> Bool
bool32ToBool Bool32
separateStencilMaskRef)
(Bool32 -> Bool
bool32ToBool Bool32
shaderSampleRateInterpolationFunctions)
(Bool32 -> Bool
bool32ToBool Bool32
tessellationIsolines)
(Bool32 -> Bool
bool32ToBool Bool32
tessellationPointMode)
(Bool32 -> Bool
bool32ToBool Bool32
triangleFans)
(Bool32 -> Bool
bool32ToBool Bool32
vertexAttributeAccessBeyondStride)
instance Storable PhysicalDevicePortabilitySubsetFeaturesKHR where
sizeOf :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Int
sizeOf ~PhysicalDevicePortabilitySubsetFeaturesKHR
_ = Int
80
alignment :: PhysicalDevicePortabilitySubsetFeaturesKHR -> Int
alignment ~PhysicalDevicePortabilitySubsetFeaturesKHR
_ = Int
8
peek :: Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
-> IO PhysicalDevicePortabilitySubsetFeaturesKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
-> PhysicalDevicePortabilitySubsetFeaturesKHR -> IO ()
poke Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
ptr PhysicalDevicePortabilitySubsetFeaturesKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePortabilitySubsetFeaturesKHR
ptr PhysicalDevicePortabilitySubsetFeaturesKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDevicePortabilitySubsetFeaturesKHR where
zero :: PhysicalDevicePortabilitySubsetFeaturesKHR
zero = Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDevicePortabilitySubsetFeaturesKHR
PhysicalDevicePortabilitySubsetFeaturesKHR
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDevicePortabilitySubsetPropertiesKHR = PhysicalDevicePortabilitySubsetPropertiesKHR
{
PhysicalDevicePortabilitySubsetPropertiesKHR -> Word32
minVertexInputBindingStrideAlignment :: Word32 }
deriving (Typeable, PhysicalDevicePortabilitySubsetPropertiesKHR
-> PhysicalDevicePortabilitySubsetPropertiesKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevicePortabilitySubsetPropertiesKHR
-> PhysicalDevicePortabilitySubsetPropertiesKHR -> Bool
$c/= :: PhysicalDevicePortabilitySubsetPropertiesKHR
-> PhysicalDevicePortabilitySubsetPropertiesKHR -> Bool
== :: PhysicalDevicePortabilitySubsetPropertiesKHR
-> PhysicalDevicePortabilitySubsetPropertiesKHR -> Bool
$c== :: PhysicalDevicePortabilitySubsetPropertiesKHR
-> PhysicalDevicePortabilitySubsetPropertiesKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevicePortabilitySubsetPropertiesKHR)
#endif
deriving instance Show PhysicalDevicePortabilitySubsetPropertiesKHR
instance ToCStruct PhysicalDevicePortabilitySubsetPropertiesKHR where
withCStruct :: forall b.
PhysicalDevicePortabilitySubsetPropertiesKHR
-> (Ptr PhysicalDevicePortabilitySubsetPropertiesKHR -> IO b)
-> IO b
withCStruct PhysicalDevicePortabilitySubsetPropertiesKHR
x Ptr PhysicalDevicePortabilitySubsetPropertiesKHR -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
p PhysicalDevicePortabilitySubsetPropertiesKHR
x (Ptr PhysicalDevicePortabilitySubsetPropertiesKHR -> IO b
f Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
p)
pokeCStruct :: forall b.
Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
-> PhysicalDevicePortabilitySubsetPropertiesKHR -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
p PhysicalDevicePortabilitySubsetPropertiesKHR{Word32
minVertexInputBindingStrideAlignment :: Word32
$sel:minVertexInputBindingStrideAlignment:PhysicalDevicePortabilitySubsetPropertiesKHR :: PhysicalDevicePortabilitySubsetPropertiesKHR -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PORTABILITY_SUBSET_PROPERTIES_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
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 PhysicalDevicePortabilitySubsetPropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
minVertexInputBindingStrideAlignment)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDevicePortabilitySubsetPropertiesKHR -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PORTABILITY_SUBSET_PROPERTIES_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
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 PhysicalDevicePortabilitySubsetPropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDevicePortabilitySubsetPropertiesKHR where
peekCStruct :: Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
-> IO PhysicalDevicePortabilitySubsetPropertiesKHR
peekCStruct Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
p = do
Word32
minVertexInputBindingStrideAlignment <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32 -> PhysicalDevicePortabilitySubsetPropertiesKHR
PhysicalDevicePortabilitySubsetPropertiesKHR
Word32
minVertexInputBindingStrideAlignment
instance Storable PhysicalDevicePortabilitySubsetPropertiesKHR where
sizeOf :: PhysicalDevicePortabilitySubsetPropertiesKHR -> Int
sizeOf ~PhysicalDevicePortabilitySubsetPropertiesKHR
_ = Int
24
alignment :: PhysicalDevicePortabilitySubsetPropertiesKHR -> Int
alignment ~PhysicalDevicePortabilitySubsetPropertiesKHR
_ = Int
8
peek :: Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
-> IO PhysicalDevicePortabilitySubsetPropertiesKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
-> PhysicalDevicePortabilitySubsetPropertiesKHR -> IO ()
poke Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
ptr PhysicalDevicePortabilitySubsetPropertiesKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePortabilitySubsetPropertiesKHR
ptr PhysicalDevicePortabilitySubsetPropertiesKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDevicePortabilitySubsetPropertiesKHR where
zero :: PhysicalDevicePortabilitySubsetPropertiesKHR
zero = Word32 -> PhysicalDevicePortabilitySubsetPropertiesKHR
PhysicalDevicePortabilitySubsetPropertiesKHR
forall a. Zero a => a
zero
type KHR_PORTABILITY_SUBSET_SPEC_VERSION = 1
pattern KHR_PORTABILITY_SUBSET_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_PORTABILITY_SUBSET_SPEC_VERSION :: forall a. Integral a => a
$mKHR_PORTABILITY_SUBSET_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_PORTABILITY_SUBSET_SPEC_VERSION = 1
type KHR_PORTABILITY_SUBSET_EXTENSION_NAME = "VK_KHR_portability_subset"
pattern KHR_PORTABILITY_SUBSET_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_PORTABILITY_SUBSET_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mKHR_PORTABILITY_SUBSET_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_PORTABILITY_SUBSET_EXTENSION_NAME = "VK_KHR_portability_subset"