{-# 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 (allocaBytesAligned)
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_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 :: CommandBuffer -> ("colorWriteEnables" ::: Vector Bool) -> io ()
cmdSetColorWriteEnableEXT commandBuffer :: CommandBuffer
commandBuffer colorWriteEnables :: "colorWriteEnables" ::: Vector Bool
colorWriteEnables = 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 vkCmdSetColorWriteEnableEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("attachmentCount" ::: Word32)
   -> ("pColorWriteEnables" ::: Ptr Bool32)
   -> IO ())
vkCmdSetColorWriteEnableEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("attachmentCount" ::: Word32)
      -> ("pColorWriteEnables" ::: Ptr Bool32)
      -> IO ())
pVkCmdSetColorWriteEnableEXT (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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 CommandBuffer_T
   -> ("attachmentCount" ::: Word32)
   -> ("pColorWriteEnables" ::: Ptr Bool32)
   -> IO ())
vkCmdSetColorWriteEnableEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("attachmentCount" ::: Word32)
   -> ("pColorWriteEnables" ::: Ptr Bool32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("attachmentCount" ::: Word32)
      -> ("pColorWriteEnables" ::: Ptr Bool32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("attachmentCount" ::: Word32)
   -> ("pColorWriteEnables" ::: Ptr Bool32)
   -> 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 "" "The function pointer for vkCmdSetColorWriteEnableEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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 <- ((("pColorWriteEnables" ::: Ptr Bool32) -> IO ()) -> IO ())
-> ContT () IO ("pColorWriteEnables" ::: Ptr Bool32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pColorWriteEnables" ::: Ptr Bool32) -> IO ()) -> IO ())
 -> ContT () IO ("pColorWriteEnables" ::: Ptr Bool32))
-> ((("pColorWriteEnables" ::: Ptr Bool32) -> IO ()) -> IO ())
-> ContT () IO ("pColorWriteEnables" ::: Ptr Bool32)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pColorWriteEnables" ::: Ptr Bool32) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Bool32 ((("colorWriteEnables" ::: Vector Bool) -> Int
forall a. Vector a -> Int
Data.Vector.length ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
  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
$ (Int -> Bool -> IO ())
-> ("colorWriteEnables" ::: Vector Bool) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Bool
e -> ("pColorWriteEnables" ::: Ptr Bool32) -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables ("pColorWriteEnables" ::: Ptr Bool32)
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32) (Bool -> Bool32
boolToBool32 (Bool
e))) ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)
  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 "vkCmdSetColorWriteEnableEXT" (Ptr CommandBuffer_T
-> ("attachmentCount" ::: Word32)
-> ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ()
vkCmdSetColorWriteEnableEXT' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ((Int -> "attachmentCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("colorWriteEnables" ::: Vector Bool) -> Int
forall a. Vector a -> Int
Data.Vector.length (("colorWriteEnables" ::: Vector Bool) -> Int)
-> ("colorWriteEnables" ::: Vector Bool) -> Int
forall a b. (a -> b) -> a -> b
$ ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) :: Word32)) ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables))
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()
data PhysicalDeviceColorWriteEnableFeaturesEXT = PhysicalDeviceColorWriteEnableFeaturesEXT
  { 
    
    
    PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
colorWriteEnable :: Bool }
  deriving (Typeable, PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool
(PhysicalDeviceColorWriteEnableFeaturesEXT
 -> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool)
-> (PhysicalDeviceColorWriteEnableFeaturesEXT
    -> PhysicalDeviceColorWriteEnableFeaturesEXT -> Bool)
-> Eq PhysicalDeviceColorWriteEnableFeaturesEXT
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 :: PhysicalDeviceColorWriteEnableFeaturesEXT
-> (Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b) -> IO b
withCStruct x :: PhysicalDeviceColorWriteEnableFeaturesEXT
x f :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p -> Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b -> IO b
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 :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p PhysicalDeviceColorWriteEnableFeaturesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COLOR_WRITE_ENABLE_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pColorWriteEnables" ::: Ptr Bool32) -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
colorWriteEnable))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COLOR_WRITE_ENABLE_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pColorWriteEnables" ::: Ptr Bool32) -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f
instance FromCStruct PhysicalDeviceColorWriteEnableFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> IO PhysicalDeviceColorWriteEnableFeaturesEXT
peekCStruct p :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p = do
    Bool32
colorWriteEnable <- ("pColorWriteEnables" ::: Ptr Bool32) -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
p Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    PhysicalDeviceColorWriteEnableFeaturesEXT
-> IO PhysicalDeviceColorWriteEnableFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceColorWriteEnableFeaturesEXT
 -> IO PhysicalDeviceColorWriteEnableFeaturesEXT)
-> PhysicalDeviceColorWriteEnableFeaturesEXT
-> IO PhysicalDeviceColorWriteEnableFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceColorWriteEnableFeaturesEXT
PhysicalDeviceColorWriteEnableFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
colorWriteEnable)
instance Storable PhysicalDeviceColorWriteEnableFeaturesEXT where
  sizeOf :: PhysicalDeviceColorWriteEnableFeaturesEXT -> Int
sizeOf ~PhysicalDeviceColorWriteEnableFeaturesEXT
_ = 24
  alignment :: PhysicalDeviceColorWriteEnableFeaturesEXT -> Int
alignment ~PhysicalDeviceColorWriteEnableFeaturesEXT
_ = 8
  peek :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> IO PhysicalDeviceColorWriteEnableFeaturesEXT
peek = Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> IO PhysicalDeviceColorWriteEnableFeaturesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> IO ()
poke ptr :: Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
ptr poked :: PhysicalDeviceColorWriteEnableFeaturesEXT
poked = Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
-> PhysicalDeviceColorWriteEnableFeaturesEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceColorWriteEnableFeaturesEXT
ptr PhysicalDeviceColorWriteEnableFeaturesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceColorWriteEnableFeaturesEXT where
  zero :: PhysicalDeviceColorWriteEnableFeaturesEXT
zero = Bool -> PhysicalDeviceColorWriteEnableFeaturesEXT
PhysicalDeviceColorWriteEnableFeaturesEXT
           Bool
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 :: PipelineColorWriteCreateInfoEXT
-> (Ptr PipelineColorWriteCreateInfoEXT -> IO b) -> IO b
withCStruct x :: PipelineColorWriteCreateInfoEXT
x f :: Ptr PipelineColorWriteCreateInfoEXT -> IO b
f = Int -> Int -> (Ptr PipelineColorWriteCreateInfoEXT -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PipelineColorWriteCreateInfoEXT -> IO b) -> IO b)
-> (Ptr PipelineColorWriteCreateInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PipelineColorWriteCreateInfoEXT
p -> Ptr PipelineColorWriteCreateInfoEXT
-> PipelineColorWriteCreateInfoEXT -> IO b -> IO b
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 :: Ptr PipelineColorWriteCreateInfoEXT
-> PipelineColorWriteCreateInfoEXT -> IO b -> IO b
pokeCStruct p :: Ptr PipelineColorWriteCreateInfoEXT
p PipelineColorWriteCreateInfoEXT{..} 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 PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COLOR_WRITE_CREATE_INFO_EXT)
    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 PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    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 ("attachmentCount" ::: Word32)
-> ("attachmentCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT
-> Int -> Ptr ("attachmentCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> "attachmentCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("colorWriteEnables" ::: Vector Bool) -> Int
forall a. Vector a -> Int
Data.Vector.length (("colorWriteEnables" ::: Vector Bool) -> Int)
-> ("colorWriteEnables" ::: Vector Bool) -> Int
forall a b. (a -> b) -> a -> b
$ ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) :: Word32))
    "pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables' <- ((("pColorWriteEnables" ::: Ptr Bool32) -> IO b) -> IO b)
-> ContT b IO ("pColorWriteEnables" ::: Ptr Bool32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pColorWriteEnables" ::: Ptr Bool32) -> IO b) -> IO b)
 -> ContT b IO ("pColorWriteEnables" ::: Ptr Bool32))
-> ((("pColorWriteEnables" ::: Ptr Bool32) -> IO b) -> IO b)
-> ContT b IO ("pColorWriteEnables" ::: Ptr Bool32)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pColorWriteEnables" ::: Ptr Bool32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Bool32 ((("colorWriteEnables" ::: Vector Bool) -> Int
forall a. Vector a -> Int
Data.Vector.length ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> Bool -> IO ())
-> ("colorWriteEnables" ::: Vector Bool) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Bool
e -> ("pColorWriteEnables" ::: Ptr Bool32) -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables' ("pColorWriteEnables" ::: Ptr Bool32)
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32) (Bool -> Bool32
boolToBool32 (Bool
e))) ("colorWriteEnables" ::: Vector Bool
colorWriteEnables)
    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 ("pColorWriteEnables" ::: Ptr Bool32)
-> ("pColorWriteEnables" ::: Ptr Bool32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT
-> Int -> Ptr ("pColorWriteEnables" ::: Ptr Bool32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Bool32))) ("pColorWriteEnables" ::: Ptr Bool32
pPColorWriteEnables')
    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 = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PipelineColorWriteCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PipelineColorWriteCreateInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COLOR_WRITE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f
instance FromCStruct PipelineColorWriteCreateInfoEXT where
  peekCStruct :: Ptr PipelineColorWriteCreateInfoEXT
-> IO PipelineColorWriteCreateInfoEXT
peekCStruct p :: Ptr PipelineColorWriteCreateInfoEXT
p = do
    "attachmentCount" ::: Word32
attachmentCount <- Ptr ("attachmentCount" ::: Word32)
-> IO ("attachmentCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT
-> Int -> Ptr ("attachmentCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "pColorWriteEnables" ::: Ptr Bool32
pColorWriteEnables <- Ptr ("pColorWriteEnables" ::: Ptr Bool32)
-> IO ("pColorWriteEnables" ::: Ptr Bool32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Bool32) ((Ptr PipelineColorWriteCreateInfoEXT
p Ptr PipelineColorWriteCreateInfoEXT
-> Int -> Ptr ("pColorWriteEnables" ::: Ptr Bool32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Bool32)))
    "colorWriteEnables" ::: Vector Bool
pColorWriteEnables' <- Int -> (Int -> IO Bool) -> IO ("colorWriteEnables" ::: Vector Bool)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("attachmentCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "attachmentCount" ::: Word32
attachmentCount) (\i :: Int
i -> do
      Bool32
pColorWriteEnablesElem <- ("pColorWriteEnables" ::: Ptr Bool32) -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pColorWriteEnables" ::: Ptr Bool32
pColorWriteEnables ("pColorWriteEnables" ::: Ptr Bool32)
-> Int -> "pColorWriteEnables" ::: Ptr Bool32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32))
      Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Bool32 -> Bool
bool32ToBool Bool32
pColorWriteEnablesElem)
    PipelineColorWriteCreateInfoEXT
-> IO PipelineColorWriteCreateInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineColorWriteCreateInfoEXT
 -> IO PipelineColorWriteCreateInfoEXT)
-> PipelineColorWriteCreateInfoEXT
-> IO PipelineColorWriteCreateInfoEXT
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
           "colorWriteEnables" ::: Vector Bool
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 :: a
$mEXT_COLOR_WRITE_ENABLE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> 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 :: a
$mEXT_COLOR_WRITE_ENABLE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_COLOR_WRITE_ENABLE_EXTENSION_NAME = "VK_EXT_color_write_enable"