{-# language CPP #-}
-- | = Name
--
-- VK_KHR_map_memory2 - device extension
--
-- == VK_KHR_map_memory2
--
-- [__Name String__]
--     @VK_KHR_map_memory2@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     272
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__; __Contact__]
--
--     -   Faith Ekstrand
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_KHR_map_memory2] @gfxstrand%0A*Here describe the issue or question you have about the VK_KHR_map_memory2 extension* >
--
-- [__Extension Proposal__]
--     <https://github.com/KhronosGroup/Vulkan-Docs/tree/main/proposals/VK_KHR_map_memory2.adoc VK_KHR_map_memory2>
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2023-03-14
--
-- [__Interactions and External Dependencies__]
--
--     -   None
--
-- [__Contributors__]
--
--     -   Faith Ekstrand, Collabora
--
--     -   Tobias Hector, AMD
--
-- == Description
--
-- This extension provides extensible versions of the Vulkan memory map and
-- unmap entrypoints. The new entrypoints are functionally identical to the
-- core entrypoints, except that their parameters are specified using
-- extensible structures that can be used to pass extension-specific
-- information.
--
-- == New Commands
--
-- -   'mapMemory2KHR'
--
-- -   'unmapMemory2KHR'
--
-- == New Structures
--
-- -   'MemoryMapInfoKHR'
--
-- -   'MemoryUnmapInfoKHR'
--
-- == New Bitmasks
--
-- -   'MemoryUnmapFlagsKHR'
--
-- == New Enum Constants
--
-- -   'KHR_MAP_MEMORY_2_EXTENSION_NAME'
--
-- -   'KHR_MAP_MEMORY_2_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MEMORY_MAP_INFO_KHR'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MEMORY_UNMAP_INFO_KHR'
--
-- == Version History
--
-- -   Revision 0, 2022-08-03 (Faith Ekstrand)
--
--     -   Internal revisions
--
-- -   Revision 1, 2023-03-14
--
--     -   Public release
--
-- == See Also
--
-- 'MemoryMapInfoKHR', 'MemoryUnmapFlagsKHR', 'MemoryUnmapInfoKHR',
-- 'mapMemory2KHR', 'unmapMemory2KHR'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_KHR_map_memory2 Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_KHR_map_memory2  ( mapMemory2KHR
                                             , unmapMemory2KHR
                                             , MemoryMapInfoKHR(..)
                                             , MemoryUnmapInfoKHR(..)
                                             , MemoryUnmapFlagsKHR(..)
                                             , KHR_MAP_MEMORY_2_SPEC_VERSION
                                             , pattern KHR_MAP_MEMORY_2_SPEC_VERSION
                                             , KHR_MAP_MEMORY_2_EXTENSION_NAME
                                             , pattern KHR_MAP_MEMORY_2_EXTENSION_NAME
                                             ) where

import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showString)
import Numeric (showHex)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkMapMemory2KHR))
import Vulkan.Dynamic (DeviceCmds(pVkUnmapMemory2KHR))
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Enums.MemoryMapFlags (MemoryMapFlags)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_MAP_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_UNMAP_INFO_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkMapMemory2KHR
  :: FunPtr (Ptr Device_T -> Ptr MemoryMapInfoKHR -> Ptr (Ptr ()) -> IO Result) -> Ptr Device_T -> Ptr MemoryMapInfoKHR -> Ptr (Ptr ()) -> IO Result

-- | vkMapMemory2KHR - Map a memory object into application address space
--
-- = Description
--
-- This function behaves identically to 'Vulkan.Core10.Memory.mapMemory'
-- except that it gets its parameters via an extensible structure pointer
-- rather than directly as function arguments.
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_MEMORY_MAP_FAILED'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_map_memory2 VK_KHR_map_memory2>,
-- 'Vulkan.Core10.Handles.Device', 'MemoryMapInfoKHR'
mapMemory2KHR :: forall io
               . (MonadIO io)
              => -- | @device@ is the logical device that owns the memory.
                 --
                 -- #VUID-vkMapMemory2KHR-device-parameter# @device@ /must/ be a valid
                 -- 'Vulkan.Core10.Handles.Device' handle
                 Device
              -> -- | @pMemoryMapInfo@ is a pointer to a 'MemoryMapInfoKHR' structure
                 -- describing parameters of the map.
                 --
                 -- #VUID-vkMapMemory2KHR-pMemoryMapInfo-parameter# @pMemoryMapInfo@ /must/
                 -- be a valid pointer to a valid 'MemoryMapInfoKHR' structure
                 MemoryMapInfoKHR
              -> io (("data" ::: Ptr ()))
mapMemory2KHR :: forall (io :: * -> *).
MonadIO io =>
Device -> MemoryMapInfoKHR -> io ("data" ::: Ptr ())
mapMemory2KHR Device
device MemoryMapInfoKHR
memoryMapInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkMapMemory2KHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR)
   -> ("ppData" ::: Ptr ("data" ::: Ptr ()))
   -> IO Result)
vkMapMemory2KHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR)
      -> ("ppData" ::: Ptr ("data" ::: Ptr ()))
      -> IO Result)
pVkMapMemory2KHR (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR)
   -> ("ppData" ::: Ptr ("data" ::: Ptr ()))
   -> IO Result)
vkMapMemory2KHRPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkMapMemory2KHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkMapMemory2KHR' :: Ptr Device_T
-> ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR)
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result
vkMapMemory2KHR' = FunPtr
  (Ptr Device_T
   -> ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR)
   -> ("ppData" ::: Ptr ("data" ::: Ptr ()))
   -> IO Result)
-> Ptr Device_T
-> ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR)
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result
mkVkMapMemory2KHR FunPtr
  (Ptr Device_T
   -> ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR)
   -> ("ppData" ::: Ptr ("data" ::: Ptr ()))
   -> IO Result)
vkMapMemory2KHRPtr
  "pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
pMemoryMapInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MemoryMapInfoKHR
memoryMapInfo)
  "ppData" ::: Ptr ("data" ::: Ptr ())
pPpData <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @(Ptr ()) Int
8) forall a. Ptr a -> IO ()
free
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkMapMemory2KHR" (Ptr Device_T
-> ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR)
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result
vkMapMemory2KHR'
                                                    (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                    "pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
pMemoryMapInfo
                                                    ("ppData" ::: Ptr ("data" ::: Ptr ())
pPpData))
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  "data" ::: Ptr ()
ppData <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) "ppData" ::: Ptr ("data" ::: Ptr ())
pPpData
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("data" ::: Ptr ()
ppData)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkUnmapMemory2KHR
  :: FunPtr (Ptr Device_T -> Ptr MemoryUnmapInfoKHR -> IO Result) -> Ptr Device_T -> Ptr MemoryUnmapInfoKHR -> IO Result

-- | vkUnmapMemory2KHR - Unmap a previously mapped memory object
--
-- = Description
--
-- This function behaves identically to 'Vulkan.Core10.Memory.unmapMemory'
-- except that it gets its parameters via an extensible structure pointer
-- rather than directly as function arguments.
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_map_memory2 VK_KHR_map_memory2>,
-- 'Vulkan.Core10.Handles.Device', 'MemoryUnmapInfoKHR'
unmapMemory2KHR :: forall io
                 . (MonadIO io)
                => -- | @device@ is the logical device that owns the memory.
                   --
                   -- #VUID-vkUnmapMemory2KHR-device-parameter# @device@ /must/ be a valid
                   -- 'Vulkan.Core10.Handles.Device' handle
                   Device
                -> -- | @pMemoryUnmapInfo@ is a pointer to a 'MemoryUnmapInfoKHR' structure
                   -- describing parameters of the unmap.
                   --
                   -- #VUID-vkUnmapMemory2KHR-pMemoryUnmapInfo-parameter# @pMemoryUnmapInfo@
                   -- /must/ be a valid pointer to a valid 'MemoryUnmapInfoKHR' structure
                   MemoryUnmapInfoKHR
                -> io ()
unmapMemory2KHR :: forall (io :: * -> *).
MonadIO io =>
Device -> MemoryUnmapInfoKHR -> io ()
unmapMemory2KHR Device
device MemoryUnmapInfoKHR
memoryUnmapInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkUnmapMemory2KHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO Result)
vkUnmapMemory2KHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO Result)
pVkUnmapMemory2KHR (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO Result)
vkUnmapMemory2KHRPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkUnmapMemory2KHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkUnmapMemory2KHR' :: Ptr Device_T
-> ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO Result
vkUnmapMemory2KHR' = FunPtr
  (Ptr Device_T
   -> ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO Result)
-> Ptr Device_T
-> ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR)
-> IO Result
mkVkUnmapMemory2KHR FunPtr
  (Ptr Device_T
   -> ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO Result)
vkUnmapMemory2KHRPtr
  "pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
pMemoryUnmapInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MemoryUnmapInfoKHR
memoryUnmapInfo)
  Result
_ <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkUnmapMemory2KHR" (Ptr Device_T
-> ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO Result
vkUnmapMemory2KHR'
                                                      (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                      "pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
pMemoryUnmapInfo)
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()


-- | VkMemoryMapInfoKHR - Structure containing parameters of a memory map
-- operation
--
-- == Valid Usage
--
-- -   #VUID-VkMemoryMapInfoKHR-memory-07958# @memory@ /must/ not be
--     currently host mapped
--
-- -   #VUID-VkMemoryMapInfoKHR-offset-07959# @offset@ /must/ be less than
--     the size of @memory@
--
-- -   #VUID-VkMemoryMapInfoKHR-size-07960# If @size@ is not equal to
--     'Vulkan.Core10.APIConstants.WHOLE_SIZE', @size@ /must/ be greater
--     than @0@
--
-- -   #VUID-VkMemoryMapInfoKHR-size-07961# If @size@ is not equal to
--     'Vulkan.Core10.APIConstants.WHOLE_SIZE', @size@ /must/ be less than
--     or equal to the size of the @memory@ minus @offset@
--
-- -   #VUID-VkMemoryMapInfoKHR-memory-07962# @memory@ /must/ have been
--     created with a memory type that reports
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT'
--
-- -   #VUID-VkMemoryMapInfoKHR-memory-07963# @memory@ /must/ not have been
--     allocated with multiple instances
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkMemoryMapInfoKHR-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MEMORY_MAP_INFO_KHR'
--
-- -   #VUID-VkMemoryMapInfoKHR-pNext-pNext# @pNext@ /must/ be @NULL@
--
-- -   #VUID-VkMemoryMapInfoKHR-flags-zerobitmask# @flags@ /must/ be @0@
--
-- -   #VUID-VkMemoryMapInfoKHR-memory-parameter# @memory@ /must/ be a
--     valid 'Vulkan.Core10.Handles.DeviceMemory' handle
--
-- == Host Synchronization
--
-- -   Host access to @memory@ /must/ be externally synchronized
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_map_memory2 VK_KHR_map_memory2>,
-- 'Vulkan.Core10.Handles.DeviceMemory',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.MemoryMapFlags.MemoryMapFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'mapMemory2KHR'
data MemoryMapInfoKHR = MemoryMapInfoKHR
  { -- | @flags@ is reserved for future use.
    MemoryMapInfoKHR -> MemoryMapFlags
flags :: MemoryMapFlags
  , -- | @memory@ is the 'Vulkan.Core10.Handles.DeviceMemory' object to be
    -- mapped.
    MemoryMapInfoKHR -> DeviceMemory
memory :: DeviceMemory
  , -- | @offset@ is a zero-based byte offset from the beginning of the memory
    -- object.
    MemoryMapInfoKHR -> DeviceSize
offset :: DeviceSize
  , -- | @size@ is the size of the memory range to map, or
    -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE' to map from @offset@ to the end
    -- of the allocation.
    MemoryMapInfoKHR -> DeviceSize
size :: DeviceSize
  }
  deriving (Typeable, MemoryMapInfoKHR -> MemoryMapInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryMapInfoKHR -> MemoryMapInfoKHR -> Bool
$c/= :: MemoryMapInfoKHR -> MemoryMapInfoKHR -> Bool
== :: MemoryMapInfoKHR -> MemoryMapInfoKHR -> Bool
$c== :: MemoryMapInfoKHR -> MemoryMapInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryMapInfoKHR)
#endif
deriving instance Show MemoryMapInfoKHR

instance ToCStruct MemoryMapInfoKHR where
  withCStruct :: forall b.
MemoryMapInfoKHR
-> (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR) -> IO b) -> IO b
withCStruct MemoryMapInfoKHR
x ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \"pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p MemoryMapInfoKHR
x (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR) -> IO b
f "pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p)
  pokeCStruct :: forall b.
("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR)
-> MemoryMapInfoKHR -> IO b -> IO b
pokeCStruct "pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p MemoryMapInfoKHR{DeviceSize
MemoryMapFlags
DeviceMemory
size :: DeviceSize
offset :: DeviceSize
memory :: DeviceMemory
flags :: MemoryMapFlags
$sel:size:MemoryMapInfoKHR :: MemoryMapInfoKHR -> DeviceSize
$sel:offset:MemoryMapInfoKHR :: MemoryMapInfoKHR -> DeviceSize
$sel:memory:MemoryMapInfoKHR :: MemoryMapInfoKHR -> DeviceMemory
$sel:flags:MemoryMapInfoKHR :: MemoryMapInfoKHR -> MemoryMapFlags
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_MAP_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MemoryMapFlags)) (MemoryMapFlags
flags)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceMemory)) (DeviceMemory
memory)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) (DeviceSize
offset)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize)) (DeviceSize
size)
    IO b
f
  cStructSize :: Int
cStructSize = Int
48
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR) -> IO b -> IO b
pokeZeroCStruct "pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_MAP_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceMemory)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct MemoryMapInfoKHR where
  peekCStruct :: ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR) -> IO MemoryMapInfoKHR
peekCStruct "pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p = do
    MemoryMapFlags
flags <- forall a. Storable a => Ptr a -> IO a
peek @MemoryMapFlags (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MemoryMapFlags))
    DeviceMemory
memory <- forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceMemory))
    DeviceSize
offset <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize))
    DeviceSize
size <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ MemoryMapFlags
-> DeviceMemory -> DeviceSize -> DeviceSize -> MemoryMapInfoKHR
MemoryMapInfoKHR
             MemoryMapFlags
flags DeviceMemory
memory DeviceSize
offset DeviceSize
size

instance Storable MemoryMapInfoKHR where
  sizeOf :: MemoryMapInfoKHR -> Int
sizeOf ~MemoryMapInfoKHR
_ = Int
48
  alignment :: MemoryMapInfoKHR -> Int
alignment ~MemoryMapInfoKHR
_ = Int
8
  peek :: ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR) -> IO MemoryMapInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR)
-> MemoryMapInfoKHR -> IO ()
poke "pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
ptr MemoryMapInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryMapInfo" ::: Ptr MemoryMapInfoKHR
ptr MemoryMapInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero MemoryMapInfoKHR where
  zero :: MemoryMapInfoKHR
zero = MemoryMapFlags
-> DeviceMemory -> DeviceSize -> DeviceSize -> MemoryMapInfoKHR
MemoryMapInfoKHR
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkMemoryUnmapInfoKHR - Structure containing parameters of a memory unmap
-- operation
--
-- == Valid Usage
--
-- -   #VUID-VkMemoryUnmapInfoKHR-memory-07964# @memory@ /must/ be
--     currently host mapped
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkMemoryUnmapInfoKHR-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MEMORY_UNMAP_INFO_KHR'
--
-- -   #VUID-VkMemoryUnmapInfoKHR-pNext-pNext# @pNext@ /must/ be @NULL@
--
-- -   #VUID-VkMemoryUnmapInfoKHR-flags-zerobitmask# @flags@ /must/ be @0@
--
-- -   #VUID-VkMemoryUnmapInfoKHR-memory-parameter# @memory@ /must/ be a
--     valid 'Vulkan.Core10.Handles.DeviceMemory' handle
--
-- == Host Synchronization
--
-- -   Host access to @memory@ /must/ be externally synchronized
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_map_memory2 VK_KHR_map_memory2>,
-- 'Vulkan.Core10.Handles.DeviceMemory', 'MemoryUnmapFlagsKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'unmapMemory2KHR'
data MemoryUnmapInfoKHR = MemoryUnmapInfoKHR
  { -- | @flags@ is reserved for future use.
    MemoryUnmapInfoKHR -> MemoryUnmapFlagsKHR
flags :: MemoryUnmapFlagsKHR
  , -- | @memory@ is the 'Vulkan.Core10.Handles.DeviceMemory' object to be
    -- unmapped.
    MemoryUnmapInfoKHR -> DeviceMemory
memory :: DeviceMemory
  }
  deriving (Typeable, MemoryUnmapInfoKHR -> MemoryUnmapInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryUnmapInfoKHR -> MemoryUnmapInfoKHR -> Bool
$c/= :: MemoryUnmapInfoKHR -> MemoryUnmapInfoKHR -> Bool
== :: MemoryUnmapInfoKHR -> MemoryUnmapInfoKHR -> Bool
$c== :: MemoryUnmapInfoKHR -> MemoryUnmapInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryUnmapInfoKHR)
#endif
deriving instance Show MemoryUnmapInfoKHR

instance ToCStruct MemoryUnmapInfoKHR where
  withCStruct :: forall b.
MemoryUnmapInfoKHR
-> (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO b)
-> IO b
withCStruct MemoryUnmapInfoKHR
x ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p MemoryUnmapInfoKHR
x (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO b
f "pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p)
  pokeCStruct :: forall b.
("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR)
-> MemoryUnmapInfoKHR -> IO b -> IO b
pokeCStruct "pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p MemoryUnmapInfoKHR{DeviceMemory
MemoryUnmapFlagsKHR
memory :: DeviceMemory
flags :: MemoryUnmapFlagsKHR
$sel:memory:MemoryUnmapInfoKHR :: MemoryUnmapInfoKHR -> DeviceMemory
$sel:flags:MemoryUnmapInfoKHR :: MemoryUnmapInfoKHR -> MemoryUnmapFlagsKHR
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_UNMAP_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MemoryUnmapFlagsKHR)) (MemoryUnmapFlagsKHR
flags)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceMemory)) (DeviceMemory
memory)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR) -> IO b -> IO b
pokeZeroCStruct "pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_UNMAP_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceMemory)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct MemoryUnmapInfoKHR where
  peekCStruct :: ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR)
-> IO MemoryUnmapInfoKHR
peekCStruct "pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p = do
    MemoryUnmapFlagsKHR
flags <- forall a. Storable a => Ptr a -> IO a
peek @MemoryUnmapFlagsKHR (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MemoryUnmapFlagsKHR))
    DeviceMemory
memory <- forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory (("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceMemory))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ MemoryUnmapFlagsKHR -> DeviceMemory -> MemoryUnmapInfoKHR
MemoryUnmapInfoKHR
             MemoryUnmapFlagsKHR
flags DeviceMemory
memory

instance Storable MemoryUnmapInfoKHR where
  sizeOf :: MemoryUnmapInfoKHR -> Int
sizeOf ~MemoryUnmapInfoKHR
_ = Int
32
  alignment :: MemoryUnmapInfoKHR -> Int
alignment ~MemoryUnmapInfoKHR
_ = Int
8
  peek :: ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR)
-> IO MemoryUnmapInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR)
-> MemoryUnmapInfoKHR -> IO ()
poke "pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
ptr MemoryUnmapInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryUnmapInfo" ::: Ptr MemoryUnmapInfoKHR
ptr MemoryUnmapInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero MemoryUnmapInfoKHR where
  zero :: MemoryUnmapInfoKHR
zero = MemoryUnmapFlagsKHR -> DeviceMemory -> MemoryUnmapInfoKHR
MemoryUnmapInfoKHR
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkMemoryUnmapFlagsKHR - Reserved for future use
--
-- = Description
--
-- @VkMemoryMapFlagsKHR@ is a bitmask type for setting a mask, but is
-- currently reserved for future use.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_map_memory2 VK_KHR_map_memory2>,
-- 'MemoryUnmapInfoKHR'
newtype MemoryUnmapFlagsKHR = MemoryUnmapFlagsKHR Flags
  deriving newtype (MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
$c/= :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
== :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
$c== :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
Eq, Eq MemoryUnmapFlagsKHR
MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Ordering
MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
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
min :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
$cmin :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
max :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
$cmax :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
>= :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
$c>= :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
> :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
$c> :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
<= :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
$c<= :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
< :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
$c< :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Bool
compare :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Ordering
$ccompare :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> Ordering
Ord, Ptr MemoryUnmapFlagsKHR -> IO MemoryUnmapFlagsKHR
Ptr MemoryUnmapFlagsKHR -> Int -> IO MemoryUnmapFlagsKHR
Ptr MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR -> IO ()
Ptr MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> IO ()
MemoryUnmapFlagsKHR -> Int
forall b. Ptr b -> Int -> IO MemoryUnmapFlagsKHR
forall b. Ptr b -> Int -> MemoryUnmapFlagsKHR -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> IO ()
$cpoke :: Ptr MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> IO ()
peek :: Ptr MemoryUnmapFlagsKHR -> IO MemoryUnmapFlagsKHR
$cpeek :: Ptr MemoryUnmapFlagsKHR -> IO MemoryUnmapFlagsKHR
pokeByteOff :: forall b. Ptr b -> Int -> MemoryUnmapFlagsKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MemoryUnmapFlagsKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO MemoryUnmapFlagsKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MemoryUnmapFlagsKHR
pokeElemOff :: Ptr MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR -> IO ()
$cpokeElemOff :: Ptr MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR -> IO ()
peekElemOff :: Ptr MemoryUnmapFlagsKHR -> Int -> IO MemoryUnmapFlagsKHR
$cpeekElemOff :: Ptr MemoryUnmapFlagsKHR -> Int -> IO MemoryUnmapFlagsKHR
alignment :: MemoryUnmapFlagsKHR -> Int
$calignment :: MemoryUnmapFlagsKHR -> Int
sizeOf :: MemoryUnmapFlagsKHR -> Int
$csizeOf :: MemoryUnmapFlagsKHR -> Int
Storable, MemoryUnmapFlagsKHR
forall a. a -> Zero a
zero :: MemoryUnmapFlagsKHR
$czero :: MemoryUnmapFlagsKHR
Zero, Eq MemoryUnmapFlagsKHR
MemoryUnmapFlagsKHR
Int -> MemoryUnmapFlagsKHR
MemoryUnmapFlagsKHR -> Bool
MemoryUnmapFlagsKHR -> Int
MemoryUnmapFlagsKHR -> Maybe Int
MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
MemoryUnmapFlagsKHR -> Int -> Bool
MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
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
popCount :: MemoryUnmapFlagsKHR -> Int
$cpopCount :: MemoryUnmapFlagsKHR -> Int
rotateR :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$crotateR :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
rotateL :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$crotateL :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
unsafeShiftR :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$cunsafeShiftR :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
shiftR :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$cshiftR :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
unsafeShiftL :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$cunsafeShiftL :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
shiftL :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$cshiftL :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
isSigned :: MemoryUnmapFlagsKHR -> Bool
$cisSigned :: MemoryUnmapFlagsKHR -> Bool
bitSize :: MemoryUnmapFlagsKHR -> Int
$cbitSize :: MemoryUnmapFlagsKHR -> Int
bitSizeMaybe :: MemoryUnmapFlagsKHR -> Maybe Int
$cbitSizeMaybe :: MemoryUnmapFlagsKHR -> Maybe Int
testBit :: MemoryUnmapFlagsKHR -> Int -> Bool
$ctestBit :: MemoryUnmapFlagsKHR -> Int -> Bool
complementBit :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$ccomplementBit :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
clearBit :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$cclearBit :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
setBit :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$csetBit :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
bit :: Int -> MemoryUnmapFlagsKHR
$cbit :: Int -> MemoryUnmapFlagsKHR
zeroBits :: MemoryUnmapFlagsKHR
$czeroBits :: MemoryUnmapFlagsKHR
rotate :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$crotate :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
shift :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
$cshift :: MemoryUnmapFlagsKHR -> Int -> MemoryUnmapFlagsKHR
complement :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
$ccomplement :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
xor :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
$cxor :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
.|. :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
$c.|. :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
.&. :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
$c.&. :: MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR -> MemoryUnmapFlagsKHR
Bits, Bits MemoryUnmapFlagsKHR
MemoryUnmapFlagsKHR -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: MemoryUnmapFlagsKHR -> Int
$ccountTrailingZeros :: MemoryUnmapFlagsKHR -> Int
countLeadingZeros :: MemoryUnmapFlagsKHR -> Int
$ccountLeadingZeros :: MemoryUnmapFlagsKHR -> Int
finiteBitSize :: MemoryUnmapFlagsKHR -> Int
$cfiniteBitSize :: MemoryUnmapFlagsKHR -> Int
FiniteBits)

conNameMemoryUnmapFlagsKHR :: String
conNameMemoryUnmapFlagsKHR :: String
conNameMemoryUnmapFlagsKHR = String
"MemoryUnmapFlagsKHR"

enumPrefixMemoryUnmapFlagsKHR :: String
enumPrefixMemoryUnmapFlagsKHR :: String
enumPrefixMemoryUnmapFlagsKHR = String
""

showTableMemoryUnmapFlagsKHR :: [(MemoryUnmapFlagsKHR, String)]
showTableMemoryUnmapFlagsKHR :: [(MemoryUnmapFlagsKHR, String)]
showTableMemoryUnmapFlagsKHR = []

instance Show MemoryUnmapFlagsKHR where
  showsPrec :: Int -> MemoryUnmapFlagsKHR -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixMemoryUnmapFlagsKHR
      [(MemoryUnmapFlagsKHR, String)]
showTableMemoryUnmapFlagsKHR
      String
conNameMemoryUnmapFlagsKHR
      (\(MemoryUnmapFlagsKHR Flags
x) -> Flags
x)
      (\Flags
x -> String -> ShowS
showString String
"0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read MemoryUnmapFlagsKHR where
  readPrec :: ReadPrec MemoryUnmapFlagsKHR
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixMemoryUnmapFlagsKHR
      [(MemoryUnmapFlagsKHR, String)]
showTableMemoryUnmapFlagsKHR
      String
conNameMemoryUnmapFlagsKHR
      Flags -> MemoryUnmapFlagsKHR
MemoryUnmapFlagsKHR

type KHR_MAP_MEMORY_2_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_KHR_MAP_MEMORY_2_SPEC_VERSION"
pattern KHR_MAP_MEMORY_2_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_MAP_MEMORY_2_SPEC_VERSION :: forall a. Integral a => a
$mKHR_MAP_MEMORY_2_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_MAP_MEMORY_2_SPEC_VERSION = 1


type KHR_MAP_MEMORY_2_EXTENSION_NAME = "VK_KHR_map_memory2"

-- No documentation found for TopLevel "VK_KHR_MAP_MEMORY_2_EXTENSION_NAME"
pattern KHR_MAP_MEMORY_2_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_MAP_MEMORY_2_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mKHR_MAP_MEMORY_2_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_MAP_MEMORY_2_EXTENSION_NAME = "VK_KHR_map_memory2"