{-# language CPP #-}
module Vulkan.Extensions.VK_NV_corner_sampled_image ( PhysicalDeviceCornerSampledImageFeaturesNV(..)
, NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION
, pattern NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION
, NV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME
, pattern NV_CORNER_SAMPLED_IMAGE_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_CORNER_SAMPLED_IMAGE_FEATURES_NV))
data PhysicalDeviceCornerSampledImageFeaturesNV = PhysicalDeviceCornerSampledImageFeaturesNV
{
PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
cornerSampledImage :: Bool }
deriving (Typeable, PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
$c/= :: PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
== :: PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
$c== :: PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceCornerSampledImageFeaturesNV)
#endif
deriving instance Show PhysicalDeviceCornerSampledImageFeaturesNV
instance ToCStruct PhysicalDeviceCornerSampledImageFeaturesNV where
withCStruct :: forall b.
PhysicalDeviceCornerSampledImageFeaturesNV
-> (Ptr PhysicalDeviceCornerSampledImageFeaturesNV -> IO b) -> IO b
withCStruct PhysicalDeviceCornerSampledImageFeaturesNV
x Ptr PhysicalDeviceCornerSampledImageFeaturesNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceCornerSampledImageFeaturesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCornerSampledImageFeaturesNV
p PhysicalDeviceCornerSampledImageFeaturesNV
x (Ptr PhysicalDeviceCornerSampledImageFeaturesNV -> IO b
f Ptr PhysicalDeviceCornerSampledImageFeaturesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCornerSampledImageFeaturesNV
p PhysicalDeviceCornerSampledImageFeaturesNV{Bool
cornerSampledImage :: Bool
$sel:cornerSampledImage:PhysicalDeviceCornerSampledImageFeaturesNV :: PhysicalDeviceCornerSampledImageFeaturesNV -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCornerSampledImageFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_CORNER_SAMPLED_IMAGE_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCornerSampledImageFeaturesNV
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 PhysicalDeviceCornerSampledImageFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
cornerSampledImage))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceCornerSampledImageFeaturesNV -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceCornerSampledImageFeaturesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCornerSampledImageFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_CORNER_SAMPLED_IMAGE_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCornerSampledImageFeaturesNV
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 PhysicalDeviceCornerSampledImageFeaturesNV
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 PhysicalDeviceCornerSampledImageFeaturesNV where
peekCStruct :: Ptr PhysicalDeviceCornerSampledImageFeaturesNV
-> IO PhysicalDeviceCornerSampledImageFeaturesNV
peekCStruct Ptr PhysicalDeviceCornerSampledImageFeaturesNV
p = do
Bool32
cornerSampledImage <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceCornerSampledImageFeaturesNV
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 -> PhysicalDeviceCornerSampledImageFeaturesNV
PhysicalDeviceCornerSampledImageFeaturesNV
(Bool32 -> Bool
bool32ToBool Bool32
cornerSampledImage)
instance Storable PhysicalDeviceCornerSampledImageFeaturesNV where
sizeOf :: PhysicalDeviceCornerSampledImageFeaturesNV -> Int
sizeOf ~PhysicalDeviceCornerSampledImageFeaturesNV
_ = Int
24
alignment :: PhysicalDeviceCornerSampledImageFeaturesNV -> Int
alignment ~PhysicalDeviceCornerSampledImageFeaturesNV
_ = Int
8
peek :: Ptr PhysicalDeviceCornerSampledImageFeaturesNV
-> IO PhysicalDeviceCornerSampledImageFeaturesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceCornerSampledImageFeaturesNV
-> PhysicalDeviceCornerSampledImageFeaturesNV -> IO ()
poke Ptr PhysicalDeviceCornerSampledImageFeaturesNV
ptr PhysicalDeviceCornerSampledImageFeaturesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCornerSampledImageFeaturesNV
ptr PhysicalDeviceCornerSampledImageFeaturesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceCornerSampledImageFeaturesNV where
zero :: PhysicalDeviceCornerSampledImageFeaturesNV
zero = Bool -> PhysicalDeviceCornerSampledImageFeaturesNV
PhysicalDeviceCornerSampledImageFeaturesNV
forall a. Zero a => a
zero
type NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION = 2
pattern NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_CORNER_SAMPLED_IMAGE_SPEC_VERSION :: forall a. Integral a => a
$mNV_CORNER_SAMPLED_IMAGE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_CORNER_SAMPLED_IMAGE_SPEC_VERSION = 2
type NV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME = "VK_NV_corner_sampled_image"
pattern NV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_CORNER_SAMPLED_IMAGE_EXTENSION_NAME = "VK_NV_corner_sampled_image"