{-# language CPP #-}
module Graphics.Vulkan.Extensions.VK_NV_representative_fragment_test ( PhysicalDeviceRepresentativeFragmentTestFeaturesNV(..)
, PipelineRepresentativeFragmentTestStateCreateInfoNV(..)
, NV_REPRESENTATIVE_FRAGMENT_TEST_SPEC_VERSION
, pattern NV_REPRESENTATIVE_FRAGMENT_TEST_SPEC_VERSION
, NV_REPRESENTATIVE_FRAGMENT_TEST_EXTENSION_NAME
, pattern NV_REPRESENTATIVE_FRAGMENT_TEST_EXTENSION_NAME
) where
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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 Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Graphics.Vulkan.Core10.BaseType (bool32ToBool)
import Graphics.Vulkan.Core10.BaseType (boolToBool32)
import Graphics.Vulkan.Core10.BaseType (Bool32)
import Graphics.Vulkan.CStruct (FromCStruct)
import Graphics.Vulkan.CStruct (FromCStruct(..))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType)
import Graphics.Vulkan.CStruct (ToCStruct)
import Graphics.Vulkan.CStruct (ToCStruct(..))
import Graphics.Vulkan.Zero (Zero(..))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_REPRESENTATIVE_FRAGMENT_TEST_FEATURES_NV))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_REPRESENTATIVE_FRAGMENT_TEST_STATE_CREATE_INFO_NV))
data PhysicalDeviceRepresentativeFragmentTestFeaturesNV = PhysicalDeviceRepresentativeFragmentTestFeaturesNV
{
representativeFragmentTest :: Bool }
deriving (Typeable)
deriving instance Show PhysicalDeviceRepresentativeFragmentTestFeaturesNV
instance ToCStruct PhysicalDeviceRepresentativeFragmentTestFeaturesNV where
withCStruct x f = allocaBytesAligned 24 8 $ \p -> pokeCStruct p x (f p)
pokeCStruct p PhysicalDeviceRepresentativeFragmentTestFeaturesNV{..} f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PHYSICAL_DEVICE_REPRESENTATIVE_FRAGMENT_TEST_FEATURES_NV)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (representativeFragmentTest))
f
cStructSize = 24
cStructAlignment = 8
pokeZeroCStruct p f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PHYSICAL_DEVICE_REPRESENTATIVE_FRAGMENT_TEST_FEATURES_NV)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (zero))
f
instance FromCStruct PhysicalDeviceRepresentativeFragmentTestFeaturesNV where
peekCStruct p = do
representativeFragmentTest <- peek @Bool32 ((p `plusPtr` 16 :: Ptr Bool32))
pure $ PhysicalDeviceRepresentativeFragmentTestFeaturesNV
(bool32ToBool representativeFragmentTest)
instance Storable PhysicalDeviceRepresentativeFragmentTestFeaturesNV where
sizeOf ~_ = 24
alignment ~_ = 8
peek = peekCStruct
poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero PhysicalDeviceRepresentativeFragmentTestFeaturesNV where
zero = PhysicalDeviceRepresentativeFragmentTestFeaturesNV
zero
data PipelineRepresentativeFragmentTestStateCreateInfoNV = PipelineRepresentativeFragmentTestStateCreateInfoNV
{
representativeFragmentTestEnable :: Bool }
deriving (Typeable)
deriving instance Show PipelineRepresentativeFragmentTestStateCreateInfoNV
instance ToCStruct PipelineRepresentativeFragmentTestStateCreateInfoNV where
withCStruct x f = allocaBytesAligned 24 8 $ \p -> pokeCStruct p x (f p)
pokeCStruct p PipelineRepresentativeFragmentTestStateCreateInfoNV{..} f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PIPELINE_REPRESENTATIVE_FRAGMENT_TEST_STATE_CREATE_INFO_NV)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (representativeFragmentTestEnable))
f
cStructSize = 24
cStructAlignment = 8
pokeZeroCStruct p f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PIPELINE_REPRESENTATIVE_FRAGMENT_TEST_STATE_CREATE_INFO_NV)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (zero))
f
instance FromCStruct PipelineRepresentativeFragmentTestStateCreateInfoNV where
peekCStruct p = do
representativeFragmentTestEnable <- peek @Bool32 ((p `plusPtr` 16 :: Ptr Bool32))
pure $ PipelineRepresentativeFragmentTestStateCreateInfoNV
(bool32ToBool representativeFragmentTestEnable)
instance Storable PipelineRepresentativeFragmentTestStateCreateInfoNV where
sizeOf ~_ = 24
alignment ~_ = 8
peek = peekCStruct
poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero PipelineRepresentativeFragmentTestStateCreateInfoNV where
zero = PipelineRepresentativeFragmentTestStateCreateInfoNV
zero
type NV_REPRESENTATIVE_FRAGMENT_TEST_SPEC_VERSION = 2
pattern NV_REPRESENTATIVE_FRAGMENT_TEST_SPEC_VERSION :: forall a . Integral a => a
pattern NV_REPRESENTATIVE_FRAGMENT_TEST_SPEC_VERSION = 2
type NV_REPRESENTATIVE_FRAGMENT_TEST_EXTENSION_NAME = "VK_NV_representative_fragment_test"
pattern NV_REPRESENTATIVE_FRAGMENT_TEST_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern NV_REPRESENTATIVE_FRAGMENT_TEST_EXTENSION_NAME = "VK_NV_representative_fragment_test"