{-# language CPP #-}
module Vulkan.Extensions.VK_NV_win32_keyed_mutex  ( Win32KeyedMutexAcquireReleaseInfoNV(..)
                                                  , NV_WIN32_KEYED_MUTEX_SPEC_VERSION
                                                  , pattern NV_WIN32_KEYED_MUTEX_SPEC_VERSION
                                                  , NV_WIN32_KEYED_MUTEX_EXTENSION_NAME
                                                  , pattern NV_WIN32_KEYED_MUTEX_EXTENSION_NAME
                                                  ) where

import Control.Monad (unless)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.IO (throwIO)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Word (Word64)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_NV))
-- | VkWin32KeyedMutexAcquireReleaseInfoNV - use Windows keyex mutex
-- mechanism to synchronize work
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_NV'
--
-- -   If @acquireCount@ is not @0@, @pAcquireSyncs@ /must/ be a valid
--     pointer to an array of @acquireCount@ valid
--     'Vulkan.Core10.Handles.DeviceMemory' handles
--
-- -   If @acquireCount@ is not @0@, @pAcquireKeys@ /must/ be a valid
--     pointer to an array of @acquireCount@ @uint64_t@ values
--
-- -   If @acquireCount@ is not @0@, @pAcquireTimeoutMilliseconds@ /must/
--     be a valid pointer to an array of @acquireCount@ @uint32_t@ values
--
-- -   If @releaseCount@ is not @0@, @pReleaseSyncs@ /must/ be a valid
--     pointer to an array of @releaseCount@ valid
--     'Vulkan.Core10.Handles.DeviceMemory' handles
--
-- -   If @releaseCount@ is not @0@, @pReleaseKeys@ /must/ be a valid
--     pointer to an array of @releaseCount@ @uint64_t@ values
--
-- -   Both of the elements of @pAcquireSyncs@, and the elements of
--     @pReleaseSyncs@ that are valid handles of non-ignored parameters
--     /must/ have been created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.DeviceMemory',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data Win32KeyedMutexAcquireReleaseInfoNV = Win32KeyedMutexAcquireReleaseInfoNV
  { -- | @pAcquireSyncs@ is a pointer to an array of
    -- 'Vulkan.Core10.Handles.DeviceMemory' objects which were imported from
    -- Direct3D 11 resources.
    Win32KeyedMutexAcquireReleaseInfoNV -> Vector DeviceMemory
acquireSyncs :: Vector DeviceMemory
  , -- | @pAcquireKeys@ is a pointer to an array of mutex key values to wait for
    -- prior to beginning the submitted work. Entries refer to the keyed mutex
    -- associated with the corresponding entries in @pAcquireSyncs@.
    Win32KeyedMutexAcquireReleaseInfoNV -> Vector Word64
acquireKeys :: Vector Word64
  , -- | @pAcquireTimeoutMilliseconds@ is a pointer to an array of timeout
    -- values, in millisecond units, for each acquire specified in
    -- @pAcquireKeys@.
    Win32KeyedMutexAcquireReleaseInfoNV -> Vector Word32
acquireTimeoutMilliseconds :: Vector Word32
  , -- | @pReleaseSyncs@ is a pointer to an array of
    -- 'Vulkan.Core10.Handles.DeviceMemory' objects which were imported from
    -- Direct3D 11 resources.
    Win32KeyedMutexAcquireReleaseInfoNV -> Vector DeviceMemory
releaseSyncs :: Vector DeviceMemory
  , -- | @pReleaseKeys@ is a pointer to an array of mutex key values to set when
    -- the submitted work has completed. Entries refer to the keyed mutex
    -- associated with the corresponding entries in @pReleaseSyncs@.
    Win32KeyedMutexAcquireReleaseInfoNV -> Vector Word64
releaseKeys :: Vector Word64
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (Win32KeyedMutexAcquireReleaseInfoNV)
#endif
deriving instance Show Win32KeyedMutexAcquireReleaseInfoNV

instance ToCStruct Win32KeyedMutexAcquireReleaseInfoNV where
  withCStruct :: Win32KeyedMutexAcquireReleaseInfoNV
-> (Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b) -> IO b
withCStruct x :: Win32KeyedMutexAcquireReleaseInfoNV
x f :: Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b
f = Int
-> Int -> (Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 72 8 ((Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b) -> IO b)
-> (Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr Win32KeyedMutexAcquireReleaseInfoNV
p -> Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> Win32KeyedMutexAcquireReleaseInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Win32KeyedMutexAcquireReleaseInfoNV
x (Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b
f Ptr Win32KeyedMutexAcquireReleaseInfoNV
p)
  pokeCStruct :: Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> Win32KeyedMutexAcquireReleaseInfoNV -> IO b -> IO b
pokeCStruct p :: Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Win32KeyedMutexAcquireReleaseInfoNV{..} f :: 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 Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_NV)
    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 Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    let pAcquireSyncsLength :: Int
pAcquireSyncsLength = Vector DeviceMemory -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DeviceMemory -> Int) -> Vector DeviceMemory -> Int
forall a b. (a -> b) -> a -> b
$ (Vector DeviceMemory
acquireSyncs)
    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
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Word64 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word64 -> Int) -> Vector Word64 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word64
acquireKeys)) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pAcquireSyncsLength) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "pAcquireKeys and pAcquireSyncs must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    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
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32 -> Int) -> Vector Word32 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word32
acquireTimeoutMilliseconds)) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pAcquireSyncsLength) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "pAcquireTimeoutMilliseconds and pAcquireSyncs must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    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 Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pAcquireSyncsLength :: Word32))
    Ptr DeviceMemory
pPAcquireSyncs' <- ((Ptr DeviceMemory -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemory)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DeviceMemory -> IO b) -> IO b)
 -> ContT b IO (Ptr DeviceMemory))
-> ((Ptr DeviceMemory -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemory)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr DeviceMemory -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DeviceMemory ((Vector DeviceMemory -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DeviceMemory
acquireSyncs)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    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
$ (Int -> DeviceMemory -> IO ()) -> Vector DeviceMemory -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DeviceMemory
e -> Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DeviceMemory
pPAcquireSyncs' Ptr DeviceMemory -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceMemory) (DeviceMemory
e)) (Vector DeviceMemory
acquireSyncs)
    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 DeviceMemory) -> Ptr DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> Int -> Ptr (Ptr DeviceMemory)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DeviceMemory))) (Ptr DeviceMemory
pPAcquireSyncs')
    Ptr Word64
pPAcquireKeys' <- ((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64))
-> ((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word64 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word64 ((Vector Word64 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word64
acquireKeys)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    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
$ (Int -> Word64 -> IO ()) -> Vector Word64 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word64
e -> Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word64
pPAcquireKeys' Ptr Word64 -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word64) (Word64
e)) (Vector Word64
acquireKeys)
    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 Word64) -> Ptr Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr Word64))) (Ptr Word64
pPAcquireKeys')
    Ptr Word32
pPAcquireTimeoutMilliseconds' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32
acquireTimeoutMilliseconds)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPAcquireTimeoutMilliseconds' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
acquireTimeoutMilliseconds)
    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 Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr Word32))) (Ptr Word32
pPAcquireTimeoutMilliseconds')
    let pReleaseSyncsLength :: Int
pReleaseSyncsLength = Vector DeviceMemory -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DeviceMemory -> Int) -> Vector DeviceMemory -> Int
forall a b. (a -> b) -> a -> b
$ (Vector DeviceMemory
releaseSyncs)
    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
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Word64 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word64 -> Int) -> Vector Word64 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word64
releaseKeys)) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pReleaseSyncsLength) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "pReleaseKeys and pReleaseSyncs must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    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 Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pReleaseSyncsLength :: Word32))
    Ptr DeviceMemory
pPReleaseSyncs' <- ((Ptr DeviceMemory -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemory)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DeviceMemory -> IO b) -> IO b)
 -> ContT b IO (Ptr DeviceMemory))
-> ((Ptr DeviceMemory -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemory)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr DeviceMemory -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DeviceMemory ((Vector DeviceMemory -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DeviceMemory
releaseSyncs)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    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
$ (Int -> DeviceMemory -> IO ()) -> Vector DeviceMemory -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DeviceMemory
e -> Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DeviceMemory
pPReleaseSyncs' Ptr DeviceMemory -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceMemory) (DeviceMemory
e)) (Vector DeviceMemory
releaseSyncs)
    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 DeviceMemory) -> Ptr DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> Int -> Ptr (Ptr DeviceMemory)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr DeviceMemory))) (Ptr DeviceMemory
pPReleaseSyncs')
    Ptr Word64
pPReleaseKeys' <- ((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64))
-> ((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word64 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word64 ((Vector Word64 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word64
releaseKeys)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    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
$ (Int -> Word64 -> IO ()) -> Vector Word64 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word64
e -> Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word64
pPReleaseKeys' Ptr Word64 -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word64) (Word64
e)) (Vector Word64
releaseKeys)
    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 Word64) -> Ptr Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr Word64))) (Ptr Word64
pPReleaseKeys')
    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 = 72
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr Win32KeyedMutexAcquireReleaseInfoNV
p f :: 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 Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_NV)
    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 Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceMemory
pPAcquireSyncs' <- ((Ptr DeviceMemory -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemory)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DeviceMemory -> IO b) -> IO b)
 -> ContT b IO (Ptr DeviceMemory))
-> ((Ptr DeviceMemory -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemory)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr DeviceMemory -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DeviceMemory ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    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
$ (Int -> DeviceMemory -> IO ()) -> Vector DeviceMemory -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DeviceMemory
e -> Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DeviceMemory
pPAcquireSyncs' Ptr DeviceMemory -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceMemory) (DeviceMemory
e)) (Vector DeviceMemory
forall a. Monoid a => a
mempty)
    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 DeviceMemory) -> Ptr DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> Int -> Ptr (Ptr DeviceMemory)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DeviceMemory))) (Ptr DeviceMemory
pPAcquireSyncs')
    Ptr Word64
pPAcquireKeys' <- ((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64))
-> ((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word64 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word64 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    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
$ (Int -> Word64 -> IO ()) -> Vector Word64 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word64
e -> Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word64
pPAcquireKeys' Ptr Word64 -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word64) (Word64
e)) (Vector Word64
forall a. Monoid a => a
mempty)
    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 Word64) -> Ptr Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr Word64))) (Ptr Word64
pPAcquireKeys')
    Ptr Word32
pPAcquireTimeoutMilliseconds' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPAcquireTimeoutMilliseconds' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
forall a. Monoid a => a
mempty)
    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 Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr Word32))) (Ptr Word32
pPAcquireTimeoutMilliseconds')
    Ptr DeviceMemory
pPReleaseSyncs' <- ((Ptr DeviceMemory -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemory)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DeviceMemory -> IO b) -> IO b)
 -> ContT b IO (Ptr DeviceMemory))
-> ((Ptr DeviceMemory -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemory)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr DeviceMemory -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DeviceMemory ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    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
$ (Int -> DeviceMemory -> IO ()) -> Vector DeviceMemory -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DeviceMemory
e -> Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DeviceMemory
pPReleaseSyncs' Ptr DeviceMemory -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceMemory) (DeviceMemory
e)) (Vector DeviceMemory
forall a. Monoid a => a
mempty)
    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 DeviceMemory) -> Ptr DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> Int -> Ptr (Ptr DeviceMemory)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr DeviceMemory))) (Ptr DeviceMemory
pPReleaseSyncs')
    Ptr Word64
pPReleaseKeys' <- ((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64))
-> ((Ptr Word64 -> IO b) -> IO b) -> ContT b IO (Ptr Word64)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word64 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word64 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    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
$ (Int -> Word64 -> IO ()) -> Vector Word64 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word64
e -> Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word64
pPReleaseKeys' Ptr Word64 -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word64) (Word64
e)) (Vector Word64
forall a. Monoid a => a
mempty)
    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 Word64) -> Ptr Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr Word64))) (Ptr Word64
pPReleaseKeys')
    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 FromCStruct Win32KeyedMutexAcquireReleaseInfoNV where
  peekCStruct :: Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> IO Win32KeyedMutexAcquireReleaseInfoNV
peekCStruct p :: Ptr Win32KeyedMutexAcquireReleaseInfoNV
p = do
    Word32
acquireCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Ptr DeviceMemory
pAcquireSyncs <- Ptr (Ptr DeviceMemory) -> IO (Ptr DeviceMemory)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr DeviceMemory) ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> Int -> Ptr (Ptr DeviceMemory)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DeviceMemory)))
    Vector DeviceMemory
pAcquireSyncs' <- Int -> (Int -> IO DeviceMemory) -> IO (Vector DeviceMemory)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
acquireCount) (\i :: Int
i -> Ptr DeviceMemory -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory ((Ptr DeviceMemory
pAcquireSyncs Ptr DeviceMemory -> Int -> Ptr DeviceMemory
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceMemory)))
    Ptr Word64
pAcquireKeys <- Ptr (Ptr Word64) -> IO (Ptr Word64)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word64) ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr Word64)))
    Vector Word64
pAcquireKeys' <- Int -> (Int -> IO Word64) -> IO (Vector Word64)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
acquireCount) (\i :: Int
i -> Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr Word64
pAcquireKeys Ptr Word64 -> Int -> Ptr Word64
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word64)))
    Ptr Word32
pAcquireTimeoutMilliseconds <- Ptr (Ptr Word32) -> IO (Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr Word32)))
    Vector Word32
pAcquireTimeoutMilliseconds' <- Int -> (Int -> IO Word32) -> IO (Vector Word32)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
acquireCount) (\i :: Int
i -> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pAcquireTimeoutMilliseconds Ptr Word32 -> Int -> Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    Word32
releaseCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    Ptr DeviceMemory
pReleaseSyncs <- Ptr (Ptr DeviceMemory) -> IO (Ptr DeviceMemory)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr DeviceMemory) ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> Int -> Ptr (Ptr DeviceMemory)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr DeviceMemory)))
    Vector DeviceMemory
pReleaseSyncs' <- Int -> (Int -> IO DeviceMemory) -> IO (Vector DeviceMemory)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
releaseCount) (\i :: Int
i -> Ptr DeviceMemory -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory ((Ptr DeviceMemory
pReleaseSyncs Ptr DeviceMemory -> Int -> Ptr DeviceMemory
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceMemory)))
    Ptr Word64
pReleaseKeys <- Ptr (Ptr Word64) -> IO (Ptr Word64)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word64) ((Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Ptr Win32KeyedMutexAcquireReleaseInfoNV -> Int -> Ptr (Ptr Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr Word64)))
    Vector Word64
pReleaseKeys' <- Int -> (Int -> IO Word64) -> IO (Vector Word64)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
releaseCount) (\i :: Int
i -> Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr Word64
pReleaseKeys Ptr Word64 -> Int -> Ptr Word64
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word64)))
    Win32KeyedMutexAcquireReleaseInfoNV
-> IO Win32KeyedMutexAcquireReleaseInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Win32KeyedMutexAcquireReleaseInfoNV
 -> IO Win32KeyedMutexAcquireReleaseInfoNV)
-> Win32KeyedMutexAcquireReleaseInfoNV
-> IO Win32KeyedMutexAcquireReleaseInfoNV
forall a b. (a -> b) -> a -> b
$ Vector DeviceMemory
-> Vector Word64
-> Vector Word32
-> Vector DeviceMemory
-> Vector Word64
-> Win32KeyedMutexAcquireReleaseInfoNV
Win32KeyedMutexAcquireReleaseInfoNV
             Vector DeviceMemory
pAcquireSyncs' Vector Word64
pAcquireKeys' Vector Word32
pAcquireTimeoutMilliseconds' Vector DeviceMemory
pReleaseSyncs' Vector Word64
pReleaseKeys'

instance Zero Win32KeyedMutexAcquireReleaseInfoNV where
  zero :: Win32KeyedMutexAcquireReleaseInfoNV
zero = Vector DeviceMemory
-> Vector Word64
-> Vector Word32
-> Vector DeviceMemory
-> Vector Word64
-> Win32KeyedMutexAcquireReleaseInfoNV
Win32KeyedMutexAcquireReleaseInfoNV
           Vector DeviceMemory
forall a. Monoid a => a
mempty
           Vector Word64
forall a. Monoid a => a
mempty
           Vector Word32
forall a. Monoid a => a
mempty
           Vector DeviceMemory
forall a. Monoid a => a
mempty
           Vector Word64
forall a. Monoid a => a
mempty


type NV_WIN32_KEYED_MUTEX_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_NV_WIN32_KEYED_MUTEX_SPEC_VERSION"
pattern NV_WIN32_KEYED_MUTEX_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_WIN32_KEYED_MUTEX_SPEC_VERSION :: a
$mNV_WIN32_KEYED_MUTEX_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_WIN32_KEYED_MUTEX_SPEC_VERSION = 2


type NV_WIN32_KEYED_MUTEX_EXTENSION_NAME = "VK_NV_win32_keyed_mutex"

-- No documentation found for TopLevel "VK_NV_WIN32_KEYED_MUTEX_EXTENSION_NAME"
pattern NV_WIN32_KEYED_MUTEX_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_WIN32_KEYED_MUTEX_EXTENSION_NAME :: a
$mNV_WIN32_KEYED_MUTEX_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_WIN32_KEYED_MUTEX_EXTENSION_NAME = "VK_NV_win32_keyed_mutex"