{-# language CPP #-}
module Vulkan.Core10.OtherTypes ( MemoryBarrier(..)
, BufferMemoryBarrier(..)
, ImageMemoryBarrier(..)
, PipelineCacheHeaderVersionOne(..)
, DrawIndirectCommand(..)
, DrawIndexedIndirectCommand(..)
, DispatchIndirectCommand(..)
, BaseOutStructure(..)
, BaseInStructure(..)
, ObjectType(..)
, VendorId(..)
) where
import Vulkan.CStruct.Utils (FixedArray)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.Ptr (castPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.Type.Equality ((:~:)(Refl))
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 Data.Int (Int32)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Word (Word8)
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.CStruct.Utils (peekByteStringFromSizedVectorPtr)
import Vulkan.CStruct.Utils (pokeFixedLengthByteString)
import Vulkan.Core10.Enums.AccessFlagBits (AccessFlags)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout)
import Vulkan.Core10.ImageView (ImageSubresourceRange)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Enums.PipelineCacheHeaderVersion (PipelineCacheHeaderVersion)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_sample_locations (SampleLocationsInfoEXT)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.APIConstants (UUID_SIZE)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BUFFER_MEMORY_BARRIER))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_BARRIER))
import Vulkan.CStruct.Extends (BaseInStructure(..))
import Vulkan.CStruct.Extends (BaseOutStructure(..))
import Vulkan.Core10.Enums.ObjectType (ObjectType(..))
import Vulkan.Core10.Enums.VendorId (VendorId(..))
data MemoryBarrier = MemoryBarrier
{
MemoryBarrier -> AccessFlags
srcAccessMask :: AccessFlags
,
MemoryBarrier -> AccessFlags
dstAccessMask :: AccessFlags
}
deriving (Typeable, MemoryBarrier -> MemoryBarrier -> Bool
(MemoryBarrier -> MemoryBarrier -> Bool)
-> (MemoryBarrier -> MemoryBarrier -> Bool) -> Eq MemoryBarrier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryBarrier -> MemoryBarrier -> Bool
$c/= :: MemoryBarrier -> MemoryBarrier -> Bool
== :: MemoryBarrier -> MemoryBarrier -> Bool
$c== :: MemoryBarrier -> MemoryBarrier -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryBarrier)
#endif
deriving instance Show MemoryBarrier
instance ToCStruct MemoryBarrier where
withCStruct :: MemoryBarrier -> (Ptr MemoryBarrier -> IO b) -> IO b
withCStruct MemoryBarrier
x Ptr MemoryBarrier -> IO b
f = Int -> (Ptr MemoryBarrier -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr MemoryBarrier -> IO b) -> IO b)
-> (Ptr MemoryBarrier -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr MemoryBarrier
p -> Ptr MemoryBarrier -> MemoryBarrier -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryBarrier
p MemoryBarrier
x (Ptr MemoryBarrier -> IO b
f Ptr MemoryBarrier
p)
pokeCStruct :: Ptr MemoryBarrier -> MemoryBarrier -> IO b -> IO b
pokeCStruct Ptr MemoryBarrier
p MemoryBarrier{AccessFlags
dstAccessMask :: AccessFlags
srcAccessMask :: AccessFlags
$sel:dstAccessMask:MemoryBarrier :: MemoryBarrier -> AccessFlags
$sel:srcAccessMask:MemoryBarrier :: MemoryBarrier -> AccessFlags
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_BARRIER)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr AccessFlags)) (AccessFlags
srcAccessMask)
Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr AccessFlags)) (AccessFlags
dstAccessMask)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: Ptr MemoryBarrier -> IO b -> IO b
pokeZeroCStruct Ptr MemoryBarrier
p IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_BARRIER)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct MemoryBarrier where
peekCStruct :: Ptr MemoryBarrier -> IO MemoryBarrier
peekCStruct Ptr MemoryBarrier
p = do
AccessFlags
srcAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr AccessFlags))
AccessFlags
dstAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr MemoryBarrier
p Ptr MemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr AccessFlags))
MemoryBarrier -> IO MemoryBarrier
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryBarrier -> IO MemoryBarrier)
-> MemoryBarrier -> IO MemoryBarrier
forall a b. (a -> b) -> a -> b
$ AccessFlags -> AccessFlags -> MemoryBarrier
MemoryBarrier
AccessFlags
srcAccessMask AccessFlags
dstAccessMask
instance Storable MemoryBarrier where
sizeOf :: MemoryBarrier -> Int
sizeOf ~MemoryBarrier
_ = Int
24
alignment :: MemoryBarrier -> Int
alignment ~MemoryBarrier
_ = Int
8
peek :: Ptr MemoryBarrier -> IO MemoryBarrier
peek = Ptr MemoryBarrier -> IO MemoryBarrier
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr MemoryBarrier -> MemoryBarrier -> IO ()
poke Ptr MemoryBarrier
ptr MemoryBarrier
poked = Ptr MemoryBarrier -> MemoryBarrier -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryBarrier
ptr MemoryBarrier
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryBarrier where
zero :: MemoryBarrier
zero = AccessFlags -> AccessFlags -> MemoryBarrier
MemoryBarrier
AccessFlags
forall a. Zero a => a
zero
AccessFlags
forall a. Zero a => a
zero
data BufferMemoryBarrier = BufferMemoryBarrier
{
BufferMemoryBarrier -> AccessFlags
srcAccessMask :: AccessFlags
,
BufferMemoryBarrier -> AccessFlags
dstAccessMask :: AccessFlags
,
BufferMemoryBarrier -> Word32
srcQueueFamilyIndex :: Word32
,
BufferMemoryBarrier -> Word32
dstQueueFamilyIndex :: Word32
,
BufferMemoryBarrier -> Buffer
buffer :: Buffer
,
BufferMemoryBarrier -> DeviceSize
offset :: DeviceSize
,
BufferMemoryBarrier -> DeviceSize
size :: DeviceSize
}
deriving (Typeable, BufferMemoryBarrier -> BufferMemoryBarrier -> Bool
(BufferMemoryBarrier -> BufferMemoryBarrier -> Bool)
-> (BufferMemoryBarrier -> BufferMemoryBarrier -> Bool)
-> Eq BufferMemoryBarrier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufferMemoryBarrier -> BufferMemoryBarrier -> Bool
$c/= :: BufferMemoryBarrier -> BufferMemoryBarrier -> Bool
== :: BufferMemoryBarrier -> BufferMemoryBarrier -> Bool
$c== :: BufferMemoryBarrier -> BufferMemoryBarrier -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BufferMemoryBarrier)
#endif
deriving instance Show BufferMemoryBarrier
instance ToCStruct BufferMemoryBarrier where
withCStruct :: BufferMemoryBarrier -> (Ptr BufferMemoryBarrier -> IO b) -> IO b
withCStruct BufferMemoryBarrier
x Ptr BufferMemoryBarrier -> IO b
f = Int -> (Ptr BufferMemoryBarrier -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
56 ((Ptr BufferMemoryBarrier -> IO b) -> IO b)
-> (Ptr BufferMemoryBarrier -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr BufferMemoryBarrier
p -> Ptr BufferMemoryBarrier -> BufferMemoryBarrier -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr BufferMemoryBarrier
p BufferMemoryBarrier
x (Ptr BufferMemoryBarrier -> IO b
f Ptr BufferMemoryBarrier
p)
pokeCStruct :: Ptr BufferMemoryBarrier -> BufferMemoryBarrier -> IO b -> IO b
pokeCStruct Ptr BufferMemoryBarrier
p BufferMemoryBarrier{Word32
DeviceSize
Buffer
AccessFlags
size :: DeviceSize
offset :: DeviceSize
buffer :: Buffer
dstQueueFamilyIndex :: Word32
srcQueueFamilyIndex :: Word32
dstAccessMask :: AccessFlags
srcAccessMask :: AccessFlags
$sel:size:BufferMemoryBarrier :: BufferMemoryBarrier -> DeviceSize
$sel:offset:BufferMemoryBarrier :: BufferMemoryBarrier -> DeviceSize
$sel:buffer:BufferMemoryBarrier :: BufferMemoryBarrier -> Buffer
$sel:dstQueueFamilyIndex:BufferMemoryBarrier :: BufferMemoryBarrier -> Word32
$sel:srcQueueFamilyIndex:BufferMemoryBarrier :: BufferMemoryBarrier -> Word32
$sel:dstAccessMask:BufferMemoryBarrier :: BufferMemoryBarrier -> AccessFlags
$sel:srcAccessMask:BufferMemoryBarrier :: BufferMemoryBarrier -> AccessFlags
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_MEMORY_BARRIER)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr AccessFlags)) (AccessFlags
srcAccessMask)
Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr AccessFlags)) (AccessFlags
dstAccessMask)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (Word32
srcQueueFamilyIndex)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32)) (Word32
dstQueueFamilyIndex)
Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Buffer)) (Buffer
buffer)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize)) (DeviceSize
offset)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr DeviceSize)) (DeviceSize
size)
IO b
f
cStructSize :: Int
cStructSize = Int
56
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: Ptr BufferMemoryBarrier -> IO b -> IO b
pokeZeroCStruct Ptr BufferMemoryBarrier
p IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_MEMORY_BARRIER)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr AccessFlags)) (AccessFlags
forall a. Zero a => a
zero)
Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr AccessFlags)) (AccessFlags
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Buffer)) (Buffer
forall a. Zero a => a
zero)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct BufferMemoryBarrier where
peekCStruct :: Ptr BufferMemoryBarrier -> IO BufferMemoryBarrier
peekCStruct Ptr BufferMemoryBarrier
p = do
AccessFlags
srcAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr AccessFlags))
AccessFlags
dstAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr AccessFlags))
Word32
srcQueueFamilyIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
Word32
dstQueueFamilyIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32))
Buffer
buffer <- Ptr Buffer -> IO Buffer
forall a. Storable a => Ptr a -> IO a
peek @Buffer ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Buffer))
DeviceSize
offset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize))
DeviceSize
size <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr BufferMemoryBarrier
p Ptr BufferMemoryBarrier -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr DeviceSize))
BufferMemoryBarrier -> IO BufferMemoryBarrier
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BufferMemoryBarrier -> IO BufferMemoryBarrier)
-> BufferMemoryBarrier -> IO BufferMemoryBarrier
forall a b. (a -> b) -> a -> b
$ AccessFlags
-> AccessFlags
-> Word32
-> Word32
-> Buffer
-> DeviceSize
-> DeviceSize
-> BufferMemoryBarrier
BufferMemoryBarrier
AccessFlags
srcAccessMask AccessFlags
dstAccessMask Word32
srcQueueFamilyIndex Word32
dstQueueFamilyIndex Buffer
buffer DeviceSize
offset DeviceSize
size
instance Storable BufferMemoryBarrier where
sizeOf :: BufferMemoryBarrier -> Int
sizeOf ~BufferMemoryBarrier
_ = Int
56
alignment :: BufferMemoryBarrier -> Int
alignment ~BufferMemoryBarrier
_ = Int
8
peek :: Ptr BufferMemoryBarrier -> IO BufferMemoryBarrier
peek = Ptr BufferMemoryBarrier -> IO BufferMemoryBarrier
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr BufferMemoryBarrier -> BufferMemoryBarrier -> IO ()
poke Ptr BufferMemoryBarrier
ptr BufferMemoryBarrier
poked = Ptr BufferMemoryBarrier -> BufferMemoryBarrier -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr BufferMemoryBarrier
ptr BufferMemoryBarrier
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero BufferMemoryBarrier where
zero :: BufferMemoryBarrier
zero = AccessFlags
-> AccessFlags
-> Word32
-> Word32
-> Buffer
-> DeviceSize
-> DeviceSize
-> BufferMemoryBarrier
BufferMemoryBarrier
AccessFlags
forall a. Zero a => a
zero
AccessFlags
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Buffer
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
data ImageMemoryBarrier (es :: [Type]) = ImageMemoryBarrier
{
ImageMemoryBarrier es -> Chain es
next :: Chain es
,
ImageMemoryBarrier es -> AccessFlags
srcAccessMask :: AccessFlags
,
ImageMemoryBarrier es -> AccessFlags
dstAccessMask :: AccessFlags
,
ImageMemoryBarrier es -> ImageLayout
oldLayout :: ImageLayout
,
ImageMemoryBarrier es -> ImageLayout
newLayout :: ImageLayout
,
ImageMemoryBarrier es -> Word32
srcQueueFamilyIndex :: Word32
,
ImageMemoryBarrier es -> Word32
dstQueueFamilyIndex :: Word32
,
ImageMemoryBarrier es -> Image
image :: Image
,
ImageMemoryBarrier es -> ImageSubresourceRange
subresourceRange :: ImageSubresourceRange
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageMemoryBarrier (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (ImageMemoryBarrier es)
instance Extensible ImageMemoryBarrier where
extensibleTypeName :: String
extensibleTypeName = String
"ImageMemoryBarrier"
setNext :: ImageMemoryBarrier ds -> Chain es -> ImageMemoryBarrier es
setNext ImageMemoryBarrier ds
x Chain es
next = ImageMemoryBarrier ds
x{$sel:next:ImageMemoryBarrier :: Chain es
next = Chain es
next}
getNext :: ImageMemoryBarrier es -> Chain es
getNext ImageMemoryBarrier{Word32
Chain es
ImageLayout
Image
ImageSubresourceRange
AccessFlags
subresourceRange :: ImageSubresourceRange
image :: Image
dstQueueFamilyIndex :: Word32
srcQueueFamilyIndex :: Word32
newLayout :: ImageLayout
oldLayout :: ImageLayout
dstAccessMask :: AccessFlags
srcAccessMask :: AccessFlags
next :: Chain es
$sel:subresourceRange:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> ImageSubresourceRange
$sel:image:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> Image
$sel:dstQueueFamilyIndex:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> Word32
$sel:srcQueueFamilyIndex:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> Word32
$sel:newLayout:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> ImageLayout
$sel:oldLayout:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> ImageLayout
$sel:dstAccessMask:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> AccessFlags
$sel:srcAccessMask:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> AccessFlags
$sel:next:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> Chain es
..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends ImageMemoryBarrier e => b) -> Maybe b
extends :: proxy e -> (Extends ImageMemoryBarrier e => b) -> Maybe b
extends proxy e
_ Extends ImageMemoryBarrier e => b
f
| Just e :~: SampleLocationsInfoEXT
Refl <- (Typeable e, Typeable SampleLocationsInfoEXT) =>
Maybe (e :~: SampleLocationsInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SampleLocationsInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageMemoryBarrier e => b
f
| Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss ImageMemoryBarrier es, PokeChain es) => ToCStruct (ImageMemoryBarrier es) where
withCStruct :: ImageMemoryBarrier es
-> (Ptr (ImageMemoryBarrier es) -> IO b) -> IO b
withCStruct ImageMemoryBarrier es
x Ptr (ImageMemoryBarrier es) -> IO b
f = Int -> (Ptr (ImageMemoryBarrier es) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
72 ((Ptr (ImageMemoryBarrier es) -> IO b) -> IO b)
-> (Ptr (ImageMemoryBarrier es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr (ImageMemoryBarrier es)
p -> Ptr (ImageMemoryBarrier es)
-> ImageMemoryBarrier es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (ImageMemoryBarrier es)
p ImageMemoryBarrier es
x (Ptr (ImageMemoryBarrier es) -> IO b
f Ptr (ImageMemoryBarrier es)
p)
pokeCStruct :: Ptr (ImageMemoryBarrier es)
-> ImageMemoryBarrier es -> IO b -> IO b
pokeCStruct Ptr (ImageMemoryBarrier es)
p ImageMemoryBarrier{Word32
Chain es
ImageLayout
Image
ImageSubresourceRange
AccessFlags
subresourceRange :: ImageSubresourceRange
image :: Image
dstQueueFamilyIndex :: Word32
srcQueueFamilyIndex :: Word32
newLayout :: ImageLayout
oldLayout :: ImageLayout
dstAccessMask :: AccessFlags
srcAccessMask :: AccessFlags
next :: Chain es
$sel:subresourceRange:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> ImageSubresourceRange
$sel:image:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> Image
$sel:dstQueueFamilyIndex:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> Word32
$sel:srcQueueFamilyIndex:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> Word32
$sel:newLayout:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> ImageLayout
$sel:oldLayout:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> ImageLayout
$sel:dstAccessMask:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> AccessFlags
$sel:srcAccessMask:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> AccessFlags
$sel:next:ImageMemoryBarrier :: forall (es :: [*]). ImageMemoryBarrier es -> Chain es
..} IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER)
Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext''
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr AccessFlags)) (AccessFlags
srcAccessMask)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr AccessFlags)) (AccessFlags
dstAccessMask)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ImageLayout)) (ImageLayout
oldLayout)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ImageLayout)) (ImageLayout
newLayout)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32)) (Word32
srcQueueFamilyIndex)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32)) (Word32
dstQueueFamilyIndex)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Image)) (Image
image)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageSubresourceRange -> ImageSubresourceRange -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr ImageSubresourceRange)) (ImageSubresourceRange
subresourceRange)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
72
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: Ptr (ImageMemoryBarrier es) -> IO b -> IO b
pokeZeroCStruct Ptr (ImageMemoryBarrier es)
p IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER)
Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext'
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr AccessFlags)) (AccessFlags
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr AccessFlags)) (AccessFlags
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ImageLayout)) (ImageLayout
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ImageLayout)) (ImageLayout
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Image)) (Image
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageSubresourceRange -> ImageSubresourceRange -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr ImageSubresourceRange)) (ImageSubresourceRange
forall a. Zero a => a
zero)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance (Extendss ImageMemoryBarrier es, PeekChain es) => FromCStruct (ImageMemoryBarrier es) where
peekCStruct :: Ptr (ImageMemoryBarrier es) -> IO (ImageMemoryBarrier es)
peekCStruct Ptr (ImageMemoryBarrier es)
p = do
Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ())))
Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
AccessFlags
srcAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr AccessFlags))
AccessFlags
dstAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr AccessFlags))
ImageLayout
oldLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ImageLayout))
ImageLayout
newLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ImageLayout))
Word32
srcQueueFamilyIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32))
Word32
dstQueueFamilyIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32))
Image
image <- Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Image))
ImageSubresourceRange
subresourceRange <- Ptr ImageSubresourceRange -> IO ImageSubresourceRange
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageSubresourceRange ((Ptr (ImageMemoryBarrier es)
p Ptr (ImageMemoryBarrier es) -> Int -> Ptr ImageSubresourceRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr ImageSubresourceRange))
ImageMemoryBarrier es -> IO (ImageMemoryBarrier es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageMemoryBarrier es -> IO (ImageMemoryBarrier es))
-> ImageMemoryBarrier es -> IO (ImageMemoryBarrier es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> AccessFlags
-> AccessFlags
-> ImageLayout
-> ImageLayout
-> Word32
-> Word32
-> Image
-> ImageSubresourceRange
-> ImageMemoryBarrier es
forall (es :: [*]).
Chain es
-> AccessFlags
-> AccessFlags
-> ImageLayout
-> ImageLayout
-> Word32
-> Word32
-> Image
-> ImageSubresourceRange
-> ImageMemoryBarrier es
ImageMemoryBarrier
Chain es
next AccessFlags
srcAccessMask AccessFlags
dstAccessMask ImageLayout
oldLayout ImageLayout
newLayout Word32
srcQueueFamilyIndex Word32
dstQueueFamilyIndex Image
image ImageSubresourceRange
subresourceRange
instance es ~ '[] => Zero (ImageMemoryBarrier es) where
zero :: ImageMemoryBarrier es
zero = Chain es
-> AccessFlags
-> AccessFlags
-> ImageLayout
-> ImageLayout
-> Word32
-> Word32
-> Image
-> ImageSubresourceRange
-> ImageMemoryBarrier es
forall (es :: [*]).
Chain es
-> AccessFlags
-> AccessFlags
-> ImageLayout
-> ImageLayout
-> Word32
-> Word32
-> Image
-> ImageSubresourceRange
-> ImageMemoryBarrier es
ImageMemoryBarrier
()
AccessFlags
forall a. Zero a => a
zero
AccessFlags
forall a. Zero a => a
zero
ImageLayout
forall a. Zero a => a
zero
ImageLayout
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Image
forall a. Zero a => a
zero
ImageSubresourceRange
forall a. Zero a => a
zero
data =
{
:: Word32
,
:: PipelineCacheHeaderVersion
,
:: Word32
,
:: Word32
,
:: ByteString
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineCacheHeaderVersionOne)
#endif
deriving instance Show PipelineCacheHeaderVersionOne
instance ToCStruct PipelineCacheHeaderVersionOne where
withCStruct :: PipelineCacheHeaderVersionOne
-> (Ptr PipelineCacheHeaderVersionOne -> IO b) -> IO b
withCStruct PipelineCacheHeaderVersionOne
x Ptr PipelineCacheHeaderVersionOne -> IO b
f = Int -> (Ptr PipelineCacheHeaderVersionOne -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PipelineCacheHeaderVersionOne -> IO b) -> IO b)
-> (Ptr PipelineCacheHeaderVersionOne -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PipelineCacheHeaderVersionOne
p -> Ptr PipelineCacheHeaderVersionOne
-> PipelineCacheHeaderVersionOne -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineCacheHeaderVersionOne
p PipelineCacheHeaderVersionOne
x (Ptr PipelineCacheHeaderVersionOne -> IO b
f Ptr PipelineCacheHeaderVersionOne
p)
pokeCStruct :: Ptr PipelineCacheHeaderVersionOne
-> PipelineCacheHeaderVersionOne -> IO b -> IO b
pokeCStruct Ptr PipelineCacheHeaderVersionOne
p PipelineCacheHeaderVersionOne{Word32
ByteString
PipelineCacheHeaderVersion
pipelineCacheUUID :: ByteString
deviceID :: Word32
vendorID :: Word32
headerVersion :: PipelineCacheHeaderVersion
headerSize :: Word32
$sel:pipelineCacheUUID:PipelineCacheHeaderVersionOne :: PipelineCacheHeaderVersionOne -> ByteString
$sel:deviceID:PipelineCacheHeaderVersionOne :: PipelineCacheHeaderVersionOne -> Word32
$sel:vendorID:PipelineCacheHeaderVersionOne :: PipelineCacheHeaderVersionOne -> Word32
$sel:headerVersion:PipelineCacheHeaderVersionOne :: PipelineCacheHeaderVersionOne -> PipelineCacheHeaderVersion
$sel:headerSize:PipelineCacheHeaderVersionOne :: PipelineCacheHeaderVersionOne -> Word32
..} IO b
f = do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
headerSize)
Ptr PipelineCacheHeaderVersion
-> PipelineCacheHeaderVersion -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne
-> Int -> Ptr PipelineCacheHeaderVersion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr PipelineCacheHeaderVersion)) (PipelineCacheHeaderVersion
headerVersion)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Word32
vendorID)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Word32)) (Word32
deviceID)
Ptr (FixedArray UUID_SIZE Word8) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (FixedArray UUID_SIZE Word8))) (ByteString
pipelineCacheUUID)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
4
pokeZeroCStruct :: Ptr PipelineCacheHeaderVersionOne -> IO b -> IO b
pokeZeroCStruct Ptr PipelineCacheHeaderVersionOne
p IO b
f = do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr PipelineCacheHeaderVersion
-> PipelineCacheHeaderVersion -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne
-> Int -> Ptr PipelineCacheHeaderVersion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr PipelineCacheHeaderVersion)) (PipelineCacheHeaderVersion
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr (FixedArray UUID_SIZE Word8) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (FixedArray UUID_SIZE Word8))) (ByteString
forall a. Monoid a => a
mempty)
IO b
f
instance FromCStruct PipelineCacheHeaderVersionOne where
peekCStruct :: Ptr PipelineCacheHeaderVersionOne
-> IO PipelineCacheHeaderVersionOne
peekCStruct Ptr PipelineCacheHeaderVersionOne
p = do
Word32
headerSize <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32))
PipelineCacheHeaderVersion
headerVersion <- Ptr PipelineCacheHeaderVersion -> IO PipelineCacheHeaderVersion
forall a. Storable a => Ptr a -> IO a
peek @PipelineCacheHeaderVersion ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne
-> Int -> Ptr PipelineCacheHeaderVersion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr PipelineCacheHeaderVersion))
Word32
vendorID <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32))
Word32
deviceID <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Word32))
ByteString
pipelineCacheUUID <- Ptr (FixedArray UUID_SIZE Word8) -> IO ByteString
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> IO ByteString
peekByteStringFromSizedVectorPtr ((Ptr PipelineCacheHeaderVersionOne
p Ptr PipelineCacheHeaderVersionOne
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (FixedArray UUID_SIZE Word8)))
PipelineCacheHeaderVersionOne -> IO PipelineCacheHeaderVersionOne
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineCacheHeaderVersionOne -> IO PipelineCacheHeaderVersionOne)
-> PipelineCacheHeaderVersionOne
-> IO PipelineCacheHeaderVersionOne
forall a b. (a -> b) -> a -> b
$ Word32
-> PipelineCacheHeaderVersion
-> Word32
-> Word32
-> ByteString
-> PipelineCacheHeaderVersionOne
PipelineCacheHeaderVersionOne
Word32
headerSize PipelineCacheHeaderVersion
headerVersion Word32
vendorID Word32
deviceID ByteString
pipelineCacheUUID
instance Storable PipelineCacheHeaderVersionOne where
sizeOf :: PipelineCacheHeaderVersionOne -> Int
sizeOf ~PipelineCacheHeaderVersionOne
_ = Int
32
alignment :: PipelineCacheHeaderVersionOne -> Int
alignment ~PipelineCacheHeaderVersionOne
_ = Int
4
peek :: Ptr PipelineCacheHeaderVersionOne
-> IO PipelineCacheHeaderVersionOne
peek = Ptr PipelineCacheHeaderVersionOne
-> IO PipelineCacheHeaderVersionOne
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PipelineCacheHeaderVersionOne
-> PipelineCacheHeaderVersionOne -> IO ()
poke Ptr PipelineCacheHeaderVersionOne
ptr PipelineCacheHeaderVersionOne
poked = Ptr PipelineCacheHeaderVersionOne
-> PipelineCacheHeaderVersionOne -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineCacheHeaderVersionOne
ptr PipelineCacheHeaderVersionOne
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PipelineCacheHeaderVersionOne where
zero :: PipelineCacheHeaderVersionOne
zero = Word32
-> PipelineCacheHeaderVersion
-> Word32
-> Word32
-> ByteString
-> PipelineCacheHeaderVersionOne
PipelineCacheHeaderVersionOne
Word32
forall a. Zero a => a
zero
PipelineCacheHeaderVersion
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
ByteString
forall a. Monoid a => a
mempty
data DrawIndirectCommand = DrawIndirectCommand
{
DrawIndirectCommand -> Word32
vertexCount :: Word32
,
DrawIndirectCommand -> Word32
instanceCount :: Word32
,
DrawIndirectCommand -> Word32
firstVertex :: Word32
,
DrawIndirectCommand -> Word32
firstInstance :: Word32
}
deriving (Typeable, DrawIndirectCommand -> DrawIndirectCommand -> Bool
(DrawIndirectCommand -> DrawIndirectCommand -> Bool)
-> (DrawIndirectCommand -> DrawIndirectCommand -> Bool)
-> Eq DrawIndirectCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrawIndirectCommand -> DrawIndirectCommand -> Bool
$c/= :: DrawIndirectCommand -> DrawIndirectCommand -> Bool
== :: DrawIndirectCommand -> DrawIndirectCommand -> Bool
$c== :: DrawIndirectCommand -> DrawIndirectCommand -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DrawIndirectCommand)
#endif
deriving instance Show DrawIndirectCommand
instance ToCStruct DrawIndirectCommand where
withCStruct :: DrawIndirectCommand -> (Ptr DrawIndirectCommand -> IO b) -> IO b
withCStruct DrawIndirectCommand
x Ptr DrawIndirectCommand -> IO b
f = Int -> (Ptr DrawIndirectCommand -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
16 ((Ptr DrawIndirectCommand -> IO b) -> IO b)
-> (Ptr DrawIndirectCommand -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr DrawIndirectCommand
p -> Ptr DrawIndirectCommand -> DrawIndirectCommand -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrawIndirectCommand
p DrawIndirectCommand
x (Ptr DrawIndirectCommand -> IO b
f Ptr DrawIndirectCommand
p)
pokeCStruct :: Ptr DrawIndirectCommand -> DrawIndirectCommand -> IO b -> IO b
pokeCStruct Ptr DrawIndirectCommand
p DrawIndirectCommand{Word32
firstInstance :: Word32
firstVertex :: Word32
instanceCount :: Word32
vertexCount :: Word32
$sel:firstInstance:DrawIndirectCommand :: DrawIndirectCommand -> Word32
$sel:firstVertex:DrawIndirectCommand :: DrawIndirectCommand -> Word32
$sel:instanceCount:DrawIndirectCommand :: DrawIndirectCommand -> Word32
$sel:vertexCount:DrawIndirectCommand :: DrawIndirectCommand -> Word32
..} IO b
f = do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
vertexCount)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Word32
instanceCount)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Word32
firstVertex)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Word32)) (Word32
firstInstance)
IO b
f
cStructSize :: Int
cStructSize = Int
16
cStructAlignment :: Int
cStructAlignment = Int
4
pokeZeroCStruct :: Ptr DrawIndirectCommand -> IO b -> IO b
pokeZeroCStruct Ptr DrawIndirectCommand
p IO b
f = do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DrawIndirectCommand where
peekCStruct :: Ptr DrawIndirectCommand -> IO DrawIndirectCommand
peekCStruct Ptr DrawIndirectCommand
p = do
Word32
vertexCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32))
Word32
instanceCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32))
Word32
firstVertex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32))
Word32
firstInstance <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndirectCommand
p Ptr DrawIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Word32))
DrawIndirectCommand -> IO DrawIndirectCommand
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DrawIndirectCommand -> IO DrawIndirectCommand)
-> DrawIndirectCommand -> IO DrawIndirectCommand
forall a b. (a -> b) -> a -> b
$ Word32 -> Word32 -> Word32 -> Word32 -> DrawIndirectCommand
DrawIndirectCommand
Word32
vertexCount Word32
instanceCount Word32
firstVertex Word32
firstInstance
instance Storable DrawIndirectCommand where
sizeOf :: DrawIndirectCommand -> Int
sizeOf ~DrawIndirectCommand
_ = Int
16
alignment :: DrawIndirectCommand -> Int
alignment ~DrawIndirectCommand
_ = Int
4
peek :: Ptr DrawIndirectCommand -> IO DrawIndirectCommand
peek = Ptr DrawIndirectCommand -> IO DrawIndirectCommand
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DrawIndirectCommand -> DrawIndirectCommand -> IO ()
poke Ptr DrawIndirectCommand
ptr DrawIndirectCommand
poked = Ptr DrawIndirectCommand -> DrawIndirectCommand -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrawIndirectCommand
ptr DrawIndirectCommand
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DrawIndirectCommand where
zero :: DrawIndirectCommand
zero = Word32 -> Word32 -> Word32 -> Word32 -> DrawIndirectCommand
DrawIndirectCommand
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
data DrawIndexedIndirectCommand = DrawIndexedIndirectCommand
{
DrawIndexedIndirectCommand -> Word32
indexCount :: Word32
,
DrawIndexedIndirectCommand -> Word32
instanceCount :: Word32
,
DrawIndexedIndirectCommand -> Word32
firstIndex :: Word32
,
DrawIndexedIndirectCommand -> Int32
vertexOffset :: Int32
,
DrawIndexedIndirectCommand -> Word32
firstInstance :: Word32
}
deriving (Typeable, DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool
(DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool)
-> (DrawIndexedIndirectCommand
-> DrawIndexedIndirectCommand -> Bool)
-> Eq DrawIndexedIndirectCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool
$c/= :: DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool
== :: DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool
$c== :: DrawIndexedIndirectCommand -> DrawIndexedIndirectCommand -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DrawIndexedIndirectCommand)
#endif
deriving instance Show DrawIndexedIndirectCommand
instance ToCStruct DrawIndexedIndirectCommand where
withCStruct :: DrawIndexedIndirectCommand
-> (Ptr DrawIndexedIndirectCommand -> IO b) -> IO b
withCStruct DrawIndexedIndirectCommand
x Ptr DrawIndexedIndirectCommand -> IO b
f = Int -> (Ptr DrawIndexedIndirectCommand -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
20 ((Ptr DrawIndexedIndirectCommand -> IO b) -> IO b)
-> (Ptr DrawIndexedIndirectCommand -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr DrawIndexedIndirectCommand
p -> Ptr DrawIndexedIndirectCommand
-> DrawIndexedIndirectCommand -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrawIndexedIndirectCommand
p DrawIndexedIndirectCommand
x (Ptr DrawIndexedIndirectCommand -> IO b
f Ptr DrawIndexedIndirectCommand
p)
pokeCStruct :: Ptr DrawIndexedIndirectCommand
-> DrawIndexedIndirectCommand -> IO b -> IO b
pokeCStruct Ptr DrawIndexedIndirectCommand
p DrawIndexedIndirectCommand{Int32
Word32
firstInstance :: Word32
vertexOffset :: Int32
firstIndex :: Word32
instanceCount :: Word32
indexCount :: Word32
$sel:firstInstance:DrawIndexedIndirectCommand :: DrawIndexedIndirectCommand -> Word32
$sel:vertexOffset:DrawIndexedIndirectCommand :: DrawIndexedIndirectCommand -> Int32
$sel:firstIndex:DrawIndexedIndirectCommand :: DrawIndexedIndirectCommand -> Word32
$sel:instanceCount:DrawIndexedIndirectCommand :: DrawIndexedIndirectCommand -> Word32
$sel:indexCount:DrawIndexedIndirectCommand :: DrawIndexedIndirectCommand -> Word32
..} IO b
f = do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
indexCount)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Word32
instanceCount)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Word32
firstIndex)
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Int32)) (Int32
vertexOffset)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
firstInstance)
IO b
f
cStructSize :: Int
cStructSize = Int
20
cStructAlignment :: Int
cStructAlignment = Int
4
pokeZeroCStruct :: Ptr DrawIndexedIndirectCommand -> IO b -> IO b
pokeZeroCStruct Ptr DrawIndexedIndirectCommand
p IO b
f = do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DrawIndexedIndirectCommand where
peekCStruct :: Ptr DrawIndexedIndirectCommand -> IO DrawIndexedIndirectCommand
peekCStruct Ptr DrawIndexedIndirectCommand
p = do
Word32
indexCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32))
Word32
instanceCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32))
Word32
firstIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32))
Int32
vertexOffset <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr Int32))
Word32
firstInstance <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawIndexedIndirectCommand
p Ptr DrawIndexedIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
DrawIndexedIndirectCommand -> IO DrawIndexedIndirectCommand
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DrawIndexedIndirectCommand -> IO DrawIndexedIndirectCommand)
-> DrawIndexedIndirectCommand -> IO DrawIndexedIndirectCommand
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> Word32
-> Int32
-> Word32
-> DrawIndexedIndirectCommand
DrawIndexedIndirectCommand
Word32
indexCount Word32
instanceCount Word32
firstIndex Int32
vertexOffset Word32
firstInstance
instance Storable DrawIndexedIndirectCommand where
sizeOf :: DrawIndexedIndirectCommand -> Int
sizeOf ~DrawIndexedIndirectCommand
_ = Int
20
alignment :: DrawIndexedIndirectCommand -> Int
alignment ~DrawIndexedIndirectCommand
_ = Int
4
peek :: Ptr DrawIndexedIndirectCommand -> IO DrawIndexedIndirectCommand
peek = Ptr DrawIndexedIndirectCommand -> IO DrawIndexedIndirectCommand
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DrawIndexedIndirectCommand
-> DrawIndexedIndirectCommand -> IO ()
poke Ptr DrawIndexedIndirectCommand
ptr DrawIndexedIndirectCommand
poked = Ptr DrawIndexedIndirectCommand
-> DrawIndexedIndirectCommand -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrawIndexedIndirectCommand
ptr DrawIndexedIndirectCommand
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DrawIndexedIndirectCommand where
zero :: DrawIndexedIndirectCommand
zero = Word32
-> Word32
-> Word32
-> Int32
-> Word32
-> DrawIndexedIndirectCommand
DrawIndexedIndirectCommand
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Int32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
data DispatchIndirectCommand = DispatchIndirectCommand
{
DispatchIndirectCommand -> Word32
x :: Word32
,
DispatchIndirectCommand -> Word32
y :: Word32
,
DispatchIndirectCommand -> Word32
z :: Word32
}
deriving (Typeable, DispatchIndirectCommand -> DispatchIndirectCommand -> Bool
(DispatchIndirectCommand -> DispatchIndirectCommand -> Bool)
-> (DispatchIndirectCommand -> DispatchIndirectCommand -> Bool)
-> Eq DispatchIndirectCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DispatchIndirectCommand -> DispatchIndirectCommand -> Bool
$c/= :: DispatchIndirectCommand -> DispatchIndirectCommand -> Bool
== :: DispatchIndirectCommand -> DispatchIndirectCommand -> Bool
$c== :: DispatchIndirectCommand -> DispatchIndirectCommand -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DispatchIndirectCommand)
#endif
deriving instance Show DispatchIndirectCommand
instance ToCStruct DispatchIndirectCommand where
withCStruct :: DispatchIndirectCommand
-> (Ptr DispatchIndirectCommand -> IO b) -> IO b
withCStruct DispatchIndirectCommand
x Ptr DispatchIndirectCommand -> IO b
f = Int -> (Ptr DispatchIndirectCommand -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
12 ((Ptr DispatchIndirectCommand -> IO b) -> IO b)
-> (Ptr DispatchIndirectCommand -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr DispatchIndirectCommand
p -> Ptr DispatchIndirectCommand
-> DispatchIndirectCommand -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DispatchIndirectCommand
p DispatchIndirectCommand
x (Ptr DispatchIndirectCommand -> IO b
f Ptr DispatchIndirectCommand
p)
pokeCStruct :: Ptr DispatchIndirectCommand
-> DispatchIndirectCommand -> IO b -> IO b
pokeCStruct Ptr DispatchIndirectCommand
p DispatchIndirectCommand{Word32
z :: Word32
y :: Word32
x :: Word32
$sel:z:DispatchIndirectCommand :: DispatchIndirectCommand -> Word32
$sel:y:DispatchIndirectCommand :: DispatchIndirectCommand -> Word32
$sel:x:DispatchIndirectCommand :: DispatchIndirectCommand -> Word32
..} IO b
f = do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
x)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Word32
y)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Word32
z)
IO b
f
cStructSize :: Int
cStructSize = Int
12
cStructAlignment :: Int
cStructAlignment = Int
4
pokeZeroCStruct :: Ptr DispatchIndirectCommand -> IO b -> IO b
pokeZeroCStruct Ptr DispatchIndirectCommand
p IO b
f = do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DispatchIndirectCommand where
peekCStruct :: Ptr DispatchIndirectCommand -> IO DispatchIndirectCommand
peekCStruct Ptr DispatchIndirectCommand
p = do
Word32
x <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32))
Word32
y <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32))
Word32
z <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DispatchIndirectCommand
p Ptr DispatchIndirectCommand -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32))
DispatchIndirectCommand -> IO DispatchIndirectCommand
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DispatchIndirectCommand -> IO DispatchIndirectCommand)
-> DispatchIndirectCommand -> IO DispatchIndirectCommand
forall a b. (a -> b) -> a -> b
$ Word32 -> Word32 -> Word32 -> DispatchIndirectCommand
DispatchIndirectCommand
Word32
x Word32
y Word32
z
instance Storable DispatchIndirectCommand where
sizeOf :: DispatchIndirectCommand -> Int
sizeOf ~DispatchIndirectCommand
_ = Int
12
alignment :: DispatchIndirectCommand -> Int
alignment ~DispatchIndirectCommand
_ = Int
4
peek :: Ptr DispatchIndirectCommand -> IO DispatchIndirectCommand
peek = Ptr DispatchIndirectCommand -> IO DispatchIndirectCommand
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DispatchIndirectCommand -> DispatchIndirectCommand -> IO ()
poke Ptr DispatchIndirectCommand
ptr DispatchIndirectCommand
poked = Ptr DispatchIndirectCommand
-> DispatchIndirectCommand -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DispatchIndirectCommand
ptr DispatchIndirectCommand
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DispatchIndirectCommand where
zero :: DispatchIndirectCommand
zero = Word32 -> Word32 -> Word32 -> DispatchIndirectCommand
DispatchIndirectCommand
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero