{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_color_write_enable ( cmdSetColorWriteEnableEXT
, PhysicalDeviceColorWriteEnableFeaturesEXT(..)
, PipelineColorWriteCreateInfoEXT(..)
, EXT_COLOR_WRITE_ENABLE_SPEC_VERSION
, pattern EXT_COLOR_WRITE_ENABLE_SPEC_VERSION
, EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME
, pattern EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME
) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.IO (throwIO)
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 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 Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import 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.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (Bool32(..))
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetColorWriteEnableEXT))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_COLOR_WRITE_ENABLE_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_COLOR_WRITE_CREATE_INFO_EXT))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdSetColorWriteEnableEXT
:: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr Bool32 -> IO ()
cmdSetColorWriteEnableEXT :: forall io
. (MonadIO io)
=>
CommandBuffer
->
("colorWriteEnables" ::: Vector Bool)
-> io ()
cmdSetColorWriteEnableEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> ("colorWriteEnables" ::: Vector Bool) -> io ()
cmdSetColorWriteEnableEXT CommandBuffer
commandBuffer
"colorWriteEnables" ::: Vector Bool
colorWriteEnables = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkCmdSetColorWriteEnableEXTPtr :: FunPtr
(Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ())
vkCmdSetColorWriteEnableEXTPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ())
pVkCmdSetColorWriteEnableEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ())
vkCmdSetColorWriteEnableEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCmdSetColorWriteEnableEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCmdSetColorWriteEnableEXT' :: Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ()
vkCmdSetColorWriteEnableEXT' = FunPtr
(Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ())
-> Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ()
mkVkCmdSetColorWriteEnableEXT FunPtr
(Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ())
vkCmdSetColorWriteEnableEXTPtr
"pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables <- 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 @Bool32 ((forall a. Vector a -> Int
Data.Vector.length ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) 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 Bool
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32) (Bool -> Bool32
boolToBool32 (Bool
e))) ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetColorWriteEnableEXT" (Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ()
vkCmdSetColorWriteEnableEXT'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
((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
$ ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) :: Word32))
("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
data PhysicalDeviceColorWriteEnableFeaturesEXT = PhysicalDeviceColorWriteEnableFeaturesEXT
{
PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
colorWriteEnable :: Bool }
deriving (Typeable, PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
$c/= :: PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
== :: PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
$c== :: PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceColorWriteEnableFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceColorWriteEnableFeaturesEXT
instance ToCStruct PhysicalDeviceColorWriteEnableFeaturesEXT where
withCStruct :: forall b.
PhysicalDeviceColorWriteEnableFeaturesEXT
-> (Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceColorWriteEnableFeaturesEXT
x Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p PhysicalDeviceColorWriteEnableFeaturesEXT
x (Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b
f Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p PhysicalDeviceColorWriteEnableFeaturesEXT{Bool
colorWriteEnable :: Bool
$sel:colorWriteEnable:PhysicalDeviceColorWriteEnableFeaturesEXT :: PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COLOR_WRITE_ENABLE_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
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 PhysicalDeviceColorWriteEnableFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
colorWriteEnable))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COLOR_WRITE_ENABLE_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
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 PhysicalDeviceColorWriteEnableFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceColorWriteEnableFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> IO PhysicalDeviceColorWriteEnableFeaturesEXT
peekCStruct Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p = do
Bool32
colorWriteEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceColorWriteEnableFeaturesEXT
PhysicalDeviceColorWriteEnableFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
colorWriteEnable)
instance Storable PhysicalDeviceColorWriteEnableFeaturesEXT where
sizeOf :: PhysicalDeviceColorWriteEnableFeaturesEXT -> Int
sizeOf ~PhysicalDeviceColorWriteEnableFeaturesEXT
_ = Int
24
alignment :: PhysicalDeviceColorWriteEnableFeaturesEXT -> Int
alignment ~PhysicalDeviceColorWriteEnableFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> IO PhysicalDeviceColorWriteEnableFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
ptr PhysicalDeviceColorWriteEnableFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
ptr PhysicalDeviceColorWriteEnableFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceColorWriteEnableFeaturesEXT where
zero :: PhysicalDeviceColorWriteEnableFeaturesEXT
zero = Bool -> PhysicalDeviceColorWriteEnableFeaturesEXT
PhysicalDeviceColorWriteEnableFeaturesEXT
forall a. Zero a => a
zero
data PipelineColorWriteCreateInfoEXT = PipelineColorWriteCreateInfoEXT
{
PipelineColorWriteCreateInfoEXT
-> "colorWriteEnables" ::: Vector Bool
colorWriteEnables :: Vector Bool }
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineColorWriteCreateInfoEXT)
#endif
deriving instance Show PipelineColorWriteCreateInfoEXT
instance ToCStruct PipelineColorWriteCreateInfoEXT where
withCStruct :: forall b.
PipelineColorWriteCreateInfoEXT
-> (Ptr PipelineColorWriteCreateInfoEXT -> IO b) -> IO b
withCStruct PipelineColorWriteCreateInfoEXT
x Ptr PipelineColorWriteCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PipelineColorWriteCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineColorWriteCreateInfoEXT
p PipelineColorWriteCreateInfoEXT
x (Ptr PipelineColorWriteCreateInfoEXT -> IO b
f Ptr PipelineColorWriteCreateInfoEXT
p)
pokeCStruct :: forall b.
Ptr PipelineColorWriteCreateInfoEXT
-> PipelineColorWriteCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr PipelineColorWriteCreateInfoEXT
p PipelineColorWriteCreateInfoEXT{"colorWriteEnables" ::: Vector Bool
colorWriteEnables :: "colorWriteEnables" ::: Vector Bool
$sel:colorWriteEnables:PipelineColorWriteCreateInfoEXT :: PipelineColorWriteCreateInfoEXT
-> "colorWriteEnables" ::: Vector Bool
..} 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 PipelineColorWriteCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COLOR_WRITE_CREATE_INFO_EXT)
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 PipelineColorWriteCreateInfoEXT
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 PipelineColorWriteCreateInfoEXT
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
$ ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) :: Word32))
"pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables' <- 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 @Bool32 ((forall a. Vector a -> Int
Data.Vector.length ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) 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 Bool
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32) (Bool -> Bool32
boolToBool32 (Bool
e))) ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)
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 PipelineColorWriteCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Bool32))) ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables')
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
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PipelineColorWriteCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr PipelineColorWriteCreateInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COLOR_WRITE_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct PipelineColorWriteCreateInfoEXT where
peekCStruct :: Ptr PipelineColorWriteCreateInfoEXT
-> IO PipelineColorWriteCreateInfoEXT
peekCStruct Ptr PipelineColorWriteCreateInfoEXT
p = do
"attachmentCount" ::: Word32
attachmentCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineColorWriteCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
"pColorWriteEnables" ::: Ptr Bool32
pColorWriteEnables <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Bool32) ((Ptr PipelineColorWriteCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Bool32)))
"colorWriteEnables" ::: Vector Bool
pColorWriteEnables' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral "attachmentCount" ::: Word32
attachmentCount) (\Int
i -> do
Bool32
pColorWriteEnablesElem <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pColorWriteEnables" ::: Ptr Bool32
pColorWriteEnables forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool32 -> Bool
bool32ToBool Bool32
pColorWriteEnablesElem)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("colorWriteEnables" ::: Vector Bool)
-> PipelineColorWriteCreateInfoEXT
PipelineColorWriteCreateInfoEXT
"colorWriteEnables" ::: Vector Bool
pColorWriteEnables'
instance Zero PipelineColorWriteCreateInfoEXT where
zero :: PipelineColorWriteCreateInfoEXT
zero = ("colorWriteEnables" ::: Vector Bool)
-> PipelineColorWriteCreateInfoEXT
PipelineColorWriteCreateInfoEXT
forall a. Monoid a => a
mempty
type EXT_COLOR_WRITE_ENABLE_SPEC_VERSION = 1
pattern EXT_COLOR_WRITE_ENABLE_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_COLOR_WRITE_ENABLE_SPEC_VERSION :: forall a. Integral a => a
$mEXT_COLOR_WRITE_ENABLE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_COLOR_WRITE_ENABLE_SPEC_VERSION = 1
type EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME = "VK_EXT_color_write_enable"
pattern EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_COLOR_WRITE_ENABLE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_COLOR_WRITE_ENABLE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME = "VK_EXT_color_write_enable"