{-# language CPP #-}
module Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation  ( MemoryDedicatedRequirements(..)
                                                                , MemoryDedicatedAllocateInfo(..)
                                                                , StructureType(..)
                                                                ) where
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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.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_MEMORY_DEDICATED_ALLOCATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_DEDICATED_REQUIREMENTS))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
data MemoryDedicatedRequirements = MemoryDedicatedRequirements
  { 
    
    
    
    MemoryDedicatedRequirements -> Bool
prefersDedicatedAllocation :: Bool
  , 
    
    MemoryDedicatedRequirements -> Bool
requiresDedicatedAllocation :: Bool
  }
  deriving (Typeable, MemoryDedicatedRequirements -> MemoryDedicatedRequirements -> Bool
(MemoryDedicatedRequirements
 -> MemoryDedicatedRequirements -> Bool)
-> (MemoryDedicatedRequirements
    -> MemoryDedicatedRequirements -> Bool)
-> Eq MemoryDedicatedRequirements
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryDedicatedRequirements -> MemoryDedicatedRequirements -> Bool
$c/= :: MemoryDedicatedRequirements -> MemoryDedicatedRequirements -> Bool
== :: MemoryDedicatedRequirements -> MemoryDedicatedRequirements -> Bool
$c== :: MemoryDedicatedRequirements -> MemoryDedicatedRequirements -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryDedicatedRequirements)
#endif
deriving instance Show MemoryDedicatedRequirements
instance ToCStruct MemoryDedicatedRequirements where
  withCStruct :: MemoryDedicatedRequirements
-> (Ptr MemoryDedicatedRequirements -> IO b) -> IO b
withCStruct x :: MemoryDedicatedRequirements
x f :: Ptr MemoryDedicatedRequirements -> IO b
f = Int -> Int -> (Ptr MemoryDedicatedRequirements -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr MemoryDedicatedRequirements -> IO b) -> IO b)
-> (Ptr MemoryDedicatedRequirements -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr MemoryDedicatedRequirements
p -> Ptr MemoryDedicatedRequirements
-> MemoryDedicatedRequirements -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryDedicatedRequirements
p MemoryDedicatedRequirements
x (Ptr MemoryDedicatedRequirements -> IO b
f Ptr MemoryDedicatedRequirements
p)
  pokeCStruct :: Ptr MemoryDedicatedRequirements
-> MemoryDedicatedRequirements -> IO b -> IO b
pokeCStruct p :: Ptr MemoryDedicatedRequirements
p MemoryDedicatedRequirements{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryDedicatedRequirements
p Ptr MemoryDedicatedRequirements -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_DEDICATED_REQUIREMENTS)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryDedicatedRequirements
p Ptr MemoryDedicatedRequirements -> 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 MemoryDedicatedRequirements
p Ptr MemoryDedicatedRequirements -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
prefersDedicatedAllocation))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryDedicatedRequirements
p Ptr MemoryDedicatedRequirements -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
requiresDedicatedAllocation))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr MemoryDedicatedRequirements -> IO b -> IO b
pokeZeroCStruct p :: Ptr MemoryDedicatedRequirements
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryDedicatedRequirements
p Ptr MemoryDedicatedRequirements -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_DEDICATED_REQUIREMENTS)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryDedicatedRequirements
p Ptr MemoryDedicatedRequirements -> 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 MemoryDedicatedRequirements
p Ptr MemoryDedicatedRequirements -> 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))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryDedicatedRequirements
p Ptr MemoryDedicatedRequirements -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f
instance FromCStruct MemoryDedicatedRequirements where
  peekCStruct :: Ptr MemoryDedicatedRequirements -> IO MemoryDedicatedRequirements
peekCStruct p :: Ptr MemoryDedicatedRequirements
p = do
    Bool32
prefersDedicatedAllocation <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr MemoryDedicatedRequirements
p Ptr MemoryDedicatedRequirements -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
requiresDedicatedAllocation <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr MemoryDedicatedRequirements
p Ptr MemoryDedicatedRequirements -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    MemoryDedicatedRequirements -> IO MemoryDedicatedRequirements
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryDedicatedRequirements -> IO MemoryDedicatedRequirements)
-> MemoryDedicatedRequirements -> IO MemoryDedicatedRequirements
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> MemoryDedicatedRequirements
MemoryDedicatedRequirements
             (Bool32 -> Bool
bool32ToBool Bool32
prefersDedicatedAllocation) (Bool32 -> Bool
bool32ToBool Bool32
requiresDedicatedAllocation)
instance Storable MemoryDedicatedRequirements where
  sizeOf :: MemoryDedicatedRequirements -> Int
sizeOf ~MemoryDedicatedRequirements
_ = 24
  alignment :: MemoryDedicatedRequirements -> Int
alignment ~MemoryDedicatedRequirements
_ = 8
  peek :: Ptr MemoryDedicatedRequirements -> IO MemoryDedicatedRequirements
peek = Ptr MemoryDedicatedRequirements -> IO MemoryDedicatedRequirements
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr MemoryDedicatedRequirements
-> MemoryDedicatedRequirements -> IO ()
poke ptr :: Ptr MemoryDedicatedRequirements
ptr poked :: MemoryDedicatedRequirements
poked = Ptr MemoryDedicatedRequirements
-> MemoryDedicatedRequirements -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryDedicatedRequirements
ptr MemoryDedicatedRequirements
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryDedicatedRequirements where
  zero :: MemoryDedicatedRequirements
zero = Bool -> Bool -> MemoryDedicatedRequirements
MemoryDedicatedRequirements
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
data MemoryDedicatedAllocateInfo = MemoryDedicatedAllocateInfo
  { 
    
    MemoryDedicatedAllocateInfo -> Image
image :: Image
  , 
    
    MemoryDedicatedAllocateInfo -> Buffer
buffer :: Buffer
  }
  deriving (Typeable, MemoryDedicatedAllocateInfo -> MemoryDedicatedAllocateInfo -> Bool
(MemoryDedicatedAllocateInfo
 -> MemoryDedicatedAllocateInfo -> Bool)
-> (MemoryDedicatedAllocateInfo
    -> MemoryDedicatedAllocateInfo -> Bool)
-> Eq MemoryDedicatedAllocateInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryDedicatedAllocateInfo -> MemoryDedicatedAllocateInfo -> Bool
$c/= :: MemoryDedicatedAllocateInfo -> MemoryDedicatedAllocateInfo -> Bool
== :: MemoryDedicatedAllocateInfo -> MemoryDedicatedAllocateInfo -> Bool
$c== :: MemoryDedicatedAllocateInfo -> MemoryDedicatedAllocateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryDedicatedAllocateInfo)
#endif
deriving instance Show MemoryDedicatedAllocateInfo
instance ToCStruct MemoryDedicatedAllocateInfo where
  withCStruct :: MemoryDedicatedAllocateInfo
-> (Ptr MemoryDedicatedAllocateInfo -> IO b) -> IO b
withCStruct x :: MemoryDedicatedAllocateInfo
x f :: Ptr MemoryDedicatedAllocateInfo -> IO b
f = Int -> Int -> (Ptr MemoryDedicatedAllocateInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr MemoryDedicatedAllocateInfo -> IO b) -> IO b)
-> (Ptr MemoryDedicatedAllocateInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr MemoryDedicatedAllocateInfo
p -> Ptr MemoryDedicatedAllocateInfo
-> MemoryDedicatedAllocateInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryDedicatedAllocateInfo
p MemoryDedicatedAllocateInfo
x (Ptr MemoryDedicatedAllocateInfo -> IO b
f Ptr MemoryDedicatedAllocateInfo
p)
  pokeCStruct :: Ptr MemoryDedicatedAllocateInfo
-> MemoryDedicatedAllocateInfo -> IO b -> IO b
pokeCStruct p :: Ptr MemoryDedicatedAllocateInfo
p MemoryDedicatedAllocateInfo{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryDedicatedAllocateInfo
p Ptr MemoryDedicatedAllocateInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_DEDICATED_ALLOCATE_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryDedicatedAllocateInfo
p Ptr MemoryDedicatedAllocateInfo -> 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 MemoryDedicatedAllocateInfo
p Ptr MemoryDedicatedAllocateInfo -> 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 MemoryDedicatedAllocateInfo
p Ptr MemoryDedicatedAllocateInfo -> 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 MemoryDedicatedAllocateInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr MemoryDedicatedAllocateInfo
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryDedicatedAllocateInfo
p Ptr MemoryDedicatedAllocateInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_DEDICATED_ALLOCATE_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryDedicatedAllocateInfo
p Ptr MemoryDedicatedAllocateInfo -> 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 MemoryDedicatedAllocateInfo where
  peekCStruct :: Ptr MemoryDedicatedAllocateInfo -> IO MemoryDedicatedAllocateInfo
peekCStruct p :: Ptr MemoryDedicatedAllocateInfo
p = do
    Image
image <- Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image ((Ptr MemoryDedicatedAllocateInfo
p Ptr MemoryDedicatedAllocateInfo -> 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 MemoryDedicatedAllocateInfo
p Ptr MemoryDedicatedAllocateInfo -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Buffer))
    MemoryDedicatedAllocateInfo -> IO MemoryDedicatedAllocateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryDedicatedAllocateInfo -> IO MemoryDedicatedAllocateInfo)
-> MemoryDedicatedAllocateInfo -> IO MemoryDedicatedAllocateInfo
forall a b. (a -> b) -> a -> b
$ Image -> Buffer -> MemoryDedicatedAllocateInfo
MemoryDedicatedAllocateInfo
             Image
image Buffer
buffer
instance Storable MemoryDedicatedAllocateInfo where
  sizeOf :: MemoryDedicatedAllocateInfo -> Int
sizeOf ~MemoryDedicatedAllocateInfo
_ = 32
  alignment :: MemoryDedicatedAllocateInfo -> Int
alignment ~MemoryDedicatedAllocateInfo
_ = 8
  peek :: Ptr MemoryDedicatedAllocateInfo -> IO MemoryDedicatedAllocateInfo
peek = Ptr MemoryDedicatedAllocateInfo -> IO MemoryDedicatedAllocateInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr MemoryDedicatedAllocateInfo
-> MemoryDedicatedAllocateInfo -> IO ()
poke ptr :: Ptr MemoryDedicatedAllocateInfo
ptr poked :: MemoryDedicatedAllocateInfo
poked = Ptr MemoryDedicatedAllocateInfo
-> MemoryDedicatedAllocateInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryDedicatedAllocateInfo
ptr MemoryDedicatedAllocateInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryDedicatedAllocateInfo where
  zero :: MemoryDedicatedAllocateInfo
zero = Image -> Buffer -> MemoryDedicatedAllocateInfo
MemoryDedicatedAllocateInfo
           Image
forall a. Zero a => a
zero
           Buffer
forall a. Zero a => a
zero