{-# language CPP #-}
module Vulkan.Core10.BufferView ( createBufferView
, withBufferView
, destroyBufferView
, BufferViewCreateInfo(..)
, BufferView(..)
, BufferViewCreateFlags(..)
) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
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 (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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 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.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.Core10.Handles (BufferView)
import Vulkan.Core10.Handles (BufferView(..))
import Vulkan.Core10.Enums.BufferViewCreateFlags (BufferViewCreateFlags)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkCreateBufferView))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyBufferView))
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_metal_objects (ExportMetalObjectCreateInfoEXT)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.Enums.Format (Format)
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.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BUFFER_VIEW_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Handles (BufferView(..))
import Vulkan.Core10.Enums.BufferViewCreateFlags (BufferViewCreateFlags(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCreateBufferView
:: FunPtr (Ptr Device_T -> Ptr (SomeStruct BufferViewCreateInfo) -> Ptr AllocationCallbacks -> Ptr BufferView -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct BufferViewCreateInfo) -> Ptr AllocationCallbacks -> Ptr BufferView -> IO Result
createBufferView :: forall a io
. (Extendss BufferViewCreateInfo a, PokeChain a, MonadIO io)
=>
Device
->
(BufferViewCreateInfo a)
->
("allocator" ::: Maybe AllocationCallbacks)
-> io (BufferView)
createBufferView :: forall (a :: [*]) (io :: * -> *).
(Extendss BufferViewCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> BufferViewCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io BufferView
createBufferView Device
device BufferViewCreateInfo a
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = IO BufferView -> io BufferView
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BufferView -> io BufferView)
-> (ContT BufferView IO BufferView -> IO BufferView)
-> ContT BufferView IO BufferView
-> io BufferView
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT BufferView IO BufferView -> IO BufferView
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT BufferView IO BufferView -> io BufferView)
-> ContT BufferView IO BufferView -> io BufferView
forall a b. (a -> b) -> a -> b
$ do
let vkCreateBufferViewPtr :: FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> IO Result)
vkCreateBufferViewPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> IO Result)
pVkCreateBufferView (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
IO () -> ContT BufferView IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT BufferView IO ())
-> IO () -> ContT BufferView IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> IO Result)
vkCreateBufferViewPtr FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> 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 String
"" String
"The function pointer for vkCreateBufferView is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkCreateBufferView' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> IO Result
vkCreateBufferView' = FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> IO Result
mkVkCreateBufferView FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> IO Result)
vkCreateBufferViewPtr
Ptr (BufferViewCreateInfo a)
pCreateInfo <- ((Ptr (BufferViewCreateInfo a) -> IO BufferView) -> IO BufferView)
-> ContT BufferView IO (Ptr (BufferViewCreateInfo a))
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (BufferViewCreateInfo a) -> IO BufferView) -> IO BufferView)
-> ContT BufferView IO (Ptr (BufferViewCreateInfo a)))
-> ((Ptr (BufferViewCreateInfo a) -> IO BufferView)
-> IO BufferView)
-> ContT BufferView IO (Ptr (BufferViewCreateInfo a))
forall a b. (a -> b) -> a -> b
$ BufferViewCreateInfo a
-> (Ptr (BufferViewCreateInfo a) -> IO BufferView) -> IO BufferView
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (BufferViewCreateInfo a
createInfo)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
"allocator" ::: Maybe AllocationCallbacks
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT BufferView IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
Just AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO BufferView)
-> IO BufferView)
-> ContT BufferView IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO BufferView)
-> IO BufferView)
-> ContT BufferView IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO BufferView)
-> IO BufferView)
-> ContT BufferView IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO BufferView)
-> IO BufferView
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
"pView" ::: Ptr BufferView
pPView <- ((("pView" ::: Ptr BufferView) -> IO BufferView) -> IO BufferView)
-> ContT BufferView IO ("pView" ::: Ptr BufferView)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pView" ::: Ptr BufferView) -> IO BufferView) -> IO BufferView)
-> ContT BufferView IO ("pView" ::: Ptr BufferView))
-> ((("pView" ::: Ptr BufferView) -> IO BufferView)
-> IO BufferView)
-> ContT BufferView IO ("pView" ::: Ptr BufferView)
forall a b. (a -> b) -> a -> b
$ IO ("pView" ::: Ptr BufferView)
-> (("pView" ::: Ptr BufferView) -> IO ())
-> (("pView" ::: Ptr BufferView) -> IO BufferView)
-> IO BufferView
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @BufferView Int
8) ("pView" ::: Ptr BufferView) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT BufferView IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT BufferView IO Result)
-> IO Result -> ContT BufferView IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreateBufferView" (Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pView" ::: Ptr BufferView)
-> IO Result
vkCreateBufferView'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(Ptr (BufferViewCreateInfo a)
-> "pCreateInfo" ::: Ptr (SomeStruct BufferViewCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (BufferViewCreateInfo a)
pCreateInfo)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator
("pView" ::: Ptr BufferView
pPView))
IO () -> ContT BufferView IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT BufferView IO ())
-> IO () -> ContT BufferView 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))
BufferView
pView <- IO BufferView -> ContT BufferView IO BufferView
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO BufferView -> ContT BufferView IO BufferView)
-> IO BufferView -> ContT BufferView IO BufferView
forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @BufferView "pView" ::: Ptr BufferView
pPView
BufferView -> ContT BufferView IO BufferView
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BufferView -> ContT BufferView IO BufferView)
-> BufferView -> ContT BufferView IO BufferView
forall a b. (a -> b) -> a -> b
$ (BufferView
pView)
withBufferView :: forall a io r . (Extendss BufferViewCreateInfo a, PokeChain a, MonadIO io) => Device -> BufferViewCreateInfo a -> Maybe AllocationCallbacks -> (io BufferView -> (BufferView -> io ()) -> r) -> r
withBufferView :: forall (a :: [*]) (io :: * -> *) r.
(Extendss BufferViewCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> BufferViewCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io BufferView -> (BufferView -> io ()) -> r)
-> r
withBufferView Device
device BufferViewCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator io BufferView -> (BufferView -> io ()) -> r
b =
io BufferView -> (BufferView -> io ()) -> r
b (Device
-> BufferViewCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io BufferView
forall (a :: [*]) (io :: * -> *).
(Extendss BufferViewCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> BufferViewCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io BufferView
createBufferView Device
device BufferViewCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
(\(BufferView
o0) -> Device
-> BufferView
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> BufferView
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyBufferView Device
device BufferView
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkDestroyBufferView
:: FunPtr (Ptr Device_T -> BufferView -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> BufferView -> Ptr AllocationCallbacks -> IO ()
destroyBufferView :: forall io
. (MonadIO io)
=>
Device
->
BufferView
->
("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyBufferView :: forall (io :: * -> *).
MonadIO io =>
Device
-> BufferView
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyBufferView Device
device BufferView
bufferView "allocator" ::: Maybe AllocationCallbacks
allocator = 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 vkDestroyBufferViewPtr :: FunPtr
(Ptr Device_T
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyBufferViewPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
pVkDestroyBufferView (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
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
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyBufferViewPtr FunPtr
(Ptr Device_T
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
-> FunPtr
(Ptr Device_T
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
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 String
"" String
"The function pointer for vkDestroyBufferView is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkDestroyBufferView' :: Ptr Device_T
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyBufferView' = FunPtr
(Ptr Device_T
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
-> Ptr Device_T
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyBufferView FunPtr
(Ptr Device_T
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyBufferViewPtr
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
"allocator" ::: Maybe AllocationCallbacks
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
Just AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
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
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDestroyBufferView" (Ptr Device_T
-> BufferView
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyBufferView'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(BufferView
bufferView)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator)
() -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()
data BufferViewCreateInfo (es :: [Type]) = BufferViewCreateInfo
{
forall (es :: [*]). BufferViewCreateInfo es -> Chain es
next :: Chain es
,
forall (es :: [*]).
BufferViewCreateInfo es -> BufferViewCreateFlags
flags :: BufferViewCreateFlags
,
forall (es :: [*]). BufferViewCreateInfo es -> Buffer
buffer :: Buffer
,
forall (es :: [*]). BufferViewCreateInfo es -> Format
format :: Format
,
forall (es :: [*]). BufferViewCreateInfo es -> DeviceSize
offset :: DeviceSize
,
forall (es :: [*]). BufferViewCreateInfo es -> DeviceSize
range :: DeviceSize
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BufferViewCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (BufferViewCreateInfo es)
instance Extensible BufferViewCreateInfo where
extensibleTypeName :: String
extensibleTypeName = String
"BufferViewCreateInfo"
setNext :: forall (ds :: [*]) (es :: [*]).
BufferViewCreateInfo ds -> Chain es -> BufferViewCreateInfo es
setNext BufferViewCreateInfo{DeviceSize
Chain ds
Format
Buffer
BufferViewCreateFlags
range :: DeviceSize
offset :: DeviceSize
format :: Format
buffer :: Buffer
flags :: BufferViewCreateFlags
next :: Chain ds
$sel:range:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> DeviceSize
$sel:offset:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> DeviceSize
$sel:format:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> Format
$sel:buffer:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> Buffer
$sel:flags:BufferViewCreateInfo :: forall (es :: [*]).
BufferViewCreateInfo es -> BufferViewCreateFlags
$sel:next:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> Chain es
..} Chain es
next' = BufferViewCreateInfo :: forall (es :: [*]).
Chain es
-> BufferViewCreateFlags
-> Buffer
-> Format
-> DeviceSize
-> DeviceSize
-> BufferViewCreateInfo es
BufferViewCreateInfo{$sel:next:BufferViewCreateInfo :: Chain es
next = Chain es
next', DeviceSize
Format
Buffer
BufferViewCreateFlags
range :: DeviceSize
offset :: DeviceSize
format :: Format
buffer :: Buffer
flags :: BufferViewCreateFlags
$sel:range:BufferViewCreateInfo :: DeviceSize
$sel:offset:BufferViewCreateInfo :: DeviceSize
$sel:format:BufferViewCreateInfo :: Format
$sel:buffer:BufferViewCreateInfo :: Buffer
$sel:flags:BufferViewCreateInfo :: BufferViewCreateFlags
..}
getNext :: forall (es :: [*]). BufferViewCreateInfo es -> Chain es
getNext BufferViewCreateInfo{DeviceSize
Chain es
Format
Buffer
BufferViewCreateFlags
range :: DeviceSize
offset :: DeviceSize
format :: Format
buffer :: Buffer
flags :: BufferViewCreateFlags
next :: Chain es
$sel:range:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> DeviceSize
$sel:offset:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> DeviceSize
$sel:format:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> Format
$sel:buffer:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> Buffer
$sel:flags:BufferViewCreateInfo :: forall (es :: [*]).
BufferViewCreateInfo es -> BufferViewCreateFlags
$sel:next:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> Chain es
..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends BufferViewCreateInfo e => b) -> Maybe b
extends :: forall e b (proxy :: * -> *).
Typeable e =>
proxy e -> (Extends BufferViewCreateInfo e => b) -> Maybe b
extends proxy e
_ Extends BufferViewCreateInfo e => b
f
| Just e :~: ExportMetalObjectCreateInfoEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
forall a b. (Typeable a, Typeable b) => Maybe (a :~: b)
eqT @e @ExportMetalObjectCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends BufferViewCreateInfo e => b
f
| Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance ( Extendss BufferViewCreateInfo es
, PokeChain es ) => ToCStruct (BufferViewCreateInfo es) where
withCStruct :: forall b.
BufferViewCreateInfo es
-> (Ptr (BufferViewCreateInfo es) -> IO b) -> IO b
withCStruct BufferViewCreateInfo es
x Ptr (BufferViewCreateInfo es) -> IO b
f = Int -> (Ptr (BufferViewCreateInfo es) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
56 ((Ptr (BufferViewCreateInfo es) -> IO b) -> IO b)
-> (Ptr (BufferViewCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr (BufferViewCreateInfo es)
p -> Ptr (BufferViewCreateInfo es)
-> BufferViewCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (BufferViewCreateInfo es)
p BufferViewCreateInfo es
x (Ptr (BufferViewCreateInfo es) -> IO b
f Ptr (BufferViewCreateInfo es)
p)
pokeCStruct :: forall b.
Ptr (BufferViewCreateInfo es)
-> BufferViewCreateInfo es -> IO b -> IO b
pokeCStruct Ptr (BufferViewCreateInfo es)
p BufferViewCreateInfo{DeviceSize
Chain es
Format
Buffer
BufferViewCreateFlags
range :: DeviceSize
offset :: DeviceSize
format :: Format
buffer :: Buffer
flags :: BufferViewCreateFlags
next :: Chain es
$sel:range:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> DeviceSize
$sel:offset:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> DeviceSize
$sel:format:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> Format
$sel:buffer:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> Buffer
$sel:flags:BufferViewCreateInfo :: forall (es :: [*]).
BufferViewCreateInfo es -> BufferViewCreateFlags
$sel:next:BufferViewCreateInfo :: forall (es :: [*]). BufferViewCreateInfo es -> Chain es
..} 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 (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_VIEW_CREATE_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 (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
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 BufferViewCreateFlags -> BufferViewCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr BufferViewCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr BufferViewCreateFlags)) (BufferViewCreateFlags
flags)
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 (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: 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 Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Format)) (Format
format)
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 (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize)) (DeviceSize
offset)
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 (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr DeviceSize)) (DeviceSize
range)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
56
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr (BufferViewCreateInfo es) -> IO b -> IO b
pokeZeroCStruct Ptr (BufferViewCreateInfo es)
p 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 (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_VIEW_CREATE_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 (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 (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
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 (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: 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 Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Format)) (Format
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 (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize)) (DeviceSize
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 (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: 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 BufferViewCreateInfo es
, PeekChain es ) => FromCStruct (BufferViewCreateInfo es) where
peekCStruct :: Ptr (BufferViewCreateInfo es) -> IO (BufferViewCreateInfo es)
peekCStruct Ptr (BufferViewCreateInfo es)
p = do
Ptr ()
pNext <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
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)
BufferViewCreateFlags
flags <- forall a. Storable a => Ptr a -> IO a
peek @BufferViewCreateFlags ((Ptr (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr BufferViewCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr BufferViewCreateFlags))
Buffer
buffer <- forall a. Storable a => Ptr a -> IO a
peek @Buffer ((Ptr (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Buffer))
Format
format <- forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Format))
DeviceSize
offset <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize))
DeviceSize
range <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr (BufferViewCreateInfo es)
p Ptr (BufferViewCreateInfo es) -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr DeviceSize))
BufferViewCreateInfo es -> IO (BufferViewCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BufferViewCreateInfo es -> IO (BufferViewCreateInfo es))
-> BufferViewCreateInfo es -> IO (BufferViewCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> BufferViewCreateFlags
-> Buffer
-> Format
-> DeviceSize
-> DeviceSize
-> BufferViewCreateInfo es
forall (es :: [*]).
Chain es
-> BufferViewCreateFlags
-> Buffer
-> Format
-> DeviceSize
-> DeviceSize
-> BufferViewCreateInfo es
BufferViewCreateInfo
Chain es
next BufferViewCreateFlags
flags Buffer
buffer Format
format DeviceSize
offset DeviceSize
range
instance es ~ '[] => Zero (BufferViewCreateInfo es) where
zero :: BufferViewCreateInfo es
zero = Chain es
-> BufferViewCreateFlags
-> Buffer
-> Format
-> DeviceSize
-> DeviceSize
-> BufferViewCreateInfo es
forall (es :: [*]).
Chain es
-> BufferViewCreateFlags
-> Buffer
-> Format
-> DeviceSize
-> DeviceSize
-> BufferViewCreateInfo es
BufferViewCreateInfo
()
BufferViewCreateFlags
forall a. Zero a => a
zero
Buffer
forall a. Zero a => a
zero
Format
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero
DeviceSize
forall a. Zero a => a
zero