{-# language CPP #-}
module Vulkan.Extensions.VK_AMD_device_coherent_memory ( PhysicalDeviceCoherentMemoryFeaturesAMD(..)
, AMD_DEVICE_COHERENT_MEMORY_SPEC_VERSION
, pattern AMD_DEVICE_COHERENT_MEMORY_SPEC_VERSION
, AMD_DEVICE_COHERENT_MEMORY_EXTENSION_NAME
, pattern AMD_DEVICE_COHERENT_MEMORY_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_COHERENT_MEMORY_FEATURES_AMD))
data PhysicalDeviceCoherentMemoryFeaturesAMD = PhysicalDeviceCoherentMemoryFeaturesAMD
{
PhysicalDeviceCoherentMemoryFeaturesAMD -> Bool
deviceCoherentMemory :: Bool }
deriving (Typeable, PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> Bool
$c/= :: PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> Bool
== :: PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> Bool
$c== :: PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceCoherentMemoryFeaturesAMD)
#endif
deriving instance Show PhysicalDeviceCoherentMemoryFeaturesAMD
instance ToCStruct PhysicalDeviceCoherentMemoryFeaturesAMD where
withCStruct :: forall b.
PhysicalDeviceCoherentMemoryFeaturesAMD
-> (Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b) -> IO b
withCStruct PhysicalDeviceCoherentMemoryFeaturesAMD
x Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p PhysicalDeviceCoherentMemoryFeaturesAMD
x (Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b
f Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p PhysicalDeviceCoherentMemoryFeaturesAMD{Bool
deviceCoherentMemory :: Bool
$sel:deviceCoherentMemory:PhysicalDeviceCoherentMemoryFeaturesAMD :: PhysicalDeviceCoherentMemoryFeaturesAMD -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COHERENT_MEMORY_FEATURES_AMD)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
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 PhysicalDeviceCoherentMemoryFeaturesAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
deviceCoherentMemory))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COHERENT_MEMORY_FEATURES_AMD)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
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 PhysicalDeviceCoherentMemoryFeaturesAMD
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 PhysicalDeviceCoherentMemoryFeaturesAMD where
peekCStruct :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> IO PhysicalDeviceCoherentMemoryFeaturesAMD
peekCStruct Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p = do
Bool32
deviceCoherentMemory <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
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 -> PhysicalDeviceCoherentMemoryFeaturesAMD
PhysicalDeviceCoherentMemoryFeaturesAMD
(Bool32 -> Bool
bool32ToBool Bool32
deviceCoherentMemory)
instance Storable PhysicalDeviceCoherentMemoryFeaturesAMD where
sizeOf :: PhysicalDeviceCoherentMemoryFeaturesAMD -> Int
sizeOf ~PhysicalDeviceCoherentMemoryFeaturesAMD
_ = Int
24
alignment :: PhysicalDeviceCoherentMemoryFeaturesAMD -> Int
alignment ~PhysicalDeviceCoherentMemoryFeaturesAMD
_ = Int
8
peek :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> IO PhysicalDeviceCoherentMemoryFeaturesAMD
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> IO ()
poke Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
ptr PhysicalDeviceCoherentMemoryFeaturesAMD
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
ptr PhysicalDeviceCoherentMemoryFeaturesAMD
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceCoherentMemoryFeaturesAMD where
zero :: PhysicalDeviceCoherentMemoryFeaturesAMD
zero = Bool -> PhysicalDeviceCoherentMemoryFeaturesAMD
PhysicalDeviceCoherentMemoryFeaturesAMD
forall a. Zero a => a
zero
type AMD_DEVICE_COHERENT_MEMORY_SPEC_VERSION = 1
pattern AMD_DEVICE_COHERENT_MEMORY_SPEC_VERSION :: forall a . Integral a => a
pattern $bAMD_DEVICE_COHERENT_MEMORY_SPEC_VERSION :: forall a. Integral a => a
$mAMD_DEVICE_COHERENT_MEMORY_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
AMD_DEVICE_COHERENT_MEMORY_SPEC_VERSION = 1
type AMD_DEVICE_COHERENT_MEMORY_EXTENSION_NAME = "VK_AMD_device_coherent_memory"
pattern AMD_DEVICE_COHERENT_MEMORY_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bAMD_DEVICE_COHERENT_MEMORY_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mAMD_DEVICE_COHERENT_MEMORY_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
AMD_DEVICE_COHERENT_MEMORY_EXTENSION_NAME = "VK_AMD_device_coherent_memory"