{-# language CPP #-}
module Vulkan.Extensions.VK_NV_extended_sparse_address_space ( PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV(..)
, PhysicalDeviceExtendedSparseAddressSpacePropertiesNV(..)
, NV_EXTENDED_SPARSE_ADDRESS_SPACE_SPEC_VERSION
, pattern NV_EXTENDED_SPARSE_ADDRESS_SPACE_SPEC_VERSION
, NV_EXTENDED_SPARSE_ADDRESS_SPACE_EXTENSION_NAME
, pattern NV_EXTENDED_SPARSE_ADDRESS_SPACE_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.BufferUsageFlagBits (BufferUsageFlags)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_SPARSE_ADDRESS_SPACE_FEATURES_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_SPARSE_ADDRESS_SPACE_PROPERTIES_NV))
data PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV = PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
{
PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Bool
extendedSparseAddressSpace :: Bool }
deriving (Typeable, PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Bool
(PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Bool)
-> (PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Bool)
-> Eq PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Bool
== :: PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Bool
$c/= :: PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Bool
/= :: PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV)
#endif
deriving instance Show PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
instance ToCStruct PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV where
withCStruct :: forall b.
PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> (Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> IO b)
-> IO b
withCStruct PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
x Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> IO b
f = Int
-> (Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> IO b)
-> IO b)
-> (Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p -> Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO b
-> IO b
forall b.
Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
x (Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> IO b
f Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV{Bool
$sel:extendedSparseAddressSpace:PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV :: PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Bool
extendedSparseAddressSpace :: Bool
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_SPARSE_ADDRESS_SPACE_FEATURES_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
extendedSparseAddressSpace))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_SPARSE_ADDRESS_SPACE_FEATURES_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV where
peekCStruct :: Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
peekCStruct Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p = do
Bool32
extendedSparseAddressSpace <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV)
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
(Bool32 -> Bool
bool32ToBool Bool32
extendedSparseAddressSpace)
instance Storable PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV where
sizeOf :: PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Int
sizeOf ~PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
_ = Int
24
alignment :: PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> Int
alignment ~PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
_ = Int
8
peek :: Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
peek = Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV -> IO ()
poke Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
poked = Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO ()
-> IO ()
forall b.
Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
ptr PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
poked (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV where
zero :: PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
zero = Bool -> PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
PhysicalDeviceExtendedSparseAddressSpaceFeaturesNV
Bool
forall a. Zero a => a
zero
data PhysicalDeviceExtendedSparseAddressSpacePropertiesNV = PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
{
PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> DeviceSize
extendedSparseAddressSpaceSize :: DeviceSize
,
PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> ImageUsageFlags
extendedSparseImageUsageFlags :: ImageUsageFlags
,
PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> BufferUsageFlags
extendedSparseBufferUsageFlags :: BufferUsageFlags
}
deriving (Typeable, PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> Bool
(PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> Bool)
-> (PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> Bool)
-> Eq PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> Bool
== :: PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> Bool
$c/= :: PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> Bool
/= :: PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceExtendedSparseAddressSpacePropertiesNV)
#endif
deriving instance Show PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
instance ToCStruct PhysicalDeviceExtendedSparseAddressSpacePropertiesNV where
withCStruct :: forall b.
PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> (Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO b)
-> IO b
withCStruct PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
x Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> IO b
f = Int
-> (Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> IO b)
-> IO b)
-> (Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p -> Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO b
-> IO b
forall b.
Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
x (Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> IO b
f Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p PhysicalDeviceExtendedSparseAddressSpacePropertiesNV{DeviceSize
ImageUsageFlags
BufferUsageFlags
$sel:extendedSparseAddressSpaceSize:PhysicalDeviceExtendedSparseAddressSpacePropertiesNV :: PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> DeviceSize
$sel:extendedSparseImageUsageFlags:PhysicalDeviceExtendedSparseAddressSpacePropertiesNV :: PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> ImageUsageFlags
$sel:extendedSparseBufferUsageFlags:PhysicalDeviceExtendedSparseAddressSpacePropertiesNV :: PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> BufferUsageFlags
extendedSparseAddressSpaceSize :: DeviceSize
extendedSparseImageUsageFlags :: ImageUsageFlags
extendedSparseBufferUsageFlags :: BufferUsageFlags
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_SPARSE_ADDRESS_SPACE_PROPERTIES_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (DeviceSize
extendedSparseAddressSpaceSize)
Ptr ImageUsageFlags -> ImageUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ImageUsageFlags)) (ImageUsageFlags
extendedSparseImageUsageFlags)
Ptr BufferUsageFlags -> BufferUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr BufferUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr BufferUsageFlags)) (BufferUsageFlags
extendedSparseBufferUsageFlags)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_SPARSE_ADDRESS_SPACE_PROPERTIES_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
Ptr ImageUsageFlags -> ImageUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ImageUsageFlags)) (ImageUsageFlags
forall a. Zero a => a
zero)
Ptr BufferUsageFlags -> BufferUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr BufferUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr BufferUsageFlags)) (BufferUsageFlags
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDeviceExtendedSparseAddressSpacePropertiesNV where
peekCStruct :: Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
peekCStruct Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p = do
DeviceSize
extendedSparseAddressSpaceSize <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize))
ImageUsageFlags
extendedSparseImageUsageFlags <- forall a. Storable a => Ptr a -> IO a
peek @ImageUsageFlags ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ImageUsageFlags))
BufferUsageFlags
extendedSparseBufferUsageFlags <- forall a. Storable a => Ptr a -> IO a
peek @BufferUsageFlags ((Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
p Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> Int -> Ptr BufferUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr BufferUsageFlags))
PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO PhysicalDeviceExtendedSparseAddressSpacePropertiesNV)
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
forall a b. (a -> b) -> a -> b
$ DeviceSize
-> ImageUsageFlags
-> BufferUsageFlags
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
DeviceSize
extendedSparseAddressSpaceSize
ImageUsageFlags
extendedSparseImageUsageFlags
BufferUsageFlags
extendedSparseBufferUsageFlags
instance Storable PhysicalDeviceExtendedSparseAddressSpacePropertiesNV where
sizeOf :: PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> Int
sizeOf ~PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
_ = Int
32
alignment :: PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> Int
alignment ~PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
_ = Int
8
peek :: Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
peek = Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV -> IO ()
poke Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
poked = Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO ()
-> IO ()
forall b.
Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
ptr PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
poked (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceExtendedSparseAddressSpacePropertiesNV where
zero :: PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
zero = DeviceSize
-> ImageUsageFlags
-> BufferUsageFlags
-> PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
PhysicalDeviceExtendedSparseAddressSpacePropertiesNV
DeviceSize
forall a. Zero a => a
zero
ImageUsageFlags
forall a. Zero a => a
zero
BufferUsageFlags
forall a. Zero a => a
zero
type NV_EXTENDED_SPARSE_ADDRESS_SPACE_SPEC_VERSION = 1
pattern NV_EXTENDED_SPARSE_ADDRESS_SPACE_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_EXTENDED_SPARSE_ADDRESS_SPACE_SPEC_VERSION :: forall a. Integral a => a
$mNV_EXTENDED_SPARSE_ADDRESS_SPACE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_EXTENDED_SPARSE_ADDRESS_SPACE_SPEC_VERSION = 1
type NV_EXTENDED_SPARSE_ADDRESS_SPACE_EXTENSION_NAME = "VK_NV_extended_sparse_address_space"
pattern NV_EXTENDED_SPARSE_ADDRESS_SPACE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_EXTENDED_SPARSE_ADDRESS_SPACE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_EXTENDED_SPARSE_ADDRESS_SPACE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_EXTENDED_SPARSE_ADDRESS_SPACE_EXTENSION_NAME = "VK_NV_extended_sparse_address_space"