{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_external_memory_acquire_unmodified ( ExternalMemoryAcquireUnmodifiedEXT(..)
, EXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_SPEC_VERSION
, pattern EXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_SPEC_VERSION
, EXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_EXTENSION_NAME
, pattern EXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_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_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_EXT))
data ExternalMemoryAcquireUnmodifiedEXT = ExternalMemoryAcquireUnmodifiedEXT
{
ExternalMemoryAcquireUnmodifiedEXT -> Bool
acquireUnmodifiedMemory :: Bool }
deriving (Typeable, ExternalMemoryAcquireUnmodifiedEXT
-> ExternalMemoryAcquireUnmodifiedEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExternalMemoryAcquireUnmodifiedEXT
-> ExternalMemoryAcquireUnmodifiedEXT -> Bool
$c/= :: ExternalMemoryAcquireUnmodifiedEXT
-> ExternalMemoryAcquireUnmodifiedEXT -> Bool
== :: ExternalMemoryAcquireUnmodifiedEXT
-> ExternalMemoryAcquireUnmodifiedEXT -> Bool
$c== :: ExternalMemoryAcquireUnmodifiedEXT
-> ExternalMemoryAcquireUnmodifiedEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ExternalMemoryAcquireUnmodifiedEXT)
#endif
deriving instance Show ExternalMemoryAcquireUnmodifiedEXT
instance ToCStruct ExternalMemoryAcquireUnmodifiedEXT where
withCStruct :: forall b.
ExternalMemoryAcquireUnmodifiedEXT
-> (Ptr ExternalMemoryAcquireUnmodifiedEXT -> IO b) -> IO b
withCStruct ExternalMemoryAcquireUnmodifiedEXT
x Ptr ExternalMemoryAcquireUnmodifiedEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr ExternalMemoryAcquireUnmodifiedEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExternalMemoryAcquireUnmodifiedEXT
p ExternalMemoryAcquireUnmodifiedEXT
x (Ptr ExternalMemoryAcquireUnmodifiedEXT -> IO b
f Ptr ExternalMemoryAcquireUnmodifiedEXT
p)
pokeCStruct :: forall b.
Ptr ExternalMemoryAcquireUnmodifiedEXT
-> ExternalMemoryAcquireUnmodifiedEXT -> IO b -> IO b
pokeCStruct Ptr ExternalMemoryAcquireUnmodifiedEXT
p ExternalMemoryAcquireUnmodifiedEXT{Bool
acquireUnmodifiedMemory :: Bool
$sel:acquireUnmodifiedMemory:ExternalMemoryAcquireUnmodifiedEXT :: ExternalMemoryAcquireUnmodifiedEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryAcquireUnmodifiedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryAcquireUnmodifiedEXT
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 ExternalMemoryAcquireUnmodifiedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
acquireUnmodifiedMemory))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr ExternalMemoryAcquireUnmodifiedEXT -> IO b -> IO b
pokeZeroCStruct Ptr ExternalMemoryAcquireUnmodifiedEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryAcquireUnmodifiedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryAcquireUnmodifiedEXT
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 ExternalMemoryAcquireUnmodifiedEXT
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 ExternalMemoryAcquireUnmodifiedEXT where
peekCStruct :: Ptr ExternalMemoryAcquireUnmodifiedEXT
-> IO ExternalMemoryAcquireUnmodifiedEXT
peekCStruct Ptr ExternalMemoryAcquireUnmodifiedEXT
p = do
Bool32
acquireUnmodifiedMemory <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr ExternalMemoryAcquireUnmodifiedEXT
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 -> ExternalMemoryAcquireUnmodifiedEXT
ExternalMemoryAcquireUnmodifiedEXT
(Bool32 -> Bool
bool32ToBool Bool32
acquireUnmodifiedMemory)
instance Storable ExternalMemoryAcquireUnmodifiedEXT where
sizeOf :: ExternalMemoryAcquireUnmodifiedEXT -> Int
sizeOf ~ExternalMemoryAcquireUnmodifiedEXT
_ = Int
24
alignment :: ExternalMemoryAcquireUnmodifiedEXT -> Int
alignment ~ExternalMemoryAcquireUnmodifiedEXT
_ = Int
8
peek :: Ptr ExternalMemoryAcquireUnmodifiedEXT
-> IO ExternalMemoryAcquireUnmodifiedEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ExternalMemoryAcquireUnmodifiedEXT
-> ExternalMemoryAcquireUnmodifiedEXT -> IO ()
poke Ptr ExternalMemoryAcquireUnmodifiedEXT
ptr ExternalMemoryAcquireUnmodifiedEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExternalMemoryAcquireUnmodifiedEXT
ptr ExternalMemoryAcquireUnmodifiedEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ExternalMemoryAcquireUnmodifiedEXT where
zero :: ExternalMemoryAcquireUnmodifiedEXT
zero = Bool -> ExternalMemoryAcquireUnmodifiedEXT
ExternalMemoryAcquireUnmodifiedEXT
forall a. Zero a => a
zero
type EXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_SPEC_VERSION = 1
pattern EXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_SPEC_VERSION :: forall a. Integral a => a
$mEXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_SPEC_VERSION = 1
type EXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_EXTENSION_NAME = "VK_EXT_external_memory_acquire_unmodified"
pattern EXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_EXTERNAL_MEMORY_ACQUIRE_UNMODIFIED_EXTENSION_NAME = "VK_EXT_external_memory_acquire_unmodified"