{-# language CPP #-}
module Vulkan.Extensions.VK_NV_dedicated_allocation_image_aliasing ( PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV(..)
, NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION
, pattern NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION
, NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME
, pattern NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_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_DEDICATED_ALLOCATION_IMAGE_ALIASING_FEATURES_NV))
data PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV = PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
{
PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
dedicatedAllocationImageAliasing :: Bool }
deriving (Typeable, PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
$c/= :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
== :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
$c== :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV)
#endif
deriving instance Show PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
instance ToCStruct PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV where
withCStruct :: forall b.
PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> (Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO b)
-> IO b
withCStruct PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
x Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
x (Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO b
f Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV{Bool
dedicatedAllocationImageAliasing :: Bool
$sel:dedicatedAllocationImageAliasing:PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEDICATED_ALLOCATION_IMAGE_ALIASING_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
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 PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
dedicatedAllocationImageAliasing))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEDICATED_ALLOCATION_IMAGE_ALIASING_FEATURES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
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 PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
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 PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV where
peekCStruct :: Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
peekCStruct Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
p = do
Bool32
dedicatedAllocationImageAliasing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
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 -> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
(Bool32 -> Bool
bool32ToBool Bool32
dedicatedAllocationImageAliasing)
instance Storable PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV where
sizeOf :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Int
sizeOf ~PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
_ = Int
24
alignment :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV -> Int
alignment ~PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
_ = Int
8
peek :: Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
-> IO ()
poke Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
ptr PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV where
zero :: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
zero = Bool -> PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV
forall a. Zero a => a
zero
type NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION = 1
pattern NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION :: forall a. Integral a => a
$mNV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_SPEC_VERSION = 1
type NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME = "VK_NV_dedicated_allocation_image_aliasing"
pattern NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_DEDICATED_ALLOCATION_IMAGE_ALIASING_EXTENSION_NAME = "VK_NV_dedicated_allocation_image_aliasing"