{-# language CPP #-}
module Vulkan.Extensions.VK_NV_dedicated_allocation  ( DedicatedAllocationImageCreateInfoNV(..)
                                                     , DedicatedAllocationBufferCreateInfoNV(..)
                                                     , DedicatedAllocationMemoryAllocateInfoNV(..)
                                                     , NV_DEDICATED_ALLOCATION_SPEC_VERSION
                                                     , pattern NV_DEDICATED_ALLOCATION_SPEC_VERSION
                                                     , NV_DEDICATED_ALLOCATION_EXTENSION_NAME
                                                     , pattern NV_DEDICATED_ALLOCATION_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 GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Core10.BaseType (bool32ToBool)
import Vulkan.Core10.BaseType (boolToBool32)
import Vulkan.Core10.BaseType (Bool32)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEDICATED_ALLOCATION_BUFFER_CREATE_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEDICATED_ALLOCATION_IMAGE_CREATE_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEDICATED_ALLOCATION_MEMORY_ALLOCATE_INFO_NV))
data DedicatedAllocationImageCreateInfoNV = DedicatedAllocationImageCreateInfoNV
  { 
    
    DedicatedAllocationImageCreateInfoNV -> Bool
dedicatedAllocation :: Bool }
  deriving (Typeable, DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> Bool
(DedicatedAllocationImageCreateInfoNV
 -> DedicatedAllocationImageCreateInfoNV -> Bool)
-> (DedicatedAllocationImageCreateInfoNV
    -> DedicatedAllocationImageCreateInfoNV -> Bool)
-> Eq DedicatedAllocationImageCreateInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> Bool
$c/= :: DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> Bool
== :: DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> Bool
$c== :: DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DedicatedAllocationImageCreateInfoNV)
#endif
deriving instance Show DedicatedAllocationImageCreateInfoNV
instance ToCStruct DedicatedAllocationImageCreateInfoNV where
  withCStruct :: DedicatedAllocationImageCreateInfoNV
-> (Ptr DedicatedAllocationImageCreateInfoNV -> IO b) -> IO b
withCStruct x :: DedicatedAllocationImageCreateInfoNV
x f :: Ptr DedicatedAllocationImageCreateInfoNV -> IO b
f = Int
-> Int
-> (Ptr DedicatedAllocationImageCreateInfoNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DedicatedAllocationImageCreateInfoNV -> IO b) -> IO b)
-> (Ptr DedicatedAllocationImageCreateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DedicatedAllocationImageCreateInfoNV
p -> Ptr DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationImageCreateInfoNV
p DedicatedAllocationImageCreateInfoNV
x (Ptr DedicatedAllocationImageCreateInfoNV -> IO b
f Ptr DedicatedAllocationImageCreateInfoNV
p)
  pokeCStruct :: Ptr DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> IO b -> IO b
pokeCStruct p :: Ptr DedicatedAllocationImageCreateInfoNV
p DedicatedAllocationImageCreateInfoNV{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p Ptr DedicatedAllocationImageCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_IMAGE_CREATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p Ptr DedicatedAllocationImageCreateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p Ptr DedicatedAllocationImageCreateInfoNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
dedicatedAllocation))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DedicatedAllocationImageCreateInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr DedicatedAllocationImageCreateInfoNV
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p Ptr DedicatedAllocationImageCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_IMAGE_CREATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p Ptr DedicatedAllocationImageCreateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p Ptr DedicatedAllocationImageCreateInfoNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f
instance FromCStruct DedicatedAllocationImageCreateInfoNV where
  peekCStruct :: Ptr DedicatedAllocationImageCreateInfoNV
-> IO DedicatedAllocationImageCreateInfoNV
peekCStruct p :: Ptr DedicatedAllocationImageCreateInfoNV
p = do
    Bool32
dedicatedAllocation <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr DedicatedAllocationImageCreateInfoNV
p Ptr DedicatedAllocationImageCreateInfoNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    DedicatedAllocationImageCreateInfoNV
-> IO DedicatedAllocationImageCreateInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DedicatedAllocationImageCreateInfoNV
 -> IO DedicatedAllocationImageCreateInfoNV)
-> DedicatedAllocationImageCreateInfoNV
-> IO DedicatedAllocationImageCreateInfoNV
forall a b. (a -> b) -> a -> b
$ Bool -> DedicatedAllocationImageCreateInfoNV
DedicatedAllocationImageCreateInfoNV
             (Bool32 -> Bool
bool32ToBool Bool32
dedicatedAllocation)
instance Storable DedicatedAllocationImageCreateInfoNV where
  sizeOf :: DedicatedAllocationImageCreateInfoNV -> Int
sizeOf ~DedicatedAllocationImageCreateInfoNV
_ = 24
  alignment :: DedicatedAllocationImageCreateInfoNV -> Int
alignment ~DedicatedAllocationImageCreateInfoNV
_ = 8
  peek :: Ptr DedicatedAllocationImageCreateInfoNV
-> IO DedicatedAllocationImageCreateInfoNV
peek = Ptr DedicatedAllocationImageCreateInfoNV
-> IO DedicatedAllocationImageCreateInfoNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> IO ()
poke ptr :: Ptr DedicatedAllocationImageCreateInfoNV
ptr poked :: DedicatedAllocationImageCreateInfoNV
poked = Ptr DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationImageCreateInfoNV
ptr DedicatedAllocationImageCreateInfoNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DedicatedAllocationImageCreateInfoNV where
  zero :: DedicatedAllocationImageCreateInfoNV
zero = Bool -> DedicatedAllocationImageCreateInfoNV
DedicatedAllocationImageCreateInfoNV
           Bool
forall a. Zero a => a
zero
data DedicatedAllocationBufferCreateInfoNV = DedicatedAllocationBufferCreateInfoNV
  { 
    
    DedicatedAllocationBufferCreateInfoNV -> Bool
dedicatedAllocation :: Bool }
  deriving (Typeable, DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> Bool
(DedicatedAllocationBufferCreateInfoNV
 -> DedicatedAllocationBufferCreateInfoNV -> Bool)
-> (DedicatedAllocationBufferCreateInfoNV
    -> DedicatedAllocationBufferCreateInfoNV -> Bool)
-> Eq DedicatedAllocationBufferCreateInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> Bool
$c/= :: DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> Bool
== :: DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> Bool
$c== :: DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DedicatedAllocationBufferCreateInfoNV)
#endif
deriving instance Show DedicatedAllocationBufferCreateInfoNV
instance ToCStruct DedicatedAllocationBufferCreateInfoNV where
  withCStruct :: DedicatedAllocationBufferCreateInfoNV
-> (Ptr DedicatedAllocationBufferCreateInfoNV -> IO b) -> IO b
withCStruct x :: DedicatedAllocationBufferCreateInfoNV
x f :: Ptr DedicatedAllocationBufferCreateInfoNV -> IO b
f = Int
-> Int
-> (Ptr DedicatedAllocationBufferCreateInfoNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DedicatedAllocationBufferCreateInfoNV -> IO b) -> IO b)
-> (Ptr DedicatedAllocationBufferCreateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DedicatedAllocationBufferCreateInfoNV
p -> Ptr DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationBufferCreateInfoNV
p DedicatedAllocationBufferCreateInfoNV
x (Ptr DedicatedAllocationBufferCreateInfoNV -> IO b
f Ptr DedicatedAllocationBufferCreateInfoNV
p)
  pokeCStruct :: Ptr DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> IO b -> IO b
pokeCStruct p :: Ptr DedicatedAllocationBufferCreateInfoNV
p DedicatedAllocationBufferCreateInfoNV{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p Ptr DedicatedAllocationBufferCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_BUFFER_CREATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p Ptr DedicatedAllocationBufferCreateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p Ptr DedicatedAllocationBufferCreateInfoNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
dedicatedAllocation))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DedicatedAllocationBufferCreateInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr DedicatedAllocationBufferCreateInfoNV
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p Ptr DedicatedAllocationBufferCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_BUFFER_CREATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p Ptr DedicatedAllocationBufferCreateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p Ptr DedicatedAllocationBufferCreateInfoNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f
instance FromCStruct DedicatedAllocationBufferCreateInfoNV where
  peekCStruct :: Ptr DedicatedAllocationBufferCreateInfoNV
-> IO DedicatedAllocationBufferCreateInfoNV
peekCStruct p :: Ptr DedicatedAllocationBufferCreateInfoNV
p = do
    Bool32
dedicatedAllocation <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr DedicatedAllocationBufferCreateInfoNV
p Ptr DedicatedAllocationBufferCreateInfoNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    DedicatedAllocationBufferCreateInfoNV
-> IO DedicatedAllocationBufferCreateInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DedicatedAllocationBufferCreateInfoNV
 -> IO DedicatedAllocationBufferCreateInfoNV)
-> DedicatedAllocationBufferCreateInfoNV
-> IO DedicatedAllocationBufferCreateInfoNV
forall a b. (a -> b) -> a -> b
$ Bool -> DedicatedAllocationBufferCreateInfoNV
DedicatedAllocationBufferCreateInfoNV
             (Bool32 -> Bool
bool32ToBool Bool32
dedicatedAllocation)
instance Storable DedicatedAllocationBufferCreateInfoNV where
  sizeOf :: DedicatedAllocationBufferCreateInfoNV -> Int
sizeOf ~DedicatedAllocationBufferCreateInfoNV
_ = 24
  alignment :: DedicatedAllocationBufferCreateInfoNV -> Int
alignment ~DedicatedAllocationBufferCreateInfoNV
_ = 8
  peek :: Ptr DedicatedAllocationBufferCreateInfoNV
-> IO DedicatedAllocationBufferCreateInfoNV
peek = Ptr DedicatedAllocationBufferCreateInfoNV
-> IO DedicatedAllocationBufferCreateInfoNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> IO ()
poke ptr :: Ptr DedicatedAllocationBufferCreateInfoNV
ptr poked :: DedicatedAllocationBufferCreateInfoNV
poked = Ptr DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationBufferCreateInfoNV
ptr DedicatedAllocationBufferCreateInfoNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DedicatedAllocationBufferCreateInfoNV where
  zero :: DedicatedAllocationBufferCreateInfoNV
zero = Bool -> DedicatedAllocationBufferCreateInfoNV
DedicatedAllocationBufferCreateInfoNV
           Bool
forall a. Zero a => a
zero
data DedicatedAllocationMemoryAllocateInfoNV = DedicatedAllocationMemoryAllocateInfoNV
  { 
    
    DedicatedAllocationMemoryAllocateInfoNV -> Image
image :: Image
  , 
    
    DedicatedAllocationMemoryAllocateInfoNV -> Buffer
buffer :: Buffer
  }
  deriving (Typeable, DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> Bool
(DedicatedAllocationMemoryAllocateInfoNV
 -> DedicatedAllocationMemoryAllocateInfoNV -> Bool)
-> (DedicatedAllocationMemoryAllocateInfoNV
    -> DedicatedAllocationMemoryAllocateInfoNV -> Bool)
-> Eq DedicatedAllocationMemoryAllocateInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> Bool
$c/= :: DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> Bool
== :: DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> Bool
$c== :: DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DedicatedAllocationMemoryAllocateInfoNV)
#endif
deriving instance Show DedicatedAllocationMemoryAllocateInfoNV
instance ToCStruct DedicatedAllocationMemoryAllocateInfoNV where
  withCStruct :: DedicatedAllocationMemoryAllocateInfoNV
-> (Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b) -> IO b
withCStruct x :: DedicatedAllocationMemoryAllocateInfoNV
x f :: Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b
f = Int
-> Int
-> (Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b) -> IO b)
-> (Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DedicatedAllocationMemoryAllocateInfoNV
p -> Ptr DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationMemoryAllocateInfoNV
p DedicatedAllocationMemoryAllocateInfoNV
x (Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b
f Ptr DedicatedAllocationMemoryAllocateInfoNV
p)
  pokeCStruct :: Ptr DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> IO b -> IO b
pokeCStruct p :: Ptr DedicatedAllocationMemoryAllocateInfoNV
p DedicatedAllocationMemoryAllocateInfoNV{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p Ptr DedicatedAllocationMemoryAllocateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_MEMORY_ALLOCATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p Ptr DedicatedAllocationMemoryAllocateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p Ptr DedicatedAllocationMemoryAllocateInfoNV -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Image)) (Image
image)
    Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p Ptr DedicatedAllocationMemoryAllocateInfoNV -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Buffer)) (Buffer
buffer)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr DedicatedAllocationMemoryAllocateInfoNV
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p Ptr DedicatedAllocationMemoryAllocateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_MEMORY_ALLOCATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p Ptr DedicatedAllocationMemoryAllocateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f
instance FromCStruct DedicatedAllocationMemoryAllocateInfoNV where
  peekCStruct :: Ptr DedicatedAllocationMemoryAllocateInfoNV
-> IO DedicatedAllocationMemoryAllocateInfoNV
peekCStruct p :: Ptr DedicatedAllocationMemoryAllocateInfoNV
p = do
    Image
image <- Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p Ptr DedicatedAllocationMemoryAllocateInfoNV -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Image))
    Buffer
buffer <- Ptr Buffer -> IO Buffer
forall a. Storable a => Ptr a -> IO a
peek @Buffer ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p Ptr DedicatedAllocationMemoryAllocateInfoNV -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Buffer))
    DedicatedAllocationMemoryAllocateInfoNV
-> IO DedicatedAllocationMemoryAllocateInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DedicatedAllocationMemoryAllocateInfoNV
 -> IO DedicatedAllocationMemoryAllocateInfoNV)
-> DedicatedAllocationMemoryAllocateInfoNV
-> IO DedicatedAllocationMemoryAllocateInfoNV
forall a b. (a -> b) -> a -> b
$ Image -> Buffer -> DedicatedAllocationMemoryAllocateInfoNV
DedicatedAllocationMemoryAllocateInfoNV
             Image
image Buffer
buffer
instance Storable DedicatedAllocationMemoryAllocateInfoNV where
  sizeOf :: DedicatedAllocationMemoryAllocateInfoNV -> Int
sizeOf ~DedicatedAllocationMemoryAllocateInfoNV
_ = 32
  alignment :: DedicatedAllocationMemoryAllocateInfoNV -> Int
alignment ~DedicatedAllocationMemoryAllocateInfoNV
_ = 8
  peek :: Ptr DedicatedAllocationMemoryAllocateInfoNV
-> IO DedicatedAllocationMemoryAllocateInfoNV
peek = Ptr DedicatedAllocationMemoryAllocateInfoNV
-> IO DedicatedAllocationMemoryAllocateInfoNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> IO ()
poke ptr :: Ptr DedicatedAllocationMemoryAllocateInfoNV
ptr poked :: DedicatedAllocationMemoryAllocateInfoNV
poked = Ptr DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationMemoryAllocateInfoNV
ptr DedicatedAllocationMemoryAllocateInfoNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DedicatedAllocationMemoryAllocateInfoNV where
  zero :: DedicatedAllocationMemoryAllocateInfoNV
zero = Image -> Buffer -> DedicatedAllocationMemoryAllocateInfoNV
DedicatedAllocationMemoryAllocateInfoNV
           Image
forall a. Zero a => a
zero
           Buffer
forall a. Zero a => a
zero
type NV_DEDICATED_ALLOCATION_SPEC_VERSION = 1
pattern NV_DEDICATED_ALLOCATION_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_DEDICATED_ALLOCATION_SPEC_VERSION :: a
$mNV_DEDICATED_ALLOCATION_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_DEDICATED_ALLOCATION_SPEC_VERSION = 1
type NV_DEDICATED_ALLOCATION_EXTENSION_NAME = "VK_NV_dedicated_allocation"
pattern NV_DEDICATED_ALLOCATION_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_DEDICATED_ALLOCATION_EXTENSION_NAME :: a
$mNV_DEDICATED_ALLOCATION_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_DEDICATED_ALLOCATION_EXTENSION_NAME = "VK_NV_dedicated_allocation"