{-# language CPP #-}
module Vulkan.Core11.Promoted_From_VK_KHR_bind_memory2  ( bindBufferMemory2
                                                        , bindImageMemory2
                                                        , BindBufferMemoryInfo(..)
                                                        , BindImageMemoryInfo(..)
                                                        , StructureType(..)
                                                        , ImageCreateFlagBits(..)
                                                        , ImageCreateFlags
                                                        ) where

import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
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 (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.NamedType ((:::))
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2 (BindBufferMemoryDeviceGroupInfo)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2 (BindImageMemoryDeviceGroupInfo)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_swapchain (BindImageMemorySwapchainInfoKHR)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion (BindImagePlaneMemoryInfo)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkBindBufferMemory2))
import Vulkan.Dynamic (DeviceCmds(pVkBindImageMemory2))
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (Image)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BIND_BUFFER_MEMORY_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BIND_IMAGE_MEMORY_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlagBits(..))
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlags)
import Vulkan.Core10.Enums.StructureType (StructureType(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkBindBufferMemory2
  :: FunPtr (Ptr Device_T -> Word32 -> Ptr (SomeStruct BindBufferMemoryInfo) -> IO Result) -> Ptr Device_T -> Word32 -> Ptr (SomeStruct BindBufferMemoryInfo) -> IO Result

-- | vkBindBufferMemory2 - Bind device memory to buffer objects
--
-- = Description
--
-- On some implementations, it /may/ be more efficient to batch memory
-- bindings into a single command.
--
-- == 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.Extensions.VK_KHR_buffer_device_address.ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS_KHR'
--
-- = See Also
--
-- 'BindBufferMemoryInfo', 'Vulkan.Core10.Handles.Device'
bindBufferMemory2 :: forall io
                   . (MonadIO io)
                  => -- | @device@ is the logical device that owns the buffers and memory.
                     --
                     -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                     Device
                  -> -- | @pBindInfos@ is a pointer to an array of @bindInfoCount@
                     -- 'BindBufferMemoryInfo' structures describing buffers and memory to bind.
                     --
                     -- @pBindInfos@ /must/ be a valid pointer to an array of @bindInfoCount@
                     -- valid 'BindBufferMemoryInfo' structures
                     ("bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo))
                  -> io ()
bindBufferMemory2 :: Device
-> ("bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo))
-> io ()
bindBufferMemory2 device :: Device
device bindInfos :: "bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo)
bindInfos = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkBindBufferMemory2Ptr :: FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
   -> IO Result)
vkBindBufferMemory2Ptr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
      -> IO Result)
pVkBindBufferMemory2 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
   -> IO Result)
vkBindBufferMemory2Ptr FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (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 "" "The function pointer for vkBindBufferMemory2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkBindBufferMemory2' :: Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
-> IO Result
vkBindBufferMemory2' = FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
   -> IO Result)
-> Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
-> IO Result
mkVkBindBufferMemory2 FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
   -> IO Result)
vkBindBufferMemory2Ptr
  Ptr (BindBufferMemoryInfo Any)
pPBindInfos <- ((Ptr (BindBufferMemoryInfo Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (BindBufferMemoryInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (BindBufferMemoryInfo Any) -> IO ()) -> IO ())
 -> ContT () IO (Ptr (BindBufferMemoryInfo Any)))
-> ((Ptr (BindBufferMemoryInfo Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (BindBufferMemoryInfo Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (BindBufferMemoryInfo Any) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(BindBufferMemoryInfo _) ((("bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo)) -> Int
forall a. Vector a -> Int
Data.Vector.length ("bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo)
bindInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
  (Int -> SomeStruct BindBufferMemoryInfo -> ContT () IO ())
-> ("bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo))
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct BindBufferMemoryInfo
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
-> SomeStruct BindBufferMemoryInfo -> IO () -> IO ()
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (BindBufferMemoryInfo Any)
-> "pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (BindBufferMemoryInfo Any)
pPBindInfos Ptr (BindBufferMemoryInfo Any)
-> Int -> Ptr (BindBufferMemoryInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (BindBufferMemoryInfo _))) (SomeStruct BindBufferMemoryInfo
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo)
bindInfos)
  Result
r <- IO Result -> ContT () IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT () IO Result)
-> IO Result -> ContT () IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo))
-> IO Result
vkBindBufferMemory2' (Device -> Ptr Device_T
deviceHandle (Device
device)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo)) -> Int
forall a. Vector a -> Int
Data.Vector.length (("bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo)) -> Int)
-> ("bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo))
-> Int
forall a b. (a -> b) -> a -> b
$ ("bindInfos" ::: Vector (SomeStruct BindBufferMemoryInfo)
bindInfos)) :: Word32)) (Ptr (BindBufferMemoryInfo Any)
-> "pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (BindBufferMemoryInfo Any)
pPBindInfos))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkBindImageMemory2
  :: FunPtr (Ptr Device_T -> Word32 -> Ptr (SomeStruct BindImageMemoryInfo) -> IO Result) -> Ptr Device_T -> Word32 -> Ptr (SomeStruct BindImageMemoryInfo) -> IO Result

-- | vkBindImageMemory2 - Bind device memory to image objects
--
-- = Description
--
-- On some implementations, it /may/ be more efficient to batch memory
-- bindings into a single command.
--
-- == Valid Usage
--
-- -   If any 'BindImageMemoryInfo'::image was created with
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_DISJOINT_BIT'
--     then all planes of 'BindImageMemoryInfo'::image /must/ be bound
--     individually in separate @pBindInfos@
--
-- -   @pBindInfos@ /must/ not refer to the same image subresource more
--     than once
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pBindInfos@ /must/ be a valid pointer to an array of
--     @bindInfoCount@ valid 'BindImageMemoryInfo' structures
--
-- -   @bindInfoCount@ /must/ be greater than @0@
--
-- == 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'
--
-- = See Also
--
-- 'BindImageMemoryInfo', 'Vulkan.Core10.Handles.Device'
bindImageMemory2 :: forall io
                  . (MonadIO io)
                 => -- | @device@ is the logical device that owns the images and memory.
                    Device
                 -> -- | @pBindInfos@ is a pointer to an array of 'BindImageMemoryInfo'
                    -- structures, describing images and memory to bind.
                    ("bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo))
                 -> io ()
bindImageMemory2 :: Device
-> ("bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo))
-> io ()
bindImageMemory2 device :: Device
device bindInfos :: "bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo)
bindInfos = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkBindImageMemory2Ptr :: FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
   -> IO Result)
vkBindImageMemory2Ptr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
      -> IO Result)
pVkBindImageMemory2 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
   -> IO Result)
vkBindImageMemory2Ptr FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (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 "" "The function pointer for vkBindImageMemory2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkBindImageMemory2' :: Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
-> IO Result
vkBindImageMemory2' = FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
   -> IO Result)
-> Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
-> IO Result
mkVkBindImageMemory2 FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
   -> IO Result)
vkBindImageMemory2Ptr
  Ptr (BindImageMemoryInfo Any)
pPBindInfos <- ((Ptr (BindImageMemoryInfo Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (BindImageMemoryInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (BindImageMemoryInfo Any) -> IO ()) -> IO ())
 -> ContT () IO (Ptr (BindImageMemoryInfo Any)))
-> ((Ptr (BindImageMemoryInfo Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (BindImageMemoryInfo Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (BindImageMemoryInfo Any) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(BindImageMemoryInfo _) ((("bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo)) -> Int
forall a. Vector a -> Int
Data.Vector.length ("bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo)
bindInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
  (Int -> SomeStruct BindImageMemoryInfo -> ContT () IO ())
-> ("bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo))
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct BindImageMemoryInfo
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
-> SomeStruct BindImageMemoryInfo -> IO () -> IO ()
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (BindImageMemoryInfo Any)
-> "pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (BindImageMemoryInfo Any)
pPBindInfos Ptr (BindImageMemoryInfo Any) -> Int -> Ptr (BindImageMemoryInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (BindImageMemoryInfo _))) (SomeStruct BindImageMemoryInfo
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo)
bindInfos)
  Result
r <- IO Result -> ContT () IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT () IO Result)
-> IO Result -> ContT () IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo))
-> IO Result
vkBindImageMemory2' (Device -> Ptr Device_T
deviceHandle (Device
device)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo)) -> Int
forall a. Vector a -> Int
Data.Vector.length (("bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo)) -> Int)
-> ("bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo)) -> Int
forall a b. (a -> b) -> a -> b
$ ("bindInfos" ::: Vector (SomeStruct BindImageMemoryInfo)
bindInfos)) :: Word32)) (Ptr (BindImageMemoryInfo Any)
-> "pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (BindImageMemoryInfo Any)
pPBindInfos))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))


-- | VkBindBufferMemoryInfo - Structure specifying how to bind a buffer to
-- memory
--
-- == Valid Usage
--
-- -   @buffer@ /must/ not already be backed by a memory object
--
-- -   @buffer@ /must/ not have been created with any sparse memory binding
--     flags
--
-- -   @memoryOffset@ /must/ be less than the size of @memory@
--
-- -   @memory@ /must/ have been allocated using one of the memory types
--     allowed in the @memoryTypeBits@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'Vulkan.Core10.MemoryManagement.getBufferMemoryRequirements' with
--     @buffer@
--
-- -   @memoryOffset@ /must/ be an integer multiple of the @alignment@
--     member of the 'Vulkan.Core10.MemoryManagement.MemoryRequirements'
--     structure returned from a call to
--     'Vulkan.Core10.MemoryManagement.getBufferMemoryRequirements' with
--     @buffer@
--
-- -   The @size@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'Vulkan.Core10.MemoryManagement.getBufferMemoryRequirements' with
--     @buffer@ /must/ be less than or equal to the size of @memory@ minus
--     @memoryOffset@
--
-- -   If @buffer@ requires a dedicated allocation(as reported by
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getBufferMemoryRequirements2'
--     in
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedRequirements'::requiresDedicatedAllocation
--     for @buffer@), @memory@ /must/ have been created with
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@buffer@
--     equal to @buffer@ and @memoryOffset@ /must/ be zero
--
-- -   If the 'Vulkan.Core10.Memory.MemoryAllocateInfo' provided when
--     @memory@ was allocated included a
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'
--     structure in its @pNext@ chain, and
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@buffer@
--     was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then @buffer@
--     /must/ equal
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@buffer@
--     and @memoryOffset@ /must/ be zero
--
-- -   If @buffer@ was created with the
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_PROTECTED_BIT'
--     bit set, the buffer /must/ be bound to a memory object allocated
--     with a memory type that reports
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_PROTECTED_BIT'
--
-- -   If @buffer@ was created with the
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_PROTECTED_BIT'
--     bit not set, the buffer /must/ not be bound to a memory object
--     created with a memory type that reports
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_PROTECTED_BIT'
--
-- -   If @buffer@ was created with
--     'Vulkan.Extensions.VK_NV_dedicated_allocation.DedicatedAllocationBufferCreateInfoNV'::@dedicatedAllocation@
--     equal to 'Vulkan.Core10.FundamentalTypes.TRUE', @memory@ /must/ have
--     been created with
--     'Vulkan.Extensions.VK_NV_dedicated_allocation.DedicatedAllocationMemoryAllocateInfoNV'::@buffer@
--     equal to @buffer@ and @memoryOffset@ /must/ be zero
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindBufferMemoryDeviceGroupInfo'
--     structure, all instances of @memory@ specified by
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindBufferMemoryDeviceGroupInfo'::@pDeviceIndices@
--     /must/ have been allocated
--
-- -   If the value of
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExportMemoryAllocateInfo'::@handleTypes@
--     used to allocate @memory@ is not @0@, it /must/ include at least one
--     of the handles set in
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExternalMemoryBufferCreateInfo'::@handleTypes@
--     when @buffer@ was created
--
-- -   If @memory@ was created by a memory import operation, that is not
--     'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ImportAndroidHardwareBufferInfoANDROID'
--     with a non-@NULL@ @buffer@ value, the external handle type of the
--     imported memory /must/ also have been set in
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExternalMemoryBufferCreateInfo'::@handleTypes@
--     when @buffer@ was created
--
-- -   If @memory@ was created with the
--     'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ImportAndroidHardwareBufferInfoANDROID'
--     memory import operation with a non-@NULL@ @buffer@ value,
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID'
--     /must/ also have been set in
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExternalMemoryBufferCreateInfo'::@handleTypes@
--     when @buffer@ was created
--
-- -   If the
--     'Vulkan.Extensions.VK_KHR_buffer_device_address.PhysicalDeviceBufferDeviceAddressFeaturesKHR'::@bufferDeviceAddress@
--     feature is enabled and @buffer@ was created with the
--     'Vulkan.Extensions.VK_KHR_buffer_device_address.BUFFER_USAGE_SHADER_DEVICE_ADDRESS_BIT_KHR'
--     bit set, @memory@ /must/ have been allocated with the
--     'Vulkan.Extensions.VK_KHR_buffer_device_address.MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT_KHR'
--     bit set
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_BIND_BUFFER_MEMORY_INFO'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindBufferMemoryDeviceGroupInfo'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   @memory@ /must/ be a valid 'Vulkan.Core10.Handles.DeviceMemory'
--     handle
--
-- -   Both of @buffer@, and @memory@ /must/ have been created, allocated,
--     or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.DeviceMemory',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'bindBufferMemory2',
-- 'Vulkan.Extensions.VK_KHR_bind_memory2.bindBufferMemory2KHR'
data BindBufferMemoryInfo (es :: [Type]) = BindBufferMemoryInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    BindBufferMemoryInfo es -> Chain es
next :: Chain es
  , -- | @buffer@ is the buffer to be attached to memory.
    BindBufferMemoryInfo es -> Buffer
buffer :: Buffer
  , -- | @memory@ is a 'Vulkan.Core10.Handles.DeviceMemory' object describing the
    -- device memory to attach.
    BindBufferMemoryInfo es -> DeviceMemory
memory :: DeviceMemory
  , -- | @memoryOffset@ is the start offset of the region of @memory@ which is to
    -- be bound to the buffer. The number of bytes returned in the
    -- 'Vulkan.Core10.MemoryManagement.MemoryRequirements'::@size@ member in
    -- @memory@, starting from @memoryOffset@ bytes, will be bound to the
    -- specified buffer.
    BindBufferMemoryInfo es -> DeviceSize
memoryOffset :: DeviceSize
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BindBufferMemoryInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (BindBufferMemoryInfo es)

instance Extensible BindBufferMemoryInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_BIND_BUFFER_MEMORY_INFO
  setNext :: BindBufferMemoryInfo ds -> Chain es -> BindBufferMemoryInfo es
setNext x :: BindBufferMemoryInfo ds
x next :: Chain es
next = BindBufferMemoryInfo ds
x{$sel:next:BindBufferMemoryInfo :: Chain es
next = Chain es
next}
  getNext :: BindBufferMemoryInfo es -> Chain es
getNext BindBufferMemoryInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends BindBufferMemoryInfo e => b) -> Maybe b
  extends :: proxy e -> (Extends BindBufferMemoryInfo e => b) -> Maybe b
extends _ f :: Extends BindBufferMemoryInfo e => b
f
    | Just Refl <- (Typeable e, Typeable BindBufferMemoryDeviceGroupInfo) =>
Maybe (e :~: BindBufferMemoryDeviceGroupInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @BindBufferMemoryDeviceGroupInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends BindBufferMemoryInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss BindBufferMemoryInfo es, PokeChain es) => ToCStruct (BindBufferMemoryInfo es) where
  withCStruct :: BindBufferMemoryInfo es
-> (Ptr (BindBufferMemoryInfo es) -> IO b) -> IO b
withCStruct x :: BindBufferMemoryInfo es
x f :: Ptr (BindBufferMemoryInfo es) -> IO b
f = Int -> Int -> (Ptr (BindBufferMemoryInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr (BindBufferMemoryInfo es) -> IO b) -> IO b)
-> (Ptr (BindBufferMemoryInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (BindBufferMemoryInfo es)
p -> Ptr (BindBufferMemoryInfo es)
-> BindBufferMemoryInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (BindBufferMemoryInfo es)
p BindBufferMemoryInfo es
x (Ptr (BindBufferMemoryInfo es) -> IO b
f Ptr (BindBufferMemoryInfo es)
p)
  pokeCStruct :: Ptr (BindBufferMemoryInfo es)
-> BindBufferMemoryInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (BindBufferMemoryInfo es)
p BindBufferMemoryInfo{..} 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 (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BIND_BUFFER_MEMORY_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Buffer)) (Buffer
buffer)
    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 DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceMemory)) (DeviceMemory
memory)
    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 DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) (DeviceSize
memoryOffset)
    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 = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (BindBufferMemoryInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (BindBufferMemoryInfo es)
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 (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BIND_BUFFER_MEMORY_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Buffer)) (Buffer
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceMemory)) (DeviceMemory
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss BindBufferMemoryInfo es, PeekChain es) => FromCStruct (BindBufferMemoryInfo es) where
  peekCStruct :: Ptr (BindBufferMemoryInfo es) -> IO (BindBufferMemoryInfo es)
peekCStruct p :: Ptr (BindBufferMemoryInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    Buffer
buffer <- Ptr Buffer -> IO Buffer
forall a. Storable a => Ptr a -> IO a
peek @Buffer ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Buffer))
    DeviceMemory
memory <- Ptr DeviceMemory -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceMemory))
    DeviceSize
memoryOffset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr (BindBufferMemoryInfo es)
p Ptr (BindBufferMemoryInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize))
    BindBufferMemoryInfo es -> IO (BindBufferMemoryInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BindBufferMemoryInfo es -> IO (BindBufferMemoryInfo es))
-> BindBufferMemoryInfo es -> IO (BindBufferMemoryInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> Buffer -> DeviceMemory -> DeviceSize -> BindBufferMemoryInfo es
forall (es :: [*]).
Chain es
-> Buffer -> DeviceMemory -> DeviceSize -> BindBufferMemoryInfo es
BindBufferMemoryInfo
             Chain es
next Buffer
buffer DeviceMemory
memory DeviceSize
memoryOffset

instance es ~ '[] => Zero (BindBufferMemoryInfo es) where
  zero :: BindBufferMemoryInfo es
zero = Chain es
-> Buffer -> DeviceMemory -> DeviceSize -> BindBufferMemoryInfo es
forall (es :: [*]).
Chain es
-> Buffer -> DeviceMemory -> DeviceSize -> BindBufferMemoryInfo es
BindBufferMemoryInfo
           ()
           Buffer
forall a. Zero a => a
zero
           DeviceMemory
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero


-- | VkBindImageMemoryInfo - Structure specifying how to bind an image to
-- memory
--
-- == Valid Usage
--
-- -   @image@ /must/ not already be backed by a memory object
--
-- -   @image@ /must/ not have been created with any sparse memory binding
--     flags
--
-- -   @memoryOffset@ /must/ be less than the size of @memory@
--
-- -   If the @pNext@ chain does not include a
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'
--     structure, @memory@ /must/ have been allocated using one of the
--     memory types allowed in the @memoryTypeBits@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getImageMemoryRequirements2'
--     with @image@
--
-- -   If the @pNext@ chain does not include a
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'
--     structure, @memoryOffset@ /must/ be an integer multiple of the
--     @alignment@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getImageMemoryRequirements2'
--     with @image@
--
-- -   If the @pNext@ chain does not include a
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'
--     structure, the difference of the size of @memory@ and @memoryOffset@
--     /must/ be greater than or equal to the @size@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getImageMemoryRequirements2'
--     with the same @image@
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'
--     structure, @image@ /must/ have been created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_DISJOINT_BIT'
--     bit set
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'
--     structure, @memory@ /must/ have been allocated using one of the
--     memory types allowed in the @memoryTypeBits@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getImageMemoryRequirements2'
--     with @image@ and where
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'::@planeAspect@
--     corresponds to the
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.ImagePlaneMemoryRequirementsInfo'::@planeAspect@
--     in the
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.ImageMemoryRequirementsInfo2'
--     structure’s @pNext@ chain
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'
--     structure, @memoryOffset@ /must/ be an integer multiple of the
--     @alignment@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getImageMemoryRequirements2'
--     with @image@ and where
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'::@planeAspect@
--     corresponds to the
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.ImagePlaneMemoryRequirementsInfo'::@planeAspect@
--     in the
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.ImageMemoryRequirementsInfo2'
--     structure’s @pNext@ chain
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'
--     structure, the difference of the size of @memory@ and @memoryOffset@
--     /must/ be greater than or equal to the @size@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getImageMemoryRequirements2'
--     with the same @image@ and where
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'::@planeAspect@
--     corresponds to the
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.ImagePlaneMemoryRequirementsInfo'::@planeAspect@
--     in the
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.ImageMemoryRequirementsInfo2'
--     structure’s @pNext@ chain
--
-- -   If @image@ requires a dedicated allocation (as reported by
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getImageMemoryRequirements2'
--     in
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedRequirements'::requiresDedicatedAllocation
--     for @image@), @memory@ /must/ have been created with
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@image@
--     equal to @image@ and @memoryOffset@ /must/ be zero
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dedicatedAllocationImageAliasing dedicated allocation image aliasing>
--     feature is not enabled, and the
--     'Vulkan.Core10.Memory.MemoryAllocateInfo' provided when @memory@ was
--     allocated included a
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'
--     structure in its @pNext@ chain, and
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@image@
--     was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then @image@
--     /must/ equal
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@image@
--     and @memoryOffset@ /must/ be zero
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dedicatedAllocationImageAliasing dedicated allocation image aliasing>
--     feature is enabled, and the
--     'Vulkan.Core10.Memory.MemoryAllocateInfo' provided when @memory@ was
--     allocated included a
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'
--     structure in its @pNext@ chain, and
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@image@
--     was not 'Vulkan.Core10.APIConstants.NULL_HANDLE', then
--     @memoryOffset@ /must/ be zero, and @image@ /must/ be either equal to
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@image@
--     or an image that was created using the same parameters in
--     'Vulkan.Core10.Image.ImageCreateInfo', with the exception that
--     @extent@ and @arrayLayers@ /may/ differ subject to the following
--     restrictions: every dimension in the @extent@ parameter of the image
--     being bound /must/ be equal to or smaller than the original image
--     for which the allocation was created; and the @arrayLayers@
--     parameter of the image being bound /must/ be equal to or smaller
--     than the original image for which the allocation was created
--
-- -   If image was created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_PROTECTED_BIT'
--     bit set, the image /must/ be bound to a memory object allocated with
--     a memory type that reports
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_PROTECTED_BIT'
--
-- -   If image was created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_PROTECTED_BIT'
--     bit not set, the image /must/ not be bound to a memory object
--     created with a memory type that reports
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_PROTECTED_BIT'
--
-- -   If @image@ was created with
--     'Vulkan.Extensions.VK_NV_dedicated_allocation.DedicatedAllocationImageCreateInfoNV'::@dedicatedAllocation@
--     equal to 'Vulkan.Core10.FundamentalTypes.TRUE', @memory@ /must/ have
--     been created with
--     'Vulkan.Extensions.VK_NV_dedicated_allocation.DedicatedAllocationMemoryAllocateInfoNV'::@image@
--     equal to @image@ and @memoryOffset@ /must/ be zero
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindImageMemoryDeviceGroupInfo'
--     structure, all instances of @memory@ specified by
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindImageMemoryDeviceGroupInfo'::@pDeviceIndices@
--     /must/ have been allocated
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindImageMemoryDeviceGroupInfo'
--     structure, and
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindImageMemoryDeviceGroupInfo'::@splitInstanceBindRegionCount@
--     is not zero, then @image@ /must/ have been created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT'
--     bit set
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindImageMemoryDeviceGroupInfo'
--     structure, all elements of
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindImageMemoryDeviceGroupInfo'::@pSplitInstanceBindRegions@
--     /must/ be valid rectangles contained within the dimensions of
--     @image@
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindImageMemoryDeviceGroupInfo'
--     structure, the union of the areas of all elements of
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindImageMemoryDeviceGroupInfo'::@pSplitInstanceBindRegions@
--     that correspond to the same instance of @image@ /must/ cover the
--     entire image
--
-- -   If @image@ was created with a valid swapchain handle in
--     'Vulkan.Extensions.VK_KHR_swapchain.ImageSwapchainCreateInfoKHR'::@swapchain@,
--     then the @pNext@ chain /must/ include a
--     'Vulkan.Extensions.VK_KHR_swapchain.BindImageMemorySwapchainInfoKHR'
--     structure containing the same swapchain handle
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Extensions.VK_KHR_swapchain.BindImageMemorySwapchainInfoKHR'
--     structure, @memory@ /must/ be
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If the @pNext@ chain does not include a
--     'Vulkan.Extensions.VK_KHR_swapchain.BindImageMemorySwapchainInfoKHR'
--     structure, @memory@ /must/ be a valid
--     'Vulkan.Core10.Handles.DeviceMemory' handle
--
-- -   If the value of
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExportMemoryAllocateInfo'::@handleTypes@
--     used to allocate @memory@ is not @0@, it /must/ include at least one
--     of the handles set in
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExternalMemoryImageCreateInfo'::@handleTypes@
--     when @image@ was created
--
-- -   If @memory@ was created by a memory import operation, that is not
--     'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ImportAndroidHardwareBufferInfoANDROID'
--     with a non-@NULL@ @buffer@ value, the external handle type of the
--     imported memory /must/ also have been set in
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExternalMemoryImageCreateInfo'::@handleTypes@
--     when @image@ was created
--
-- -   If @memory@ was created with the
--     'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ImportAndroidHardwareBufferInfoANDROID'
--     memory import operation with a non-@NULL@ @buffer@ value,
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID'
--     /must/ also have been set in
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExternalMemoryImageCreateInfo'::@handleTypes@
--     when @image@ was created
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_BIND_IMAGE_MEMORY_INFO'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindImageMemoryDeviceGroupInfo',
--     'Vulkan.Extensions.VK_KHR_swapchain.BindImageMemorySwapchainInfoKHR',
--     or
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.BindImagePlaneMemoryInfo'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @image@ /must/ be a valid 'Vulkan.Core10.Handles.Image' handle
--
-- -   Both of @image@, and @memory@ 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.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Handles.Image',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'bindImageMemory2',
-- 'Vulkan.Extensions.VK_KHR_bind_memory2.bindImageMemory2KHR'
data BindImageMemoryInfo (es :: [Type]) = BindImageMemoryInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    BindImageMemoryInfo es -> Chain es
next :: Chain es
  , -- | @image@ is the image to be attached to memory.
    BindImageMemoryInfo es -> Image
image :: Image
  , -- | @memory@ is a 'Vulkan.Core10.Handles.DeviceMemory' object describing the
    -- device memory to attach.
    BindImageMemoryInfo es -> DeviceMemory
memory :: DeviceMemory
  , -- | @memoryOffset@ is the start offset of the region of @memory@ which is to
    -- be bound to the image. The number of bytes returned in the
    -- 'Vulkan.Core10.MemoryManagement.MemoryRequirements'::@size@ member in
    -- @memory@, starting from @memoryOffset@ bytes, will be bound to the
    -- specified image.
    BindImageMemoryInfo es -> DeviceSize
memoryOffset :: DeviceSize
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BindImageMemoryInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (BindImageMemoryInfo es)

instance Extensible BindImageMemoryInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_BIND_IMAGE_MEMORY_INFO
  setNext :: BindImageMemoryInfo ds -> Chain es -> BindImageMemoryInfo es
setNext x :: BindImageMemoryInfo ds
x next :: Chain es
next = BindImageMemoryInfo ds
x{$sel:next:BindImageMemoryInfo :: Chain es
next = Chain es
next}
  getNext :: BindImageMemoryInfo es -> Chain es
getNext BindImageMemoryInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends BindImageMemoryInfo e => b) -> Maybe b
  extends :: proxy e -> (Extends BindImageMemoryInfo e => b) -> Maybe b
extends _ f :: Extends BindImageMemoryInfo e => b
f
    | Just Refl <- (Typeable e, Typeable BindImagePlaneMemoryInfo) =>
Maybe (e :~: BindImagePlaneMemoryInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @BindImagePlaneMemoryInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends BindImageMemoryInfo e => b
f
    | Just Refl <- (Typeable e, Typeable BindImageMemorySwapchainInfoKHR) =>
Maybe (e :~: BindImageMemorySwapchainInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @BindImageMemorySwapchainInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends BindImageMemoryInfo e => b
f
    | Just Refl <- (Typeable e, Typeable BindImageMemoryDeviceGroupInfo) =>
Maybe (e :~: BindImageMemoryDeviceGroupInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @BindImageMemoryDeviceGroupInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends BindImageMemoryInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss BindImageMemoryInfo es, PokeChain es) => ToCStruct (BindImageMemoryInfo es) where
  withCStruct :: BindImageMemoryInfo es
-> (Ptr (BindImageMemoryInfo es) -> IO b) -> IO b
withCStruct x :: BindImageMemoryInfo es
x f :: Ptr (BindImageMemoryInfo es) -> IO b
f = Int -> Int -> (Ptr (BindImageMemoryInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr (BindImageMemoryInfo es) -> IO b) -> IO b)
-> (Ptr (BindImageMemoryInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (BindImageMemoryInfo es)
p -> Ptr (BindImageMemoryInfo es)
-> BindImageMemoryInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (BindImageMemoryInfo es)
p BindImageMemoryInfo es
x (Ptr (BindImageMemoryInfo es) -> IO b
f Ptr (BindImageMemoryInfo es)
p)
  pokeCStruct :: Ptr (BindImageMemoryInfo es)
-> BindImageMemoryInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (BindImageMemoryInfo es)
p BindImageMemoryInfo{..} 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 (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BIND_IMAGE_MEMORY_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Image)) (Image
image)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceMemory)) (DeviceMemory
memory)
    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 DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) (DeviceSize
memoryOffset)
    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 = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (BindImageMemoryInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (BindImageMemoryInfo es)
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 (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BIND_IMAGE_MEMORY_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Image)) (Image
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceMemory)) (DeviceMemory
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss BindImageMemoryInfo es, PeekChain es) => FromCStruct (BindImageMemoryInfo es) where
  peekCStruct :: Ptr (BindImageMemoryInfo es) -> IO (BindImageMemoryInfo es)
peekCStruct p :: Ptr (BindImageMemoryInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    Image
image <- Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Image))
    DeviceMemory
memory <- Ptr DeviceMemory -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceMemory))
    DeviceSize
memoryOffset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr (BindImageMemoryInfo es)
p Ptr (BindImageMemoryInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize))
    BindImageMemoryInfo es -> IO (BindImageMemoryInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BindImageMemoryInfo es -> IO (BindImageMemoryInfo es))
-> BindImageMemoryInfo es -> IO (BindImageMemoryInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> Image -> DeviceMemory -> DeviceSize -> BindImageMemoryInfo es
forall (es :: [*]).
Chain es
-> Image -> DeviceMemory -> DeviceSize -> BindImageMemoryInfo es
BindImageMemoryInfo
             Chain es
next Image
image DeviceMemory
memory DeviceSize
memoryOffset

instance es ~ '[] => Zero (BindImageMemoryInfo es) where
  zero :: BindImageMemoryInfo es
zero = Chain es
-> Image -> DeviceMemory -> DeviceSize -> BindImageMemoryInfo es
forall (es :: [*]).
Chain es
-> Image -> DeviceMemory -> DeviceSize -> BindImageMemoryInfo es
BindImageMemoryInfo
           ()
           Image
forall a. Zero a => a
zero
           DeviceMemory
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero