{-# LINE 1 "src/Gpu/Vulkan/Memory/Middle/Internal.hsc" #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE FlexibleContexts, UndecidableInstances #-}
{-# LANGUAGE PatternSynonyms, ViewPatterns #-}
{-# LANGUAGE StandaloneDeriving, GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -Wall -fno-warn-tabs #-}
module Gpu.Vulkan.Memory.Middle.Internal (
M(..), mToCore, AllocateInfo(..), allocate, reallocate, reallocate', free,
group, allocate', free', lookup, Group,
MapFlags(..), map, unmap,
Requirements(..), requirementsFromCore,
Barrier(..), barrierToCore,
Barrier2(..), barrier2ToCore,
Heap(..), heapFromCore,
MType(..), mTypeFromCore,
TypeBits, TypeIndex, elemTypeIndex, typeBitsToTypeIndices
) where
import Prelude hiding (map, lookup)
import Foreign.Ptr
import Foreign.Marshal.Alloc hiding (free)
import Foreign.Storable
import Foreign.Storable.PeekPoke
import Foreign.C.Enum
import Control.Concurrent.STM
import Control.Concurrent.STM.TSem
import Data.TypeLevel.Maybe qualified as TMaybe
import Data.TypeLevel.ParMaybe qualified as TPMaybe
import Data.Default
import Data.Bits
import Data.Map qualified as M
import Data.IORef
import Data.Word
import Gpu.Vulkan.Enum
import Gpu.Vulkan.Exception.Middle.Internal
import Gpu.Vulkan.Exception.Enum
import Gpu.Vulkan.Memory.Enum
import qualified Gpu.Vulkan.Device.Middle.Types as Device
import qualified Gpu.Vulkan.AllocationCallbacks.Middle.Internal as AllocationCallbacks
import qualified Gpu.Vulkan.Memory.Core as C
import qualified Gpu.Vulkan.Pipeline.Enum as Pipeline
newtype M = M (IORef C.M)
mToCore :: M -> IO C.M
mToCore :: M -> IO M
mToCore (M IORef M
r) = IORef M -> IO M
forall a. IORef a -> IO a
readIORef IORef M
r
newtype TypeBits = TypeBits Word32 deriving (Int -> TypeBits -> ShowS
[TypeBits] -> ShowS
TypeBits -> String
(Int -> TypeBits -> ShowS)
-> (TypeBits -> String) -> ([TypeBits] -> ShowS) -> Show TypeBits
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TypeBits -> ShowS
showsPrec :: Int -> TypeBits -> ShowS
$cshow :: TypeBits -> String
show :: TypeBits -> String
$cshowList :: [TypeBits] -> ShowS
showList :: [TypeBits] -> ShowS
Show, TypeBits -> TypeBits -> Bool
(TypeBits -> TypeBits -> Bool)
-> (TypeBits -> TypeBits -> Bool) -> Eq TypeBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeBits -> TypeBits -> Bool
== :: TypeBits -> TypeBits -> Bool
$c/= :: TypeBits -> TypeBits -> Bool
/= :: TypeBits -> TypeBits -> Bool
Eq, Eq TypeBits
TypeBits
Eq TypeBits =>
(TypeBits -> TypeBits -> TypeBits)
-> (TypeBits -> TypeBits -> TypeBits)
-> (TypeBits -> TypeBits -> TypeBits)
-> (TypeBits -> TypeBits)
-> (TypeBits -> Int -> TypeBits)
-> (TypeBits -> Int -> TypeBits)
-> TypeBits
-> (Int -> TypeBits)
-> (TypeBits -> Int -> TypeBits)
-> (TypeBits -> Int -> TypeBits)
-> (TypeBits -> Int -> TypeBits)
-> (TypeBits -> Int -> Bool)
-> (TypeBits -> Maybe Int)
-> (TypeBits -> Int)
-> (TypeBits -> Bool)
-> (TypeBits -> Int -> TypeBits)
-> (TypeBits -> Int -> TypeBits)
-> (TypeBits -> Int -> TypeBits)
-> (TypeBits -> Int -> TypeBits)
-> (TypeBits -> Int -> TypeBits)
-> (TypeBits -> Int -> TypeBits)
-> (TypeBits -> Int)
-> Bits TypeBits
Int -> TypeBits
TypeBits -> Bool
TypeBits -> Int
TypeBits -> Maybe Int
TypeBits -> TypeBits
TypeBits -> Int -> Bool
TypeBits -> Int -> TypeBits
TypeBits -> TypeBits -> TypeBits
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: TypeBits -> TypeBits -> TypeBits
.&. :: TypeBits -> TypeBits -> TypeBits
$c.|. :: TypeBits -> TypeBits -> TypeBits
.|. :: TypeBits -> TypeBits -> TypeBits
$cxor :: TypeBits -> TypeBits -> TypeBits
xor :: TypeBits -> TypeBits -> TypeBits
$ccomplement :: TypeBits -> TypeBits
complement :: TypeBits -> TypeBits
$cshift :: TypeBits -> Int -> TypeBits
shift :: TypeBits -> Int -> TypeBits
$crotate :: TypeBits -> Int -> TypeBits
rotate :: TypeBits -> Int -> TypeBits
$czeroBits :: TypeBits
zeroBits :: TypeBits
$cbit :: Int -> TypeBits
bit :: Int -> TypeBits
$csetBit :: TypeBits -> Int -> TypeBits
setBit :: TypeBits -> Int -> TypeBits
$cclearBit :: TypeBits -> Int -> TypeBits
clearBit :: TypeBits -> Int -> TypeBits
$ccomplementBit :: TypeBits -> Int -> TypeBits
complementBit :: TypeBits -> Int -> TypeBits
$ctestBit :: TypeBits -> Int -> Bool
testBit :: TypeBits -> Int -> Bool
$cbitSizeMaybe :: TypeBits -> Maybe Int
bitSizeMaybe :: TypeBits -> Maybe Int
$cbitSize :: TypeBits -> Int
bitSize :: TypeBits -> Int
$cisSigned :: TypeBits -> Bool
isSigned :: TypeBits -> Bool
$cshiftL :: TypeBits -> Int -> TypeBits
shiftL :: TypeBits -> Int -> TypeBits
$cunsafeShiftL :: TypeBits -> Int -> TypeBits
unsafeShiftL :: TypeBits -> Int -> TypeBits
$cshiftR :: TypeBits -> Int -> TypeBits
shiftR :: TypeBits -> Int -> TypeBits
$cunsafeShiftR :: TypeBits -> Int -> TypeBits
unsafeShiftR :: TypeBits -> Int -> TypeBits
$crotateL :: TypeBits -> Int -> TypeBits
rotateL :: TypeBits -> Int -> TypeBits
$crotateR :: TypeBits -> Int -> TypeBits
rotateR :: TypeBits -> Int -> TypeBits
$cpopCount :: TypeBits -> Int
popCount :: TypeBits -> Int
Bits, Bits TypeBits
Bits TypeBits =>
(TypeBits -> Int)
-> (TypeBits -> Int) -> (TypeBits -> Int) -> FiniteBits TypeBits
TypeBits -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: TypeBits -> Int
finiteBitSize :: TypeBits -> Int
$ccountLeadingZeros :: TypeBits -> Int
countLeadingZeros :: TypeBits -> Int
$ccountTrailingZeros :: TypeBits -> Int
countTrailingZeros :: TypeBits -> Int
FiniteBits)
{-# LINE 65 "src/Gpu/Vulkan/Memory/Middle/Internal.hsc" #-}
newtype TypeIndex = TypeIndex Word32
deriving (Int -> TypeIndex -> ShowS
[TypeIndex] -> ShowS
TypeIndex -> String
(Int -> TypeIndex -> ShowS)
-> (TypeIndex -> String)
-> ([TypeIndex] -> ShowS)
-> Show TypeIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TypeIndex -> ShowS
showsPrec :: Int -> TypeIndex -> ShowS
$cshow :: TypeIndex -> String
show :: TypeIndex -> String
$cshowList :: [TypeIndex] -> ShowS
showList :: [TypeIndex] -> ShowS
Show, TypeIndex -> TypeIndex -> Bool
(TypeIndex -> TypeIndex -> Bool)
-> (TypeIndex -> TypeIndex -> Bool) -> Eq TypeIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeIndex -> TypeIndex -> Bool
== :: TypeIndex -> TypeIndex -> Bool
$c/= :: TypeIndex -> TypeIndex -> Bool
/= :: TypeIndex -> TypeIndex -> Bool
Eq, Eq TypeIndex
Eq TypeIndex =>
(TypeIndex -> TypeIndex -> Ordering)
-> (TypeIndex -> TypeIndex -> Bool)
-> (TypeIndex -> TypeIndex -> Bool)
-> (TypeIndex -> TypeIndex -> Bool)
-> (TypeIndex -> TypeIndex -> Bool)
-> (TypeIndex -> TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex -> TypeIndex)
-> Ord TypeIndex
TypeIndex -> TypeIndex -> Bool
TypeIndex -> TypeIndex -> Ordering
TypeIndex -> TypeIndex -> TypeIndex
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TypeIndex -> TypeIndex -> Ordering
compare :: TypeIndex -> TypeIndex -> Ordering
$c< :: TypeIndex -> TypeIndex -> Bool
< :: TypeIndex -> TypeIndex -> Bool
$c<= :: TypeIndex -> TypeIndex -> Bool
<= :: TypeIndex -> TypeIndex -> Bool
$c> :: TypeIndex -> TypeIndex -> Bool
> :: TypeIndex -> TypeIndex -> Bool
$c>= :: TypeIndex -> TypeIndex -> Bool
>= :: TypeIndex -> TypeIndex -> Bool
$cmax :: TypeIndex -> TypeIndex -> TypeIndex
max :: TypeIndex -> TypeIndex -> TypeIndex
$cmin :: TypeIndex -> TypeIndex -> TypeIndex
min :: TypeIndex -> TypeIndex -> TypeIndex
Ord, Int -> TypeIndex
TypeIndex -> Int
TypeIndex -> [TypeIndex]
TypeIndex -> TypeIndex
TypeIndex -> TypeIndex -> [TypeIndex]
TypeIndex -> TypeIndex -> TypeIndex -> [TypeIndex]
(TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex)
-> (Int -> TypeIndex)
-> (TypeIndex -> Int)
-> (TypeIndex -> [TypeIndex])
-> (TypeIndex -> TypeIndex -> [TypeIndex])
-> (TypeIndex -> TypeIndex -> [TypeIndex])
-> (TypeIndex -> TypeIndex -> TypeIndex -> [TypeIndex])
-> Enum TypeIndex
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: TypeIndex -> TypeIndex
succ :: TypeIndex -> TypeIndex
$cpred :: TypeIndex -> TypeIndex
pred :: TypeIndex -> TypeIndex
$ctoEnum :: Int -> TypeIndex
toEnum :: Int -> TypeIndex
$cfromEnum :: TypeIndex -> Int
fromEnum :: TypeIndex -> Int
$cenumFrom :: TypeIndex -> [TypeIndex]
enumFrom :: TypeIndex -> [TypeIndex]
$cenumFromThen :: TypeIndex -> TypeIndex -> [TypeIndex]
enumFromThen :: TypeIndex -> TypeIndex -> [TypeIndex]
$cenumFromTo :: TypeIndex -> TypeIndex -> [TypeIndex]
enumFromTo :: TypeIndex -> TypeIndex -> [TypeIndex]
$cenumFromThenTo :: TypeIndex -> TypeIndex -> TypeIndex -> [TypeIndex]
enumFromThenTo :: TypeIndex -> TypeIndex -> TypeIndex -> [TypeIndex]
Enum, Integer -> TypeIndex
TypeIndex -> TypeIndex
TypeIndex -> TypeIndex -> TypeIndex
(TypeIndex -> TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex)
-> (Integer -> TypeIndex)
-> Num TypeIndex
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: TypeIndex -> TypeIndex -> TypeIndex
+ :: TypeIndex -> TypeIndex -> TypeIndex
$c- :: TypeIndex -> TypeIndex -> TypeIndex
- :: TypeIndex -> TypeIndex -> TypeIndex
$c* :: TypeIndex -> TypeIndex -> TypeIndex
* :: TypeIndex -> TypeIndex -> TypeIndex
$cnegate :: TypeIndex -> TypeIndex
negate :: TypeIndex -> TypeIndex
$cabs :: TypeIndex -> TypeIndex
abs :: TypeIndex -> TypeIndex
$csignum :: TypeIndex -> TypeIndex
signum :: TypeIndex -> TypeIndex
$cfromInteger :: Integer -> TypeIndex
fromInteger :: Integer -> TypeIndex
Num, Num TypeIndex
Ord TypeIndex
(Num TypeIndex, Ord TypeIndex) =>
(TypeIndex -> Rational) -> Real TypeIndex
TypeIndex -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: TypeIndex -> Rational
toRational :: TypeIndex -> Rational
Real, Enum TypeIndex
Real TypeIndex
(Real TypeIndex, Enum TypeIndex) =>
(TypeIndex -> TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex -> TypeIndex)
-> (TypeIndex -> TypeIndex -> (TypeIndex, TypeIndex))
-> (TypeIndex -> TypeIndex -> (TypeIndex, TypeIndex))
-> (TypeIndex -> Integer)
-> Integral TypeIndex
TypeIndex -> Integer
TypeIndex -> TypeIndex -> (TypeIndex, TypeIndex)
TypeIndex -> TypeIndex -> TypeIndex
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: TypeIndex -> TypeIndex -> TypeIndex
quot :: TypeIndex -> TypeIndex -> TypeIndex
$crem :: TypeIndex -> TypeIndex -> TypeIndex
rem :: TypeIndex -> TypeIndex -> TypeIndex
$cdiv :: TypeIndex -> TypeIndex -> TypeIndex
div :: TypeIndex -> TypeIndex -> TypeIndex
$cmod :: TypeIndex -> TypeIndex -> TypeIndex
mod :: TypeIndex -> TypeIndex -> TypeIndex
$cquotRem :: TypeIndex -> TypeIndex -> (TypeIndex, TypeIndex)
quotRem :: TypeIndex -> TypeIndex -> (TypeIndex, TypeIndex)
$cdivMod :: TypeIndex -> TypeIndex -> (TypeIndex, TypeIndex)
divMod :: TypeIndex -> TypeIndex -> (TypeIndex, TypeIndex)
$ctoInteger :: TypeIndex -> Integer
toInteger :: TypeIndex -> Integer
Integral)
typeBitsToTypeIndices :: TypeBits -> [TypeIndex]
typeBitsToTypeIndices :: TypeBits -> [TypeIndex]
typeBitsToTypeIndices TypeBits
bs = ((TypeIndex, Bool) -> TypeIndex
forall a b. (a, b) -> a
fst ((TypeIndex, Bool) -> TypeIndex)
-> [(TypeIndex, Bool)] -> [TypeIndex]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)
([(TypeIndex, Bool)] -> [TypeIndex])
-> ([Bool] -> [(TypeIndex, Bool)]) -> [Bool] -> [TypeIndex]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TypeIndex, Bool) -> Bool)
-> [(TypeIndex, Bool)] -> [(TypeIndex, Bool)]
forall a. (a -> Bool) -> [a] -> [a]
filter (TypeIndex, Bool) -> Bool
forall a b. (a, b) -> b
snd ([(TypeIndex, Bool)] -> [(TypeIndex, Bool)])
-> ([Bool] -> [(TypeIndex, Bool)]) -> [Bool] -> [(TypeIndex, Bool)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TypeIndex] -> [Bool] -> [(TypeIndex, Bool)]
forall a b. [a] -> [b] -> [(a, b)]
zip [TypeIndex
0 ..] ([Bool] -> [TypeIndex]) -> [Bool] -> [TypeIndex]
forall a b. (a -> b) -> a -> b
$ TypeBits -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit TypeBits
bs (Int -> Bool) -> [Int] -> [Bool]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int
0 .. TypeBits -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize TypeBits
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
elemTypeIndex :: TypeIndex -> TypeBits -> Bool
elemTypeIndex :: TypeIndex -> TypeBits -> Bool
elemTypeIndex TypeIndex
ti TypeBits
tbs = TypeBits -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit TypeBits
tbs (Int -> Bool) -> Int -> Bool
forall a b. (a -> b) -> a -> b
$ TypeIndex -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral TypeIndex
ti
data Requirements = Requirements {
Requirements -> Size
requirementsSize :: Device.Size,
Requirements -> Size
requirementsAlignment :: Device.Size,
Requirements -> TypeBits
requirementsMemoryTypeBits :: TypeBits }
deriving Int -> Requirements -> ShowS
[Requirements] -> ShowS
Requirements -> String
(Int -> Requirements -> ShowS)
-> (Requirements -> String)
-> ([Requirements] -> ShowS)
-> Show Requirements
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Requirements -> ShowS
showsPrec :: Int -> Requirements -> ShowS
$cshow :: Requirements -> String
show :: Requirements -> String
$cshowList :: [Requirements] -> ShowS
showList :: [Requirements] -> ShowS
Show
requirementsFromCore :: C.Requirements -> Requirements
requirementsFromCore :: Requirements -> Requirements
requirementsFromCore C.Requirements {
requirementsSize :: Requirements -> Word64
C.requirementsSize = Word64
sz,
requirementsAlignment :: Requirements -> Word64
C.requirementsAlignment = Word64
al,
requirementsMemoryTypeBits :: Requirements -> Word32
C.requirementsMemoryTypeBits = Word32
mtbs } = Requirements {
requirementsSize :: Size
requirementsSize = Word64 -> Size
Device.Size Word64
sz,
requirementsAlignment :: Size
requirementsAlignment = Word64 -> Size
Device.Size Word64
al,
requirementsMemoryTypeBits :: TypeBits
requirementsMemoryTypeBits = Word32 -> TypeBits
TypeBits Word32
mtbs }
data MType = MType {
MType -> PropertyFlags
mTypePropertyFlags :: PropertyFlags,
MType -> Word32
mTypeHeapIndex :: Word32 }
{-# LINE 94 "src/Gpu/Vulkan/Memory/Middle/Internal.hsc" #-}
deriving Int -> MType -> ShowS
[MType] -> ShowS
MType -> String
(Int -> MType -> ShowS)
-> (MType -> String) -> ([MType] -> ShowS) -> Show MType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MType -> ShowS
showsPrec :: Int -> MType -> ShowS
$cshow :: MType -> String
show :: MType -> String
$cshowList :: [MType] -> ShowS
showList :: [MType] -> ShowS
Show
mTypeFromCore :: C.MType -> MType
mTypeFromCore :: MType -> MType
mTypeFromCore C.MType {
mTypePropertyFlags :: MType -> Word32
C.mTypePropertyFlags = Word32
pfs,
mTypeHeapIndex :: MType -> Word32
C.mTypeHeapIndex = Word32
hi } = MType {
mTypePropertyFlags :: PropertyFlags
mTypePropertyFlags = Word32 -> PropertyFlags
PropertyFlagBits Word32
pfs,
mTypeHeapIndex :: Word32
mTypeHeapIndex = Word32
hi }
data Heap = Heap { Heap -> Size
heapSize :: Device.Size, Heap -> HeapFlags
heapFlags :: HeapFlags }
deriving Int -> Heap -> ShowS
[Heap] -> ShowS
Heap -> String
(Int -> Heap -> ShowS)
-> (Heap -> String) -> ([Heap] -> ShowS) -> Show Heap
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Heap -> ShowS
showsPrec :: Int -> Heap -> ShowS
$cshow :: Heap -> String
show :: Heap -> String
$cshowList :: [Heap] -> ShowS
showList :: [Heap] -> ShowS
Show
heapFromCore :: C.Heap -> Heap
heapFromCore :: Heap -> Heap
heapFromCore C.Heap { heapSize :: Heap -> Word64
C.heapSize = Word64
sz, heapFlags :: Heap -> Word32
C.heapFlags = Word32
flgs } =
Heap { heapSize :: Size
heapSize = Word64 -> Size
Device.Size Word64
sz, heapFlags :: HeapFlags
heapFlags = Word32 -> HeapFlags
HeapFlagBits Word32
flgs }
data AllocateInfo mn = AllocateInfo {
forall (mn :: Maybe (*)). AllocateInfo mn -> M mn
allocateInfoNext :: TMaybe.M mn,
forall (mn :: Maybe (*)). AllocateInfo mn -> Size
allocateInfoAllocationSize :: Device.Size,
forall (mn :: Maybe (*)). AllocateInfo mn -> TypeIndex
allocateInfoMemoryTypeIndex :: TypeIndex }
deriving instance Show (TMaybe.M mn) => Show (AllocateInfo mn)
allocateInfoToCore :: WithPoked (TMaybe.M mn) =>
AllocateInfo mn -> (Ptr C.AllocateInfo -> IO a) -> IO ()
allocateInfoToCore :: forall (mn :: Maybe (*)) a.
WithPoked (M mn) =>
AllocateInfo mn -> (Ptr AllocateInfo -> IO a) -> IO ()
allocateInfoToCore AllocateInfo {
allocateInfoNext :: forall (mn :: Maybe (*)). AllocateInfo mn -> M mn
allocateInfoNext = M mn
mnxt,
allocateInfoAllocationSize :: forall (mn :: Maybe (*)). AllocateInfo mn -> Size
allocateInfoAllocationSize = Device.Size Word64
sz,
allocateInfoMemoryTypeIndex :: forall (mn :: Maybe (*)). AllocateInfo mn -> TypeIndex
allocateInfoMemoryTypeIndex = TypeIndex Word32
mti } Ptr AllocateInfo -> IO a
f =
M mn -> (forall s. PtrS s (M mn) -> IO ()) -> IO ()
forall a b.
WithPoked a =>
a -> (forall s. PtrS s a -> IO b) -> IO b
forall b. M mn -> (forall s. PtrS s (M mn) -> IO b) -> IO b
withPoked' M mn
mnxt \PtrS s (M mn)
pnxt -> PtrS s (M mn) -> (Ptr (M mn) -> IO a) -> IO ()
forall s a b. PtrS s a -> (Ptr a -> IO b) -> IO ()
withPtrS PtrS s (M mn)
pnxt \(Ptr (M mn) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr -> Ptr ()
pnxt') ->
let ci :: AllocateInfo
ci = C.AllocateInfo {
allocateInfoSType :: ()
C.allocateInfoSType = (),
allocateInfoPNext :: Ptr ()
C.allocateInfoPNext = Ptr ()
pnxt',
allocateInfoAllocationSize :: Word64
C.allocateInfoAllocationSize = Word64
sz,
allocateInfoMemoryTypeIndex :: Word32
C.allocateInfoMemoryTypeIndex = Word32
mti } in
AllocateInfo -> (Ptr AllocateInfo -> IO a) -> IO a
forall a b. Pokable a => a -> (Ptr a -> IO b) -> IO b
withPoked AllocateInfo
ci Ptr AllocateInfo -> IO a
f
allocate :: WithPoked (TMaybe.M mn) =>
Device.D -> AllocateInfo mn -> TPMaybe.M AllocationCallbacks.A ma -> IO M
allocate :: forall (mn :: Maybe (*)) (ma :: Maybe (*)).
WithPoked (M mn) =>
D -> AllocateInfo mn -> M A ma -> IO M
allocate (Device.D D
dvc) AllocateInfo mn
ai M A ma
mac = IORef M -> M
M (IORef M -> M) -> IO (IORef M) -> IO M
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr M -> IO (IORef M)) -> IO (IORef M)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr M
pm -> do
AllocateInfo mn -> (Ptr AllocateInfo -> IO ()) -> IO ()
forall (mn :: Maybe (*)) a.
WithPoked (M mn) =>
AllocateInfo mn -> (Ptr AllocateInfo -> IO a) -> IO ()
allocateInfoToCore AllocateInfo mn
ai \Ptr AllocateInfo
pai ->
M A ma -> (Ptr A -> IO ()) -> IO ()
forall (ma :: Maybe (*)) b. M A ma -> (Ptr A -> IO b) -> IO ()
AllocationCallbacks.mToCore M A ma
mac \Ptr A
pac -> do
r <- D -> Ptr AllocateInfo -> Ptr A -> Ptr M -> IO Int32
C.allocate D
dvc Ptr AllocateInfo
pai Ptr A
pac Ptr M
pm
throwUnlessSuccess $ Result r
M -> IO (IORef M)
forall a. a -> IO (IORef a)
newIORef (M -> IO (IORef M)) -> IO M -> IO (IORef M)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr M -> IO M
forall a. Storable a => Ptr a -> IO a
peek Ptr M
pm
group :: Device.D -> TPMaybe.M AllocationCallbacks.A mf ->
(forall s . Group s k -> IO a) -> IO a
group :: forall (mf :: Maybe (*)) k a.
D -> M A mf -> (forall s. Group s k -> IO a) -> IO a
group D
dvc M A mf
mac forall s. Group s k -> IO a
f = do
(sem, mng) <-STM (TSem, TVar (Map k M)) -> IO (TSem, TVar (Map k M))
forall a. STM a -> IO a
atomically (STM (TSem, TVar (Map k M)) -> IO (TSem, TVar (Map k M)))
-> STM (TSem, TVar (Map k M)) -> IO (TSem, TVar (Map k M))
forall a b. (a -> b) -> a -> b
$ (,) (TSem -> TVar (Map k M) -> (TSem, TVar (Map k M)))
-> STM TSem -> STM (TVar (Map k M) -> (TSem, TVar (Map k M)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Integer -> STM TSem
newTSem Integer
1 STM (TVar (Map k M) -> (TSem, TVar (Map k M)))
-> STM (TVar (Map k M)) -> STM (TSem, TVar (Map k M))
forall a b. STM (a -> b) -> STM a -> STM b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Map k M -> STM (TVar (Map k M))
forall a. a -> STM (TVar a)
newTVar Map k M
forall k a. Map k a
M.empty
rtn <- f $ Group sem mng
((\M
m -> D -> M -> M A mf -> IO ()
forall (mf :: Maybe (*)). D -> M -> M A mf -> IO ()
free D
dvc M
m M A mf
mac) `mapM_`) =<< atomically (readTVar mng)
pure rtn
allocate' :: (Ord k, WithPoked (TMaybe.M mn)) =>
Device.D -> Group sm k -> k -> AllocateInfo mn ->
TPMaybe.M AllocationCallbacks.A ma -> IO (Either String M)
allocate' :: forall k (mn :: Maybe (*)) sm (ma :: Maybe (*)).
(Ord k, WithPoked (M mn)) =>
D
-> Group sm k
-> k
-> AllocateInfo mn
-> M A ma
-> IO (Either String M)
allocate' (Device.D D
dvc) (Group TSem
sem TVar (Map k M)
ms) k
k AllocateInfo mn
ai M A ma
mac = do
ok <- STM Bool -> IO Bool
forall a. STM a -> IO a
atomically do
mx <- (k -> Map k M -> Maybe M
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
k) (Map k M -> Maybe M) -> STM (Map k M) -> STM (Maybe M)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar (Map k M) -> STM (Map k M)
forall a. TVar a -> STM a
readTVar TVar (Map k M)
ms
case mx of
Maybe M
Nothing -> TSem -> STM ()
waitTSem TSem
sem STM () -> STM Bool -> STM Bool
forall a b. STM a -> STM b -> STM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> STM Bool
forall a. a -> STM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
Just M
_ -> Bool -> STM Bool
forall a. a -> STM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
if ok
then do m <- M <$> alloca \Ptr M
pm -> do
AllocateInfo mn -> (Ptr AllocateInfo -> IO ()) -> IO ()
forall (mn :: Maybe (*)) a.
WithPoked (M mn) =>
AllocateInfo mn -> (Ptr AllocateInfo -> IO a) -> IO ()
allocateInfoToCore AllocateInfo mn
ai \Ptr AllocateInfo
pai ->
M A ma -> (Ptr A -> IO ()) -> IO ()
forall (ma :: Maybe (*)) b. M A ma -> (Ptr A -> IO b) -> IO ()
AllocationCallbacks.mToCore M A ma
mac \Ptr A
pac -> do
r <- D -> Ptr AllocateInfo -> Ptr A -> Ptr M -> IO Int32
C.allocate D
dvc Ptr AllocateInfo
pai Ptr A
pac Ptr M
pm
throwUnlessSuccess $ Result r
M -> IO (IORef M)
forall a. a -> IO (IORef a)
newIORef (M -> IO (IORef M)) -> IO M -> IO (IORef M)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr M -> IO M
forall a. Storable a => Ptr a -> IO a
peek Ptr M
pm
atomically do
modifyTVar ms (M.insert k m)
signalTSem sem
pure $ Right m
else pure . Left $ "Gpu.Vulkan.Memory.allocate': The key already exist"
data Group s k = Group TSem (TVar (M.Map k M))
free' :: Ord k => Device.D ->
Group smng k -> k -> TPMaybe.M AllocationCallbacks.A mc ->
IO (Either String ())
free' :: forall k smng (mc :: Maybe (*)).
Ord k =>
D -> Group smng k -> k -> M A mc -> IO (Either String ())
free' D
dvc (Group TSem
sem TVar (Map k M)
ms) k
k M A mc
mac = do
mm <- STM (Maybe M) -> IO (Maybe M)
forall a. STM a -> IO a
atomically do
mx <- (k -> Map k M -> Maybe M
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
k) (Map k M -> Maybe M) -> STM (Map k M) -> STM (Maybe M)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar (Map k M) -> STM (Map k M)
forall a. TVar a -> STM a
readTVar TVar (Map k M)
ms
case mx of
Maybe M
Nothing -> Maybe M -> STM (Maybe M)
forall a. a -> STM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe M
forall a. Maybe a
Nothing
Just M
_ -> TSem -> STM ()
waitTSem TSem
sem STM () -> STM (Maybe M) -> STM (Maybe M)
forall a b. STM a -> STM b -> STM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe M -> STM (Maybe M)
forall a. a -> STM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe M
mx
case mm of
Maybe M
Nothing -> Either String () -> IO (Either String ())
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> IO (Either String ()))
-> Either String () -> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ String -> Either String ()
forall a b. a -> Either a b
Left String
"Gpu.Vulkan.Memory.free': No such key"
Just M
m -> do
D -> M -> M A mc -> IO ()
forall (mf :: Maybe (*)). D -> M -> M A mf -> IO ()
free D
dvc M
m M A mc
mac
STM (Either String ()) -> IO (Either String ())
forall a. STM a -> IO a
atomically do
TVar (Map k M) -> (Map k M -> Map k M) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar TVar (Map k M)
ms (k -> Map k M -> Map k M
forall k a. Ord k => k -> Map k a -> Map k a
M.delete k
k)
TSem -> STM ()
signalTSem TSem
sem
Either String () -> STM (Either String ())
forall a. a -> STM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> STM (Either String ()))
-> Either String () -> STM (Either String ())
forall a b. (a -> b) -> a -> b
$ () -> Either String ()
forall a b. b -> Either a b
Right ()
lookup :: Ord k => Group sm k -> k -> IO (Maybe M)
lookup :: forall k sm. Ord k => Group sm k -> k -> IO (Maybe M)
lookup (Group TSem
_sem TVar (Map k M)
ms) k
k = STM (Maybe M) -> IO (Maybe M)
forall a. STM a -> IO a
atomically (STM (Maybe M) -> IO (Maybe M)) -> STM (Maybe M) -> IO (Maybe M)
forall a b. (a -> b) -> a -> b
$ k -> Map k M -> Maybe M
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
k (Map k M -> Maybe M) -> STM (Map k M) -> STM (Maybe M)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar (Map k M) -> STM (Map k M)
forall a. TVar a -> STM a
readTVar TVar (Map k M)
ms
reallocate :: WithPoked (TMaybe.M mn) =>
Device.D -> AllocateInfo mn ->
TPMaybe.M AllocationCallbacks.A ma ->
M -> IO ()
reallocate :: forall (mn :: Maybe (*)) (ma :: Maybe (*)).
WithPoked (M mn) =>
D -> AllocateInfo mn -> M A ma -> M -> IO ()
reallocate d :: D
d@(Device.D D
dvc) AllocateInfo mn
ai M A ma
macc m :: M
m@(M IORef M
rm) =
(Ptr M -> IO ()) -> IO ()
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr M
pm -> AllocateInfo mn -> (Ptr AllocateInfo -> IO ()) -> IO ()
forall (mn :: Maybe (*)) a.
WithPoked (M mn) =>
AllocateInfo mn -> (Ptr AllocateInfo -> IO a) -> IO ()
allocateInfoToCore AllocateInfo mn
ai \Ptr AllocateInfo
pai ->
M A ma -> (Ptr A -> IO ()) -> IO ()
forall (ma :: Maybe (*)) b. M A ma -> (Ptr A -> IO b) -> IO ()
AllocationCallbacks.mToCore M A ma
macc \Ptr A
pac -> do
r <- D -> Ptr AllocateInfo -> Ptr A -> Ptr M -> IO Int32
C.allocate D
dvc Ptr AllocateInfo
pai Ptr A
pac Ptr M
pm
throwUnlessSuccess $ Result r
free d m macc
writeIORef rm =<< peek pm
reallocate' :: WithPoked (TMaybe.M mn) =>
Device.D -> AllocateInfo mn ->
TPMaybe.M AllocationCallbacks.A ma ->
M -> IO a -> IO ()
reallocate' :: forall (mn :: Maybe (*)) (ma :: Maybe (*)) a.
WithPoked (M mn) =>
D -> AllocateInfo mn -> M A ma -> M -> IO a -> IO ()
reallocate' (Device.D D
dvc) AllocateInfo mn
ai M A ma
macc (M IORef M
rm) IO a
act =
(Ptr M -> IO ()) -> IO ()
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr M
pm -> AllocateInfo mn -> (Ptr AllocateInfo -> IO ()) -> IO ()
forall (mn :: Maybe (*)) a.
WithPoked (M mn) =>
AllocateInfo mn -> (Ptr AllocateInfo -> IO a) -> IO ()
allocateInfoToCore AllocateInfo mn
ai \Ptr AllocateInfo
pai ->
M A ma -> (Ptr A -> IO ()) -> IO ()
forall (ma :: Maybe (*)) b. M A ma -> (Ptr A -> IO b) -> IO ()
AllocationCallbacks.mToCore M A ma
macc \Ptr A
pac -> do
r <- D -> Ptr AllocateInfo -> Ptr A -> Ptr M -> IO Int32
C.allocate D
dvc Ptr AllocateInfo
pai Ptr A
pac Ptr M
pm
throwUnlessSuccess $ Result r
mm <- readIORef rm
writeIORef rm =<< peek pm
_ <- act
C.free dvc mm pac
free :: Device.D -> M -> TPMaybe.M AllocationCallbacks.A mf -> IO ()
free :: forall (mf :: Maybe (*)). D -> M -> M A mf -> IO ()
free (Device.D D
dvc) (M IORef M
mem) M A mf
mac =
M A mf -> (Ptr A -> IO ()) -> IO ()
forall (ma :: Maybe (*)) b. M A ma -> (Ptr A -> IO b) -> IO ()
AllocationCallbacks.mToCore M A mf
mac \Ptr A
pac -> do
m <- IORef M -> IO M
forall a. IORef a -> IO a
readIORef IORef M
mem
C.free dvc m pac
enum "MapFlags" ''Word32
{-# LINE 228 "src/Gpu/Vulkan/Memory/Middle/Internal.hsc" #-}
[''Eq, ''Show, ''Storable, ''Bits] [("MapFlagsZero", 0)]
instance Default MapFlags where def :: MapFlags
def = MapFlags
MapFlagsZero
map :: Device.D -> M -> Device.Size -> Device.Size -> MapFlags ->
IO (Ptr a)
map :: forall a. D -> M -> Size -> Size -> MapFlags -> IO (Ptr a)
map (Device.D D
dvc) (M IORef M
mem)
(Device.Size Word64
ofst) (Device.Size Word64
sz) (MapFlags Word32
flgs) = (Ptr (Ptr a) -> IO (Ptr a)) -> IO (Ptr a)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr (Ptr a)
pd ->
IORef M -> IO M
forall a. IORef a -> IO a
readIORef IORef M
mem IO M -> (M -> IO (Ptr a)) -> IO (Ptr a)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \M
m ->
D -> M -> Word64 -> Word64 -> Word32 -> Ptr (Ptr a) -> IO Int32
forall a.
D -> M -> Word64 -> Word64 -> Word32 -> Ptr (Ptr a) -> IO Int32
C.map D
dvc M
m Word64
ofst Word64
sz Word32
flgs Ptr (Ptr a)
pd IO Int32 -> (Int32 -> IO (Ptr a)) -> IO (Ptr a)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int32
r ->
Result -> IO ()
throwUnlessSuccess (Int32 -> Result
Result Int32
r) IO () -> IO (Ptr a) -> IO (Ptr a)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Ptr (Ptr a) -> IO (Ptr a)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr a)
pd
unmap :: Device.D -> M -> IO ()
unmap :: D -> M -> IO ()
unmap (Device.D D
dvc) (M IORef M
mem) = D -> M -> IO ()
C.unmap D
dvc (M -> IO ()) -> IO M -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IORef M -> IO M
forall a. IORef a -> IO a
readIORef IORef M
mem
data Barrier mn = Barrier {
forall (mn :: Maybe (*)). Barrier mn -> M mn
barrierNext :: TMaybe.M mn,
forall (mn :: Maybe (*)). Barrier mn -> AccessFlags
barrierSrcAccessMask :: AccessFlags,
forall (mn :: Maybe (*)). Barrier mn -> AccessFlags
barrierDstAccessMask :: AccessFlags }
deriving instance Show (TMaybe.M mn) => Show (Barrier mn)
barrierToCore :: WithPoked (TMaybe.M mn) =>
Barrier mn -> (C.Barrier -> IO a) -> IO ()
barrierToCore :: forall (mn :: Maybe (*)) a.
WithPoked (M mn) =>
Barrier mn -> (Barrier -> IO a) -> IO ()
barrierToCore Barrier {
barrierNext :: forall (mn :: Maybe (*)). Barrier mn -> M mn
barrierNext = M mn
mnxt,
barrierSrcAccessMask :: forall (mn :: Maybe (*)). Barrier mn -> AccessFlags
barrierSrcAccessMask = AccessFlagBits Word32
sam,
barrierDstAccessMask :: forall (mn :: Maybe (*)). Barrier mn -> AccessFlags
barrierDstAccessMask = AccessFlagBits Word32
dam } Barrier -> IO a
f =
M mn -> (forall s. PtrS s (M mn) -> IO ()) -> IO ()
forall a b.
WithPoked a =>
a -> (forall s. PtrS s a -> IO b) -> IO b
forall b. M mn -> (forall s. PtrS s (M mn) -> IO b) -> IO b
withPoked' M mn
mnxt \PtrS s (M mn)
pnxt -> PtrS s (M mn) -> (Ptr (M mn) -> IO a) -> IO ()
forall s a b. PtrS s a -> (Ptr a -> IO b) -> IO ()
withPtrS PtrS s (M mn)
pnxt \(Ptr (M mn) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr -> Ptr ()
pnxt') -> Barrier -> IO a
f C.Barrier {
barrierSType :: ()
C.barrierSType = (),
barrierPNext :: Ptr ()
C.barrierPNext = Ptr ()
pnxt',
barrierSrcAccessMask :: Word32
C.barrierSrcAccessMask = Word32
sam,
barrierDstAccessMask :: Word32
C.barrierDstAccessMask = Word32
dam }
data Barrier2 mn = Barrier2 {
forall (mn :: Maybe (*)). Barrier2 mn -> M mn
barrier2Next :: TMaybe.M mn,
forall (mn :: Maybe (*)). Barrier2 mn -> StageFlags2
barrier2SrcStageMask :: Pipeline.StageFlags2,
forall (mn :: Maybe (*)). Barrier2 mn -> AccessFlags2
barrier2SrcAccessMask :: AccessFlags2,
forall (mn :: Maybe (*)). Barrier2 mn -> StageFlags2
barrier2DstStageMask :: Pipeline.StageFlags2,
forall (mn :: Maybe (*)). Barrier2 mn -> AccessFlags2
barrier2DstAccessMask :: AccessFlags2 }
deriving instance Show (TMaybe.M mn) => Show (Barrier2 mn)
barrier2ToCore :: WithPoked (TMaybe.M mn) =>
Barrier2 mn -> (C.Barrier2 -> IO a) -> IO ()
barrier2ToCore :: forall (mn :: Maybe (*)) a.
WithPoked (M mn) =>
Barrier2 mn -> (Barrier2 -> IO a) -> IO ()
barrier2ToCore Barrier2 {
barrier2Next :: forall (mn :: Maybe (*)). Barrier2 mn -> M mn
barrier2Next = M mn
mnxt,
barrier2SrcStageMask :: forall (mn :: Maybe (*)). Barrier2 mn -> StageFlags2
barrier2SrcStageMask = Pipeline.StageFlagBits2 Word64
ssm,
barrier2SrcAccessMask :: forall (mn :: Maybe (*)). Barrier2 mn -> AccessFlags2
barrier2SrcAccessMask = AccessFlagBits2 Word64
sam,
barrier2DstStageMask :: forall (mn :: Maybe (*)). Barrier2 mn -> StageFlags2
barrier2DstStageMask = Pipeline.StageFlagBits2 Word64
dsm,
barrier2DstAccessMask :: forall (mn :: Maybe (*)). Barrier2 mn -> AccessFlags2
barrier2DstAccessMask = AccessFlagBits2 Word64
dam } Barrier2 -> IO a
f =
M mn -> (forall s. PtrS s (M mn) -> IO ()) -> IO ()
forall a b.
WithPoked a =>
a -> (forall s. PtrS s a -> IO b) -> IO b
forall b. M mn -> (forall s. PtrS s (M mn) -> IO b) -> IO b
withPoked' M mn
mnxt \PtrS s (M mn)
pnxt -> PtrS s (M mn) -> (Ptr (M mn) -> IO a) -> IO ()
forall s a b. PtrS s a -> (Ptr a -> IO b) -> IO ()
withPtrS PtrS s (M mn)
pnxt \(Ptr (M mn) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr -> Ptr ()
pnxt') -> Barrier2 -> IO a
f C.Barrier2 {
barrier2SType :: ()
C.barrier2SType = (),
barrier2PNext :: Ptr ()
C.barrier2PNext = Ptr ()
pnxt',
barrier2SrcStageMask :: Word64
C.barrier2SrcStageMask = Word64
ssm,
barrier2SrcAccessMask :: Word64
C.barrier2SrcAccessMask = Word64
sam,
barrier2DstStageMask :: Word64
C.barrier2DstStageMask = Word64
dsm,
barrier2DstAccessMask :: Word64
C.barrier2DstAccessMask = Word64
dam }