{-# 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 (allocaBytesAligned)
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
(PhysicalDeviceCoherentMemoryFeaturesAMD
 -> PhysicalDeviceCoherentMemoryFeaturesAMD -> Bool)
-> (PhysicalDeviceCoherentMemoryFeaturesAMD
    -> PhysicalDeviceCoherentMemoryFeaturesAMD -> Bool)
-> Eq PhysicalDeviceCoherentMemoryFeaturesAMD
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 :: PhysicalDeviceCoherentMemoryFeaturesAMD
-> (Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b) -> IO b
withCStruct x :: PhysicalDeviceCoherentMemoryFeaturesAMD
x f :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b) -> IO b)
-> (Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p -> Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b -> IO b
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 :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p PhysicalDeviceCoherentMemoryFeaturesAMD{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COHERENT_MEMORY_FEATURES_AMD)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> 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 PhysicalDeviceCoherentMemoryFeaturesAMD
p Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
deviceCoherentMemory))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COHERENT_MEMORY_FEATURES_AMD)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> 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 PhysicalDeviceCoherentMemoryFeaturesAMD
p Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> 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 PhysicalDeviceCoherentMemoryFeaturesAMD where
  peekCStruct :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> IO PhysicalDeviceCoherentMemoryFeaturesAMD
peekCStruct p :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p = do
    Bool32
deviceCoherentMemory <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
p Ptr PhysicalDeviceCoherentMemoryFeaturesAMD -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    PhysicalDeviceCoherentMemoryFeaturesAMD
-> IO PhysicalDeviceCoherentMemoryFeaturesAMD
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceCoherentMemoryFeaturesAMD
 -> IO PhysicalDeviceCoherentMemoryFeaturesAMD)
-> PhysicalDeviceCoherentMemoryFeaturesAMD
-> IO PhysicalDeviceCoherentMemoryFeaturesAMD
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceCoherentMemoryFeaturesAMD
PhysicalDeviceCoherentMemoryFeaturesAMD
             (Bool32 -> Bool
bool32ToBool Bool32
deviceCoherentMemory)
instance Storable PhysicalDeviceCoherentMemoryFeaturesAMD where
  sizeOf :: PhysicalDeviceCoherentMemoryFeaturesAMD -> Int
sizeOf ~PhysicalDeviceCoherentMemoryFeaturesAMD
_ = 24
  alignment :: PhysicalDeviceCoherentMemoryFeaturesAMD -> Int
alignment ~PhysicalDeviceCoherentMemoryFeaturesAMD
_ = 8
  peek :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> IO PhysicalDeviceCoherentMemoryFeaturesAMD
peek = Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> IO PhysicalDeviceCoherentMemoryFeaturesAMD
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> IO ()
poke ptr :: Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
ptr poked :: PhysicalDeviceCoherentMemoryFeaturesAMD
poked = Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
-> PhysicalDeviceCoherentMemoryFeaturesAMD -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCoherentMemoryFeaturesAMD
ptr PhysicalDeviceCoherentMemoryFeaturesAMD
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceCoherentMemoryFeaturesAMD where
  zero :: PhysicalDeviceCoherentMemoryFeaturesAMD
zero = Bool -> PhysicalDeviceCoherentMemoryFeaturesAMD
PhysicalDeviceCoherentMemoryFeaturesAMD
           Bool
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 :: a
$mAMD_DEVICE_COHERENT_MEMORY_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> 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 :: a
$mAMD_DEVICE_COHERENT_MEMORY_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
AMD_DEVICE_COHERENT_MEMORY_EXTENSION_NAME = "VK_AMD_device_coherent_memory"