{-# language CPP #-}
module Vulkan.Core11.Promoted_From_VK_KHR_multiview ( PhysicalDeviceMultiviewFeatures(..)
, PhysicalDeviceMultiviewProperties(..)
, RenderPassMultiviewCreateInfo(..)
, StructureType(..)
, DependencyFlagBits(..)
, DependencyFlags
) where
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Data.Int (Int32)
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.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PROPERTIES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_MULTIVIEW_CREATE_INFO))
import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlagBits(..))
import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlags)
import Vulkan.Core10.Enums.StructureType (StructureType(..))
data PhysicalDeviceMultiviewFeatures = PhysicalDeviceMultiviewFeatures
{
PhysicalDeviceMultiviewFeatures -> Bool
multiview :: Bool
,
PhysicalDeviceMultiviewFeatures -> Bool
multiviewGeometryShader :: Bool
,
PhysicalDeviceMultiviewFeatures -> Bool
multiviewTessellationShader :: Bool
}
deriving (Typeable, PhysicalDeviceMultiviewFeatures
-> PhysicalDeviceMultiviewFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceMultiviewFeatures
-> PhysicalDeviceMultiviewFeatures -> Bool
$c/= :: PhysicalDeviceMultiviewFeatures
-> PhysicalDeviceMultiviewFeatures -> Bool
== :: PhysicalDeviceMultiviewFeatures
-> PhysicalDeviceMultiviewFeatures -> Bool
$c== :: PhysicalDeviceMultiviewFeatures
-> PhysicalDeviceMultiviewFeatures -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMultiviewFeatures)
#endif
deriving instance Show PhysicalDeviceMultiviewFeatures
instance ToCStruct PhysicalDeviceMultiviewFeatures where
withCStruct :: forall b.
PhysicalDeviceMultiviewFeatures
-> (Ptr PhysicalDeviceMultiviewFeatures -> IO b) -> IO b
withCStruct PhysicalDeviceMultiviewFeatures
x Ptr PhysicalDeviceMultiviewFeatures -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceMultiviewFeatures
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMultiviewFeatures
p PhysicalDeviceMultiviewFeatures
x (Ptr PhysicalDeviceMultiviewFeatures -> IO b
f Ptr PhysicalDeviceMultiviewFeatures
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceMultiviewFeatures
-> PhysicalDeviceMultiviewFeatures -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMultiviewFeatures
p PhysicalDeviceMultiviewFeatures{Bool
multiviewTessellationShader :: Bool
multiviewGeometryShader :: Bool
multiview :: Bool
$sel:multiviewTessellationShader:PhysicalDeviceMultiviewFeatures :: PhysicalDeviceMultiviewFeatures -> Bool
$sel:multiviewGeometryShader:PhysicalDeviceMultiviewFeatures :: PhysicalDeviceMultiviewFeatures -> Bool
$sel:multiview:PhysicalDeviceMultiviewFeatures :: PhysicalDeviceMultiviewFeatures -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiview))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiviewGeometryShader))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiviewTessellationShader))
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDeviceMultiviewFeatures -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceMultiviewFeatures
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceMultiviewFeatures where
peekCStruct :: Ptr PhysicalDeviceMultiviewFeatures
-> IO PhysicalDeviceMultiviewFeatures
peekCStruct Ptr PhysicalDeviceMultiviewFeatures
p = do
Bool32
multiview <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
multiviewGeometryShader <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
multiviewTessellationShader <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceMultiviewFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> Bool -> PhysicalDeviceMultiviewFeatures
PhysicalDeviceMultiviewFeatures
(Bool32 -> Bool
bool32ToBool Bool32
multiview)
(Bool32 -> Bool
bool32ToBool Bool32
multiviewGeometryShader)
(Bool32 -> Bool
bool32ToBool Bool32
multiviewTessellationShader)
instance Storable PhysicalDeviceMultiviewFeatures where
sizeOf :: PhysicalDeviceMultiviewFeatures -> Int
sizeOf ~PhysicalDeviceMultiviewFeatures
_ = Int
32
alignment :: PhysicalDeviceMultiviewFeatures -> Int
alignment ~PhysicalDeviceMultiviewFeatures
_ = Int
8
peek :: Ptr PhysicalDeviceMultiviewFeatures
-> IO PhysicalDeviceMultiviewFeatures
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceMultiviewFeatures
-> PhysicalDeviceMultiviewFeatures -> IO ()
poke Ptr PhysicalDeviceMultiviewFeatures
ptr PhysicalDeviceMultiviewFeatures
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMultiviewFeatures
ptr PhysicalDeviceMultiviewFeatures
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceMultiviewFeatures where
zero :: PhysicalDeviceMultiviewFeatures
zero = Bool -> Bool -> Bool -> PhysicalDeviceMultiviewFeatures
PhysicalDeviceMultiviewFeatures
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDeviceMultiviewProperties = PhysicalDeviceMultiviewProperties
{
PhysicalDeviceMultiviewProperties -> Word32
maxMultiviewViewCount :: Word32
,
PhysicalDeviceMultiviewProperties -> Word32
maxMultiviewInstanceIndex :: Word32
}
deriving (Typeable, PhysicalDeviceMultiviewProperties
-> PhysicalDeviceMultiviewProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceMultiviewProperties
-> PhysicalDeviceMultiviewProperties -> Bool
$c/= :: PhysicalDeviceMultiviewProperties
-> PhysicalDeviceMultiviewProperties -> Bool
== :: PhysicalDeviceMultiviewProperties
-> PhysicalDeviceMultiviewProperties -> Bool
$c== :: PhysicalDeviceMultiviewProperties
-> PhysicalDeviceMultiviewProperties -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMultiviewProperties)
#endif
deriving instance Show PhysicalDeviceMultiviewProperties
instance ToCStruct PhysicalDeviceMultiviewProperties where
withCStruct :: forall b.
PhysicalDeviceMultiviewProperties
-> (Ptr PhysicalDeviceMultiviewProperties -> IO b) -> IO b
withCStruct PhysicalDeviceMultiviewProperties
x Ptr PhysicalDeviceMultiviewProperties -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceMultiviewProperties
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMultiviewProperties
p PhysicalDeviceMultiviewProperties
x (Ptr PhysicalDeviceMultiviewProperties -> IO b
f Ptr PhysicalDeviceMultiviewProperties
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceMultiviewProperties
-> PhysicalDeviceMultiviewProperties -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMultiviewProperties
p PhysicalDeviceMultiviewProperties{Word32
maxMultiviewInstanceIndex :: Word32
maxMultiviewViewCount :: Word32
$sel:maxMultiviewInstanceIndex:PhysicalDeviceMultiviewProperties :: PhysicalDeviceMultiviewProperties -> Word32
$sel:maxMultiviewViewCount:PhysicalDeviceMultiviewProperties :: PhysicalDeviceMultiviewProperties -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
maxMultiviewViewCount)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (Word32
maxMultiviewInstanceIndex)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDeviceMultiviewProperties -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceMultiviewProperties
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMultiviewProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDeviceMultiviewProperties where
peekCStruct :: Ptr PhysicalDeviceMultiviewProperties
-> IO PhysicalDeviceMultiviewProperties
peekCStruct Ptr PhysicalDeviceMultiviewProperties
p = do
Word32
maxMultiviewViewCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMultiviewProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Word32
maxMultiviewInstanceIndex <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMultiviewProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32 -> Word32 -> PhysicalDeviceMultiviewProperties
PhysicalDeviceMultiviewProperties
Word32
maxMultiviewViewCount Word32
maxMultiviewInstanceIndex
instance Storable PhysicalDeviceMultiviewProperties where
sizeOf :: PhysicalDeviceMultiviewProperties -> Int
sizeOf ~PhysicalDeviceMultiviewProperties
_ = Int
24
alignment :: PhysicalDeviceMultiviewProperties -> Int
alignment ~PhysicalDeviceMultiviewProperties
_ = Int
8
peek :: Ptr PhysicalDeviceMultiviewProperties
-> IO PhysicalDeviceMultiviewProperties
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceMultiviewProperties
-> PhysicalDeviceMultiviewProperties -> IO ()
poke Ptr PhysicalDeviceMultiviewProperties
ptr PhysicalDeviceMultiviewProperties
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMultiviewProperties
ptr PhysicalDeviceMultiviewProperties
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceMultiviewProperties where
zero :: PhysicalDeviceMultiviewProperties
zero = Word32 -> Word32 -> PhysicalDeviceMultiviewProperties
PhysicalDeviceMultiviewProperties
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data RenderPassMultiviewCreateInfo = RenderPassMultiviewCreateInfo
{
RenderPassMultiviewCreateInfo -> Vector Word32
viewMasks :: Vector Word32
,
RenderPassMultiviewCreateInfo -> Vector Int32
viewOffsets :: Vector Int32
,
RenderPassMultiviewCreateInfo -> Vector Word32
correlationMasks :: Vector Word32
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RenderPassMultiviewCreateInfo)
#endif
deriving instance Show RenderPassMultiviewCreateInfo
instance ToCStruct RenderPassMultiviewCreateInfo where
withCStruct :: forall b.
RenderPassMultiviewCreateInfo
-> (Ptr RenderPassMultiviewCreateInfo -> IO b) -> IO b
withCStruct RenderPassMultiviewCreateInfo
x Ptr RenderPassMultiviewCreateInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
64 forall a b. (a -> b) -> a -> b
$ \Ptr RenderPassMultiviewCreateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr RenderPassMultiviewCreateInfo
p RenderPassMultiviewCreateInfo
x (Ptr RenderPassMultiviewCreateInfo -> IO b
f Ptr RenderPassMultiviewCreateInfo
p)
pokeCStruct :: forall b.
Ptr RenderPassMultiviewCreateInfo
-> RenderPassMultiviewCreateInfo -> IO b -> IO b
pokeCStruct Ptr RenderPassMultiviewCreateInfo
p RenderPassMultiviewCreateInfo{Vector Int32
Vector Word32
correlationMasks :: Vector Word32
viewOffsets :: Vector Int32
viewMasks :: Vector Word32
$sel:correlationMasks:RenderPassMultiviewCreateInfo :: RenderPassMultiviewCreateInfo -> Vector Word32
$sel:viewOffsets:RenderPassMultiviewCreateInfo :: RenderPassMultiviewCreateInfo -> Vector Int32
$sel:viewMasks:RenderPassMultiviewCreateInfo :: RenderPassMultiviewCreateInfo -> Vector Word32
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_MULTIVIEW_CREATE_INFO)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector Word32
viewMasks)) :: Word32))
Ptr Word32
pPViewMasks' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Word32 ((forall a. Vector a -> Int
Data.Vector.length (Vector Word32
viewMasks)) forall a. Num a => a -> a -> a
* Int
4)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Word32
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPViewMasks' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
viewMasks)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Word32))) (Ptr Word32
pPViewMasks')
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector Int32
viewOffsets)) :: Word32))
Ptr Int32
pPViewOffsets' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Int32 ((forall a. Vector a -> Int
Data.Vector.length (Vector Int32
viewOffsets)) forall a. Num a => a -> a -> a
* Int
4)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Int32
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Int32
pPViewOffsets' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Int32) (Int32
e)) (Vector Int32
viewOffsets)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr (Ptr Int32))) (Ptr Int32
pPViewOffsets')
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector Word32
correlationMasks)) :: Word32))
Ptr Word32
pPCorrelationMasks' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Word32 ((forall a. Vector a -> Int
Data.Vector.length (Vector Word32
correlationMasks)) forall a. Num a => a -> a -> a
* Int
4)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Word32
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPCorrelationMasks' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
correlationMasks)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr (Ptr Word32))) (Ptr Word32
pPCorrelationMasks')
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
64
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr RenderPassMultiviewCreateInfo -> IO b -> IO b
pokeZeroCStruct Ptr RenderPassMultiviewCreateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_MULTIVIEW_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct RenderPassMultiviewCreateInfo where
peekCStruct :: Ptr RenderPassMultiviewCreateInfo
-> IO RenderPassMultiviewCreateInfo
peekCStruct Ptr RenderPassMultiviewCreateInfo
p = do
Word32
subpassCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Ptr Word32
pViewMasks <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Word32)))
Vector Word32
pViewMasks' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
subpassCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pViewMasks forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
Word32
dependencyCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32))
Ptr Int32
pViewOffsets <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Int32) ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr (Ptr Int32)))
Vector Int32
pViewOffsets' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
dependencyCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr Int32
pViewOffsets forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Int32)))
Word32
correlationMaskCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word32))
Ptr Word32
pCorrelationMasks <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr RenderPassMultiviewCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr (Ptr Word32)))
Vector Word32
pCorrelationMasks' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
correlationMaskCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pCorrelationMasks forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector Word32
-> Vector Int32 -> Vector Word32 -> RenderPassMultiviewCreateInfo
RenderPassMultiviewCreateInfo
Vector Word32
pViewMasks' Vector Int32
pViewOffsets' Vector Word32
pCorrelationMasks'
instance Zero RenderPassMultiviewCreateInfo where
zero :: RenderPassMultiviewCreateInfo
zero = Vector Word32
-> Vector Int32 -> Vector Word32 -> RenderPassMultiviewCreateInfo
RenderPassMultiviewCreateInfo
forall a. Monoid a => a
mempty
forall a. Monoid a => a
mempty
forall a. Monoid a => a
mempty