{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_memory_priority  ( PhysicalDeviceMemoryPriorityFeaturesEXT(..)
                                                 , MemoryPriorityAllocateInfoEXT(..)
                                                 , EXT_MEMORY_PRIORITY_SPEC_VERSION
                                                 , pattern EXT_MEMORY_PRIORITY_SPEC_VERSION
                                                 , EXT_MEMORY_PRIORITY_EXTENSION_NAME
                                                 , pattern EXT_MEMORY_PRIORITY_EXTENSION_NAME
                                                 ) where
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.Coerce (coerce)
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.C.Types (CFloat)
import Foreign.C.Types (CFloat(..))
import Foreign.C.Types (CFloat(CFloat))
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_MEMORY_PRIORITY_ALLOCATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PRIORITY_FEATURES_EXT))
data PhysicalDeviceMemoryPriorityFeaturesEXT = PhysicalDeviceMemoryPriorityFeaturesEXT
  { 
    
    
    PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
memoryPriority :: Bool }
  deriving (Typeable, PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
$c/= :: PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
== :: PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
$c== :: PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMemoryPriorityFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceMemoryPriorityFeaturesEXT
instance ToCStruct PhysicalDeviceMemoryPriorityFeaturesEXT where
  withCStruct :: forall b.
PhysicalDeviceMemoryPriorityFeaturesEXT
-> (Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceMemoryPriorityFeaturesEXT
x Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p PhysicalDeviceMemoryPriorityFeaturesEXT
x (Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b
f Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p PhysicalDeviceMemoryPriorityFeaturesEXT{Bool
memoryPriority :: Bool
$sel:memoryPriority:PhysicalDeviceMemoryPriorityFeaturesEXT :: PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PRIORITY_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
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 PhysicalDeviceMemoryPriorityFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
memoryPriority))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PRIORITY_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
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 PhysicalDeviceMemoryPriorityFeaturesEXT
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 PhysicalDeviceMemoryPriorityFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> IO PhysicalDeviceMemoryPriorityFeaturesEXT
peekCStruct Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p = do
    Bool32
memoryPriority <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
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 -> PhysicalDeviceMemoryPriorityFeaturesEXT
PhysicalDeviceMemoryPriorityFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
memoryPriority)
instance Storable PhysicalDeviceMemoryPriorityFeaturesEXT where
  sizeOf :: PhysicalDeviceMemoryPriorityFeaturesEXT -> Int
sizeOf ~PhysicalDeviceMemoryPriorityFeaturesEXT
_ = Int
24
  alignment :: PhysicalDeviceMemoryPriorityFeaturesEXT -> Int
alignment ~PhysicalDeviceMemoryPriorityFeaturesEXT
_ = Int
8
  peek :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> IO PhysicalDeviceMemoryPriorityFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
ptr PhysicalDeviceMemoryPriorityFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
ptr PhysicalDeviceMemoryPriorityFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceMemoryPriorityFeaturesEXT where
  zero :: PhysicalDeviceMemoryPriorityFeaturesEXT
zero = Bool -> PhysicalDeviceMemoryPriorityFeaturesEXT
PhysicalDeviceMemoryPriorityFeaturesEXT
           forall a. Zero a => a
zero
data MemoryPriorityAllocateInfoEXT = MemoryPriorityAllocateInfoEXT
  { 
    
    
    
    
    
    
    MemoryPriorityAllocateInfoEXT -> Float
priority :: Float }
  deriving (Typeable, MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> Bool
$c/= :: MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> Bool
== :: MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> Bool
$c== :: MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryPriorityAllocateInfoEXT)
#endif
deriving instance Show MemoryPriorityAllocateInfoEXT
instance ToCStruct MemoryPriorityAllocateInfoEXT where
  withCStruct :: forall b.
MemoryPriorityAllocateInfoEXT
-> (Ptr MemoryPriorityAllocateInfoEXT -> IO b) -> IO b
withCStruct MemoryPriorityAllocateInfoEXT
x Ptr MemoryPriorityAllocateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr MemoryPriorityAllocateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryPriorityAllocateInfoEXT
p MemoryPriorityAllocateInfoEXT
x (Ptr MemoryPriorityAllocateInfoEXT -> IO b
f Ptr MemoryPriorityAllocateInfoEXT
p)
  pokeCStruct :: forall b.
Ptr MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> IO b -> IO b
pokeCStruct Ptr MemoryPriorityAllocateInfoEXT
p MemoryPriorityAllocateInfoEXT{Float
priority :: Float
$sel:priority:MemoryPriorityAllocateInfoEXT :: MemoryPriorityAllocateInfoEXT -> Float
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryPriorityAllocateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_PRIORITY_ALLOCATE_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryPriorityAllocateInfoEXT
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 MemoryPriorityAllocateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
priority))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr MemoryPriorityAllocateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr MemoryPriorityAllocateInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryPriorityAllocateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_PRIORITY_ALLOCATE_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryPriorityAllocateInfoEXT
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 MemoryPriorityAllocateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CFloat)) (Float -> CFloat
CFloat (forall a. Zero a => a
zero))
    IO b
f
instance FromCStruct MemoryPriorityAllocateInfoEXT where
  peekCStruct :: Ptr MemoryPriorityAllocateInfoEXT
-> IO MemoryPriorityAllocateInfoEXT
peekCStruct Ptr MemoryPriorityAllocateInfoEXT
p = do
    CFloat
priority <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr MemoryPriorityAllocateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CFloat))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Float -> MemoryPriorityAllocateInfoEXT
MemoryPriorityAllocateInfoEXT
             (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
priority)
instance Storable MemoryPriorityAllocateInfoEXT where
  sizeOf :: MemoryPriorityAllocateInfoEXT -> Int
sizeOf ~MemoryPriorityAllocateInfoEXT
_ = Int
24
  alignment :: MemoryPriorityAllocateInfoEXT -> Int
alignment ~MemoryPriorityAllocateInfoEXT
_ = Int
8
  peek :: Ptr MemoryPriorityAllocateInfoEXT
-> IO MemoryPriorityAllocateInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> IO ()
poke Ptr MemoryPriorityAllocateInfoEXT
ptr MemoryPriorityAllocateInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryPriorityAllocateInfoEXT
ptr MemoryPriorityAllocateInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryPriorityAllocateInfoEXT where
  zero :: MemoryPriorityAllocateInfoEXT
zero = Float -> MemoryPriorityAllocateInfoEXT
MemoryPriorityAllocateInfoEXT
           forall a. Zero a => a
zero
type EXT_MEMORY_PRIORITY_SPEC_VERSION = 1
pattern EXT_MEMORY_PRIORITY_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_MEMORY_PRIORITY_SPEC_VERSION :: forall a. Integral a => a
$mEXT_MEMORY_PRIORITY_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_MEMORY_PRIORITY_SPEC_VERSION = 1
type EXT_MEMORY_PRIORITY_EXTENSION_NAME = "VK_EXT_memory_priority"
pattern EXT_MEMORY_PRIORITY_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_MEMORY_PRIORITY_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_MEMORY_PRIORITY_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_MEMORY_PRIORITY_EXTENSION_NAME = "VK_EXT_memory_priority"