{-# language CPP #-}
-- | = Name
--
-- VK_NV_win32_keyed_mutex - device extension
--
-- == VK_NV_win32_keyed_mutex
--
-- [__Name String__]
--     @VK_NV_win32_keyed_mutex@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     59
--
-- [__Revision__]
--     2
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_NV_external_memory_win32@ to be enabled for any
--         device-level functionality
--
-- [__Deprecation state__]
--
--     -   /Promoted/ to @VK_KHR_win32_keyed_mutex@ extension
--
-- [__Contact__]
--
--     -   Carsten Rohde
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_NV_win32_keyed_mutex] @crohde%0A*Here describe the issue or question you have about the VK_NV_win32_keyed_mutex extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2016-08-19
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   James Jones, NVIDIA
--
--     -   Carsten Rohde, NVIDIA
--
-- == Description
--
-- Applications that wish to import Direct3D 11 memory objects into the
-- Vulkan API may wish to use the native keyed mutex mechanism to
-- synchronize access to the memory between Vulkan and Direct3D. This
-- extension provides a way for an application to access the keyed mutex
-- associated with an imported Vulkan memory object when submitting command
-- buffers to a queue.
--
-- == New Structures
--
-- -   Extending 'Vulkan.Core10.Queue.SubmitInfo',
--     'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.SubmitInfo2':
--
--     -   'Win32KeyedMutexAcquireReleaseInfoNV'
--
-- == New Enum Constants
--
-- -   'NV_WIN32_KEYED_MUTEX_EXTENSION_NAME'
--
-- -   'NV_WIN32_KEYED_MUTEX_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_NV'
--
-- == Examples
--
-- >     //
-- >     // Import a memory object from Direct3D 11, and synchronize
-- >     // access to it in Vulkan using keyed mutex objects.
-- >     //
-- >
-- >     extern VkPhysicalDevice physicalDevice;
-- >     extern VkDevice device;
-- >     extern HANDLE sharedNtHandle;
-- >
-- >     static const VkFormat format = VK_FORMAT_R8G8B8A8_UNORM;
-- >     static const VkExternalMemoryHandleTypeFlagsNV handleType =
-- >         VK_EXTERNAL_MEMORY_HANDLE_TYPE_D3D11_IMAGE_BIT_NV;
-- >
-- >     VkPhysicalDeviceMemoryProperties memoryProperties;
-- >     VkExternalImageFormatPropertiesNV properties;
-- >     VkExternalMemoryImageCreateInfoNV externalMemoryImageCreateInfo;
-- >     VkImageCreateInfo imageCreateInfo;
-- >     VkImage image;
-- >     VkMemoryRequirements imageMemoryRequirements;
-- >     uint32_t numMemoryTypes;
-- >     uint32_t memoryType;
-- >     VkImportMemoryWin32HandleInfoNV importMemoryInfo;
-- >     VkMemoryAllocateInfo memoryAllocateInfo;
-- >     VkDeviceMemory mem;
-- >     VkResult result;
-- >
-- >     // Figure out how many memory types the device supports
-- >     vkGetPhysicalDeviceMemoryProperties(physicalDevice,
-- >                                         &memoryProperties);
-- >     numMemoryTypes = memoryProperties.memoryTypeCount;
-- >
-- >     // Check the external handle type capabilities for the chosen format
-- >     // Importable 2D image support with at least 1 mip level, 1 array
-- >     // layer, and VK_SAMPLE_COUNT_1_BIT using optimal tiling and supporting
-- >     // texturing and color rendering is required.
-- >     result = vkGetPhysicalDeviceExternalImageFormatPropertiesNV(
-- >         physicalDevice,
-- >         format,
-- >         VK_IMAGE_TYPE_2D,
-- >         VK_IMAGE_TILING_OPTIMAL,
-- >         VK_IMAGE_USAGE_SAMPLED_BIT |
-- >         VK_IMAGE_USAGE_COLOR_ATTACHMENT_BIT,
-- >         0,
-- >         handleType,
-- >         &properties);
-- >
-- >     if ((result != VK_SUCCESS) ||
-- >         !(properties.externalMemoryFeatures &
-- >           VK_EXTERNAL_MEMORY_FEATURE_IMPORTABLE_BIT_NV)) {
-- >         abort();
-- >     }
-- >
-- >     // Set up the external memory image creation info
-- >     memset(&externalMemoryImageCreateInfo,
-- >            0, sizeof(externalMemoryImageCreateInfo));
-- >     externalMemoryImageCreateInfo.sType =
-- >         VK_STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO_NV;
-- >     externalMemoryImageCreateInfo.handleTypes = handleType;
-- >     // Set up the  core image creation info
-- >     memset(&imageCreateInfo, 0, sizeof(imageCreateInfo));
-- >     imageCreateInfo.sType = VK_STRUCTURE_TYPE_IMAGE_CREATE_INFO;
-- >     imageCreateInfo.pNext = &externalMemoryImageCreateInfo;
-- >     imageCreateInfo.format = format;
-- >     imageCreateInfo.extent.width = 64;
-- >     imageCreateInfo.extent.height = 64;
-- >     imageCreateInfo.extent.depth = 1;
-- >     imageCreateInfo.mipLevels = 1;
-- >     imageCreateInfo.arrayLayers = 1;
-- >     imageCreateInfo.samples = VK_SAMPLE_COUNT_1_BIT;
-- >     imageCreateInfo.tiling = VK_IMAGE_TILING_OPTIMAL;
-- >     imageCreateInfo.usage = VK_IMAGE_USAGE_SAMPLED_BIT |
-- >         VK_IMAGE_USAGE_COLOR_ATTACHMENT_BIT;
-- >     imageCreateInfo.sharingMode = VK_SHARING_MODE_EXCLUSIVE;
-- >     imageCreateInfo.initialLayout = VK_IMAGE_LAYOUT_UNDEFINED;
-- >
-- >     vkCreateImage(device, &imageCreateInfo, NULL, &image);
-- >     vkGetImageMemoryRequirements(device,
-- >                                  image,
-- >                                  &imageMemoryRequirements);
-- >
-- >     // For simplicity, just pick the first compatible memory type.
-- >     for (memoryType = 0; memoryType < numMemoryTypes; memoryType++) {
-- >         if ((1 << memoryType) & imageMemoryRequirements.memoryTypeBits) {
-- >             break;
-- >         }
-- >     }
-- >
-- >     // At least one memory type must be supported given the prior external
-- >     // handle capability check.
-- >     assert(memoryType < numMemoryTypes);
-- >
-- >     // Allocate the external memory object.
-- >     memset(&exportMemoryAllocateInfo, 0, sizeof(exportMemoryAllocateInfo));
-- >     exportMemoryAllocateInfo.sType =
-- >         VK_STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO_NV;
-- >     importMemoryInfo.handleTypes = handleType;
-- >     importMemoryInfo.handle = sharedNtHandle;
-- >
-- >     memset(&memoryAllocateInfo, 0, sizeof(memoryAllocateInfo));
-- >     memoryAllocateInfo.sType = VK_STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO;
-- >     memoryAllocateInfo.pNext = &exportMemoryAllocateInfo;
-- >     memoryAllocateInfo.allocationSize = imageMemoryRequirements.size;
-- >     memoryAllocateInfo.memoryTypeIndex = memoryType;
-- >
-- >     vkAllocateMemory(device, &memoryAllocateInfo, NULL, &mem);
-- >
-- >     vkBindImageMemory(device, image, mem, 0);
-- >
-- >     ...
-- >
-- >     const uint64_t acquireKey = 1;
-- >     const uint32_t timeout = INFINITE;
-- >     const uint64_t releaseKey = 2;
-- >
-- >     VkWin32KeyedMutexAcquireReleaseInfoNV keyedMutex =
-- >         { VK_STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_NV };
-- >     keyedMutex.acquireCount = 1;
-- >     keyedMutex.pAcquireSyncs = &mem;
-- >     keyedMutex.pAcquireKeys = &acquireKey;
-- >     keyedMutex.pAcquireTimeoutMilliseconds = &timeout;
-- >     keyedMutex.releaseCount = 1;
-- >     keyedMutex.pReleaseSyncs = &mem;
-- >     keyedMutex.pReleaseKeys = &releaseKey;
-- >
-- >     VkSubmitInfo submit_info = { VK_STRUCTURE_TYPE_SUBMIT_INFO, &keyedMutex };
-- >     submit_info.commandBufferCount = 1;
-- >     submit_info.pCommandBuffers = &cmd_buf;
-- >     vkQueueSubmit(queue, 1, &submit_info, VK_NULL_HANDLE);
--
-- == Version History
--
-- -   Revision 2, 2016-08-11 (James Jones)
--
--     -   Updated sample code based on the NV external memory extensions.
--
--     -   Renamed from NVX to NV extension.
--
--     -   Added Overview and Description sections.
--
--     -   Updated sample code to use the NV external memory extensions.
--
-- -   Revision 1, 2016-06-14 (Carsten Rohde)
--
--     -   Initial draft.
--
-- == See Also
--
-- 'Win32KeyedMutexAcquireReleaseInfoNV'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_NV_win32_keyed_mutex Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
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 (allocaBytes)
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 Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable(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.Core10.Enums.StructureType (StructureType)
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)
--
-- -   #VUID-VkWin32KeyedMutexAcquireReleaseInfoNV-sType-sType# @sType@
--     /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_NV'
--
-- -   #VUID-VkWin32KeyedMutexAcquireReleaseInfoNV-pAcquireSyncs-parameter#
--     If @acquireCount@ is not @0@, @pAcquireSyncs@ /must/ be a valid
--     pointer to an array of @acquireCount@ valid
--     'Vulkan.Core10.Handles.DeviceMemory' handles
--
-- -   #VUID-VkWin32KeyedMutexAcquireReleaseInfoNV-pAcquireKeys-parameter#
--     If @acquireCount@ is not @0@, @pAcquireKeys@ /must/ be a valid
--     pointer to an array of @acquireCount@ @uint64_t@ values
--
-- -   #VUID-VkWin32KeyedMutexAcquireReleaseInfoNV-pAcquireTimeoutMilliseconds-parameter#
--     If @acquireCount@ is not @0@, @pAcquireTimeoutMilliseconds@ /must/
--     be a valid pointer to an array of @acquireCount@ @uint32_t@ values
--
-- -   #VUID-VkWin32KeyedMutexAcquireReleaseInfoNV-pReleaseSyncs-parameter#
--     If @releaseCount@ is not @0@, @pReleaseSyncs@ /must/ be a valid
--     pointer to an array of @releaseCount@ valid
--     'Vulkan.Core10.Handles.DeviceMemory' handles
--
-- -   #VUID-VkWin32KeyedMutexAcquireReleaseInfoNV-pReleaseKeys-parameter#
--     If @releaseCount@ is not @0@, @pReleaseKeys@ /must/ be a valid
--     pointer to an array of @releaseCount@ @uint64_t@ values
--
-- -   #VUID-VkWin32KeyedMutexAcquireReleaseInfoNV-commonparent# 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
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_win32_keyed_mutex VK_NV_win32_keyed_mutex>,
-- '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 :: forall b.
Win32KeyedMutexAcquireReleaseInfoNV
-> (Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b) -> IO b
withCStruct Win32KeyedMutexAcquireReleaseInfoNV
x Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b
f = Int -> (Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
72 ((Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b) -> IO b)
-> (Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \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 :: forall b.
Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> Win32KeyedMutexAcquireReleaseInfoNV -> IO b -> IO b
pokeCStruct Ptr Win32KeyedMutexAcquireReleaseInfoNV
p Win32KeyedMutexAcquireReleaseInfoNV{Vector Word32
Vector Word64
Vector DeviceMemory
releaseKeys :: Vector Word64
releaseSyncs :: Vector DeviceMemory
acquireTimeoutMilliseconds :: Vector Word32
acquireKeys :: Vector Word64
acquireSyncs :: Vector DeviceMemory
$sel:releaseKeys:Win32KeyedMutexAcquireReleaseInfoNV :: Win32KeyedMutexAcquireReleaseInfoNV -> Vector Word64
$sel:releaseSyncs:Win32KeyedMutexAcquireReleaseInfoNV :: Win32KeyedMutexAcquireReleaseInfoNV -> Vector DeviceMemory
$sel:acquireTimeoutMilliseconds:Win32KeyedMutexAcquireReleaseInfoNV :: Win32KeyedMutexAcquireReleaseInfoNV -> Vector Word32
$sel:acquireKeys:Win32KeyedMutexAcquireReleaseInfoNV :: Win32KeyedMutexAcquireReleaseInfoNV -> Vector Word64
$sel:acquireSyncs:Win32KeyedMutexAcquireReleaseInfoNV :: Win32KeyedMutexAcquireReleaseInfoNV -> Vector DeviceMemory
..} 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` Int
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` Int
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 String
"" String
"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 String
"" String
"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` Int
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
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @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
* Int
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_ (\Int
i 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` (Int
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` Int
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
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @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
* Int
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_ (\Int
i 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` (Int
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` Int
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
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @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
* Int
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_ (\Int
i 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` (Int
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` Int
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 String
"" String
"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` Int
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
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @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
* Int
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_ (\Int
i 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` (Int
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` Int
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
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @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
* Int
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_ (\Int
i 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` (Int
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` Int
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 = Int
72
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr Win32KeyedMutexAcquireReleaseInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr Win32KeyedMutexAcquireReleaseInfoNV
p IO b
f = do
    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` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_NV)
    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` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct Win32KeyedMutexAcquireReleaseInfoNV where
  peekCStruct :: Ptr Win32KeyedMutexAcquireReleaseInfoNV
-> IO Win32KeyedMutexAcquireReleaseInfoNV
peekCStruct Ptr Win32KeyedMutexAcquireReleaseInfoNV
p = do
    Word32
acquireCount <- 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` Int
16 :: Ptr Word32))
    Ptr DeviceMemory
pAcquireSyncs <- 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` Int
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) (\Int
i -> 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` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceMemory)))
    Ptr Word64
pAcquireKeys <- 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` Int
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) (\Int
i -> 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` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word64)))
    Ptr Word32
pAcquireTimeoutMilliseconds <- 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` Int
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) (\Int
i -> 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` (Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    Word32
releaseCount <- 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` Int
48 :: Ptr Word32))
    Ptr DeviceMemory
pReleaseSyncs <- 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` Int
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) (\Int
i -> 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` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceMemory)))
    Ptr Word64
pReleaseKeys <- 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` Int
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) (\Int
i -> 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` (Int
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 :: forall a. Integral a => 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 :: forall a. (Eq a, IsString a) => 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"