{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_conditional_rendering  ( cmdBeginConditionalRenderingEXT
                                                       , cmdUseConditionalRenderingEXT
                                                       , cmdEndConditionalRenderingEXT
                                                       , ConditionalRenderingBeginInfoEXT(..)
                                                       , CommandBufferInheritanceConditionalRenderingInfoEXT(..)
                                                       , PhysicalDeviceConditionalRenderingFeaturesEXT(..)
                                                       , ConditionalRenderingFlagBitsEXT( CONDITIONAL_RENDERING_INVERTED_BIT_EXT
                                                                                        , ..
                                                                                        )
                                                       , ConditionalRenderingFlagsEXT
                                                       , EXT_CONDITIONAL_RENDERING_SPEC_VERSION
                                                       , pattern EXT_CONDITIONAL_RENDERING_SPEC_VERSION
                                                       , EXT_CONDITIONAL_RENDERING_EXTENSION_NAME
                                                       , pattern EXT_CONDITIONAL_RENDERING_EXTENSION_NAME
                                                       ) where
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 GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.IO.Class (MonadIO)
import Data.Bits (Bits)
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 GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdBeginConditionalRenderingEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdEndConditionalRenderingEXT))
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_CONDITIONAL_RENDERING_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdBeginConditionalRenderingEXT
  :: FunPtr (Ptr CommandBuffer_T -> Ptr ConditionalRenderingBeginInfoEXT -> IO ()) -> Ptr CommandBuffer_T -> Ptr ConditionalRenderingBeginInfoEXT -> IO ()
cmdBeginConditionalRenderingEXT :: forall io
                                 . (MonadIO io)
                                => 
                                   
                                   CommandBuffer
                                -> 
                                   
                                   
                                   ConditionalRenderingBeginInfoEXT
                                -> io ()
cmdBeginConditionalRenderingEXT :: CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io ()
cmdBeginConditionalRenderingEXT commandBuffer :: CommandBuffer
commandBuffer conditionalRenderingBegin :: ConditionalRenderingBeginInfoEXT
conditionalRenderingBegin = 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 vkCmdBeginConditionalRenderingEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
vkCmdBeginConditionalRenderingEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pConditionalRenderingBegin"
          ::: Ptr ConditionalRenderingBeginInfoEXT)
      -> IO ())
pVkCmdBeginConditionalRenderingEXT (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
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
vkCmdBeginConditionalRenderingEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pConditionalRenderingBegin"
          ::: Ptr ConditionalRenderingBeginInfoEXT)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> 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 vkCmdBeginConditionalRenderingEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBeginConditionalRenderingEXT' :: Ptr CommandBuffer_T
-> ("pConditionalRenderingBegin"
    ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ()
vkCmdBeginConditionalRenderingEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pConditionalRenderingBegin"
    ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ()
mkVkCmdBeginConditionalRenderingEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
vkCmdBeginConditionalRenderingEXTPtr
  "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin <- ((("pConditionalRenderingBegin"
   ::: Ptr ConditionalRenderingBeginInfoEXT)
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pConditionalRenderingBegin"
      ::: Ptr ConditionalRenderingBeginInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pConditionalRenderingBegin"
    ::: Ptr ConditionalRenderingBeginInfoEXT)
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pConditionalRenderingBegin"
       ::: Ptr ConditionalRenderingBeginInfoEXT))
-> ((("pConditionalRenderingBegin"
      ::: Ptr ConditionalRenderingBeginInfoEXT)
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pConditionalRenderingBegin"
      ::: Ptr ConditionalRenderingBeginInfoEXT)
forall a b. (a -> b) -> a -> b
$ ConditionalRenderingBeginInfoEXT
-> (("pConditionalRenderingBegin"
     ::: Ptr ConditionalRenderingBeginInfoEXT)
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ConditionalRenderingBeginInfoEXT
conditionalRenderingBegin)
  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
$ Ptr CommandBuffer_T
-> ("pConditionalRenderingBegin"
    ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ()
vkCmdBeginConditionalRenderingEXT' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()
cmdUseConditionalRenderingEXT :: forall io r . MonadIO io => CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io r -> io r
cmdUseConditionalRenderingEXT :: CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io r -> io r
cmdUseConditionalRenderingEXT commandBuffer :: CommandBuffer
commandBuffer pConditionalRenderingBegin :: ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin a :: io r
a =
  (CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io ()
forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io ()
cmdBeginConditionalRenderingEXT CommandBuffer
commandBuffer ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin) io () -> io r -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> io r
a io r -> io () -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (CommandBuffer -> io ()
forall (io :: * -> *). MonadIO io => CommandBuffer -> io ()
cmdEndConditionalRenderingEXT CommandBuffer
commandBuffer)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdEndConditionalRenderingEXT
  :: FunPtr (Ptr CommandBuffer_T -> IO ()) -> Ptr CommandBuffer_T -> IO ()
cmdEndConditionalRenderingEXT :: forall io
                               . (MonadIO io)
                              => 
                                 
                                 CommandBuffer
                              -> io ()
cmdEndConditionalRenderingEXT :: CommandBuffer -> io ()
cmdEndConditionalRenderingEXT commandBuffer :: CommandBuffer
commandBuffer = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdEndConditionalRenderingEXTPtr :: FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndConditionalRenderingEXTPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> IO ())
pVkCmdEndConditionalRenderingEXT (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndConditionalRenderingEXTPtr FunPtr (Ptr CommandBuffer_T -> IO ())
-> FunPtr (Ptr CommandBuffer_T -> IO ()) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr CommandBuffer_T -> 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 vkCmdEndConditionalRenderingEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdEndConditionalRenderingEXT' :: Ptr CommandBuffer_T -> IO ()
vkCmdEndConditionalRenderingEXT' = FunPtr (Ptr CommandBuffer_T -> IO ())
-> Ptr CommandBuffer_T -> IO ()
mkVkCmdEndConditionalRenderingEXT FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndConditionalRenderingEXTPtr
  Ptr CommandBuffer_T -> IO ()
vkCmdEndConditionalRenderingEXT' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()
data ConditionalRenderingBeginInfoEXT = ConditionalRenderingBeginInfoEXT
  { 
    ConditionalRenderingBeginInfoEXT -> Buffer
buffer :: Buffer
  , 
    
    ConditionalRenderingBeginInfoEXT -> DeviceSize
offset :: DeviceSize
  , 
    
    ConditionalRenderingBeginInfoEXT -> ConditionalRenderingFlagsEXT
flags :: ConditionalRenderingFlagsEXT
  }
  deriving (Typeable, ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
(ConditionalRenderingBeginInfoEXT
 -> ConditionalRenderingBeginInfoEXT -> Bool)
-> (ConditionalRenderingBeginInfoEXT
    -> ConditionalRenderingBeginInfoEXT -> Bool)
-> Eq ConditionalRenderingBeginInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
$c/= :: ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
== :: ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
$c== :: ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ConditionalRenderingBeginInfoEXT)
#endif
deriving instance Show ConditionalRenderingBeginInfoEXT
instance ToCStruct ConditionalRenderingBeginInfoEXT where
  withCStruct :: ConditionalRenderingBeginInfoEXT
-> (("pConditionalRenderingBegin"
     ::: Ptr ConditionalRenderingBeginInfoEXT)
    -> IO b)
-> IO b
withCStruct x :: ConditionalRenderingBeginInfoEXT
x f :: ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO b
f = Int
-> Int
-> (("pConditionalRenderingBegin"
     ::: Ptr ConditionalRenderingBeginInfoEXT)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((("pConditionalRenderingBegin"
   ::: Ptr ConditionalRenderingBeginInfoEXT)
  -> IO b)
 -> IO b)
-> (("pConditionalRenderingBegin"
     ::: Ptr ConditionalRenderingBeginInfoEXT)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p -> ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> ConditionalRenderingBeginInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ConditionalRenderingBeginInfoEXT
x (("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO b
f "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p)
  pokeCStruct :: ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> ConditionalRenderingBeginInfoEXT -> IO b -> IO b
pokeCStruct p :: "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ConditionalRenderingBeginInfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Buffer)) (Buffer
buffer)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
offset)
    Ptr ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr ConditionalRenderingFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ConditionalRenderingFlagsEXT)) (ConditionalRenderingFlagsEXT
flags)
    IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO b -> IO b
pokeZeroCStruct p :: "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Buffer)) (Buffer
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct ConditionalRenderingBeginInfoEXT where
  peekCStruct :: ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ConditionalRenderingBeginInfoEXT
peekCStruct p :: "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p = do
    Buffer
buffer <- Ptr Buffer -> IO Buffer
forall a. Storable a => Ptr a -> IO a
peek @Buffer (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Buffer))
    DeviceSize
offset <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
    ConditionalRenderingFlagsEXT
flags <- Ptr ConditionalRenderingFlagsEXT -> IO ConditionalRenderingFlagsEXT
forall a. Storable a => Ptr a -> IO a
peek @ConditionalRenderingFlagsEXT (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> Int -> Ptr ConditionalRenderingFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ConditionalRenderingFlagsEXT))
    ConditionalRenderingBeginInfoEXT
-> IO ConditionalRenderingBeginInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ConditionalRenderingBeginInfoEXT
 -> IO ConditionalRenderingBeginInfoEXT)
-> ConditionalRenderingBeginInfoEXT
-> IO ConditionalRenderingBeginInfoEXT
forall a b. (a -> b) -> a -> b
$ Buffer
-> DeviceSize
-> ConditionalRenderingFlagsEXT
-> ConditionalRenderingBeginInfoEXT
ConditionalRenderingBeginInfoEXT
             Buffer
buffer DeviceSize
offset ConditionalRenderingFlagsEXT
flags
instance Storable ConditionalRenderingBeginInfoEXT where
  sizeOf :: ConditionalRenderingBeginInfoEXT -> Int
sizeOf ~ConditionalRenderingBeginInfoEXT
_ = 40
  alignment :: ConditionalRenderingBeginInfoEXT -> Int
alignment ~ConditionalRenderingBeginInfoEXT
_ = 8
  peek :: ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ConditionalRenderingBeginInfoEXT
peek = ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ConditionalRenderingBeginInfoEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> ConditionalRenderingBeginInfoEXT -> IO ()
poke ptr :: "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
ptr poked :: ConditionalRenderingBeginInfoEXT
poked = ("pConditionalRenderingBegin"
 ::: Ptr ConditionalRenderingBeginInfoEXT)
-> ConditionalRenderingBeginInfoEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
ptr ConditionalRenderingBeginInfoEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ConditionalRenderingBeginInfoEXT where
  zero :: ConditionalRenderingBeginInfoEXT
zero = Buffer
-> DeviceSize
-> ConditionalRenderingFlagsEXT
-> ConditionalRenderingBeginInfoEXT
ConditionalRenderingBeginInfoEXT
           Buffer
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           ConditionalRenderingFlagsEXT
forall a. Zero a => a
zero
data CommandBufferInheritanceConditionalRenderingInfoEXT = CommandBufferInheritanceConditionalRenderingInfoEXT
  { 
    
    
    
    
    
    
    CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
conditionalRenderingEnable :: Bool }
  deriving (Typeable, CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
(CommandBufferInheritanceConditionalRenderingInfoEXT
 -> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool)
-> (CommandBufferInheritanceConditionalRenderingInfoEXT
    -> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool)
-> Eq CommandBufferInheritanceConditionalRenderingInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
$c/= :: CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
== :: CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
$c== :: CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CommandBufferInheritanceConditionalRenderingInfoEXT)
#endif
deriving instance Show CommandBufferInheritanceConditionalRenderingInfoEXT
instance ToCStruct CommandBufferInheritanceConditionalRenderingInfoEXT where
  withCStruct :: CommandBufferInheritanceConditionalRenderingInfoEXT
-> (Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
    -> IO b)
-> IO b
withCStruct x :: CommandBufferInheritanceConditionalRenderingInfoEXT
x f :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT -> IO b
f = Int
-> Int
-> (Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT -> IO b)
 -> IO b)
-> (Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p -> Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p CommandBufferInheritanceConditionalRenderingInfoEXT
x (Ptr CommandBufferInheritanceConditionalRenderingInfoEXT -> IO b
f Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p)
  pokeCStruct :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO b
-> IO b
pokeCStruct p :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p CommandBufferInheritanceConditionalRenderingInfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_CONDITIONAL_RENDERING_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
conditionalRenderingEnable))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO b -> IO b
pokeZeroCStruct p :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_CONDITIONAL_RENDERING_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> Int -> 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 CommandBufferInheritanceConditionalRenderingInfoEXT where
  peekCStruct :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO CommandBufferInheritanceConditionalRenderingInfoEXT
peekCStruct p :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p = do
    Bool32
conditionalRenderingEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO CommandBufferInheritanceConditionalRenderingInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CommandBufferInheritanceConditionalRenderingInfoEXT
 -> IO CommandBufferInheritanceConditionalRenderingInfoEXT)
-> CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO CommandBufferInheritanceConditionalRenderingInfoEXT
forall a b. (a -> b) -> a -> b
$ Bool -> CommandBufferInheritanceConditionalRenderingInfoEXT
CommandBufferInheritanceConditionalRenderingInfoEXT
             (Bool32 -> Bool
bool32ToBool Bool32
conditionalRenderingEnable)
instance Storable CommandBufferInheritanceConditionalRenderingInfoEXT where
  sizeOf :: CommandBufferInheritanceConditionalRenderingInfoEXT -> Int
sizeOf ~CommandBufferInheritanceConditionalRenderingInfoEXT
_ = 24
  alignment :: CommandBufferInheritanceConditionalRenderingInfoEXT -> Int
alignment ~CommandBufferInheritanceConditionalRenderingInfoEXT
_ = 8
  peek :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO CommandBufferInheritanceConditionalRenderingInfoEXT
peek = Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO CommandBufferInheritanceConditionalRenderingInfoEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> IO ()
poke ptr :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
ptr poked :: CommandBufferInheritanceConditionalRenderingInfoEXT
poked = Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO ()
-> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
ptr CommandBufferInheritanceConditionalRenderingInfoEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero CommandBufferInheritanceConditionalRenderingInfoEXT where
  zero :: CommandBufferInheritanceConditionalRenderingInfoEXT
zero = Bool -> CommandBufferInheritanceConditionalRenderingInfoEXT
CommandBufferInheritanceConditionalRenderingInfoEXT
           Bool
forall a. Zero a => a
zero
data PhysicalDeviceConditionalRenderingFeaturesEXT = PhysicalDeviceConditionalRenderingFeaturesEXT
  { 
    
    PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
conditionalRendering :: Bool
  , 
    
    
    PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
inheritedConditionalRendering :: Bool
  }
  deriving (Typeable, PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
(PhysicalDeviceConditionalRenderingFeaturesEXT
 -> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool)
-> (PhysicalDeviceConditionalRenderingFeaturesEXT
    -> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool)
-> Eq PhysicalDeviceConditionalRenderingFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
$c/= :: PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
== :: PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
$c== :: PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceConditionalRenderingFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceConditionalRenderingFeaturesEXT
instance ToCStruct PhysicalDeviceConditionalRenderingFeaturesEXT where
  withCStruct :: PhysicalDeviceConditionalRenderingFeaturesEXT
-> (Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceConditionalRenderingFeaturesEXT
x f :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p -> Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p PhysicalDeviceConditionalRenderingFeaturesEXT
x (Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b
f Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p PhysicalDeviceConditionalRenderingFeaturesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
conditionalRendering))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
inheritedConditionalRendering))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f
instance FromCStruct PhysicalDeviceConditionalRenderingFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> IO PhysicalDeviceConditionalRenderingFeaturesEXT
peekCStruct p :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p = do
    Bool32
conditionalRendering <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
inheritedConditionalRendering <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    PhysicalDeviceConditionalRenderingFeaturesEXT
-> IO PhysicalDeviceConditionalRenderingFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceConditionalRenderingFeaturesEXT
 -> IO PhysicalDeviceConditionalRenderingFeaturesEXT)
-> PhysicalDeviceConditionalRenderingFeaturesEXT
-> IO PhysicalDeviceConditionalRenderingFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> PhysicalDeviceConditionalRenderingFeaturesEXT
PhysicalDeviceConditionalRenderingFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
conditionalRendering) (Bool32 -> Bool
bool32ToBool Bool32
inheritedConditionalRendering)
instance Storable PhysicalDeviceConditionalRenderingFeaturesEXT where
  sizeOf :: PhysicalDeviceConditionalRenderingFeaturesEXT -> Int
sizeOf ~PhysicalDeviceConditionalRenderingFeaturesEXT
_ = 24
  alignment :: PhysicalDeviceConditionalRenderingFeaturesEXT -> Int
alignment ~PhysicalDeviceConditionalRenderingFeaturesEXT
_ = 8
  peek :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> IO PhysicalDeviceConditionalRenderingFeaturesEXT
peek = Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> IO PhysicalDeviceConditionalRenderingFeaturesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> IO ()
poke ptr :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
ptr poked :: PhysicalDeviceConditionalRenderingFeaturesEXT
poked = Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
ptr PhysicalDeviceConditionalRenderingFeaturesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceConditionalRenderingFeaturesEXT where
  zero :: PhysicalDeviceConditionalRenderingFeaturesEXT
zero = Bool -> Bool -> PhysicalDeviceConditionalRenderingFeaturesEXT
PhysicalDeviceConditionalRenderingFeaturesEXT
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
newtype ConditionalRenderingFlagBitsEXT = ConditionalRenderingFlagBitsEXT Flags
  deriving newtype (ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
(ConditionalRenderingFlagsEXT
 -> ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Bool)
-> Eq ConditionalRenderingFlagsEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c/= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
== :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c== :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
Eq, Eq ConditionalRenderingFlagsEXT
Eq ConditionalRenderingFlagsEXT =>
(ConditionalRenderingFlagsEXT
 -> ConditionalRenderingFlagsEXT -> Ordering)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> Ord ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Ordering
ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$cmin :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
max :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$cmax :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
>= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c>= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
> :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c> :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
<= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c<= :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
< :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
$c< :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Bool
compare :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Ordering
$ccompare :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> Ordering
$cp1Ord :: Eq ConditionalRenderingFlagsEXT
Ord, Ptr b -> Int -> IO ConditionalRenderingFlagsEXT
Ptr b -> Int -> ConditionalRenderingFlagsEXT -> IO ()
Ptr ConditionalRenderingFlagsEXT -> IO ConditionalRenderingFlagsEXT
Ptr ConditionalRenderingFlagsEXT
-> Int -> IO ConditionalRenderingFlagsEXT
Ptr ConditionalRenderingFlagsEXT
-> Int -> ConditionalRenderingFlagsEXT -> IO ()
Ptr ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> IO ()
ConditionalRenderingFlagsEXT -> Int
(ConditionalRenderingFlagsEXT -> Int)
-> (ConditionalRenderingFlagsEXT -> Int)
-> (Ptr ConditionalRenderingFlagsEXT
    -> Int -> IO ConditionalRenderingFlagsEXT)
-> (Ptr ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO ConditionalRenderingFlagsEXT)
-> (forall b.
    Ptr b -> Int -> ConditionalRenderingFlagsEXT -> IO ())
-> (Ptr ConditionalRenderingFlagsEXT
    -> IO ConditionalRenderingFlagsEXT)
-> (Ptr ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> IO ())
-> Storable ConditionalRenderingFlagsEXT
forall b. Ptr b -> Int -> IO ConditionalRenderingFlagsEXT
forall b. Ptr b -> Int -> ConditionalRenderingFlagsEXT -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> IO ()
$cpoke :: Ptr ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> IO ()
peek :: Ptr ConditionalRenderingFlagsEXT -> IO ConditionalRenderingFlagsEXT
$cpeek :: Ptr ConditionalRenderingFlagsEXT -> IO ConditionalRenderingFlagsEXT
pokeByteOff :: Ptr b -> Int -> ConditionalRenderingFlagsEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ConditionalRenderingFlagsEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO ConditionalRenderingFlagsEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ConditionalRenderingFlagsEXT
pokeElemOff :: Ptr ConditionalRenderingFlagsEXT
-> Int -> ConditionalRenderingFlagsEXT -> IO ()
$cpokeElemOff :: Ptr ConditionalRenderingFlagsEXT
-> Int -> ConditionalRenderingFlagsEXT -> IO ()
peekElemOff :: Ptr ConditionalRenderingFlagsEXT
-> Int -> IO ConditionalRenderingFlagsEXT
$cpeekElemOff :: Ptr ConditionalRenderingFlagsEXT
-> Int -> IO ConditionalRenderingFlagsEXT
alignment :: ConditionalRenderingFlagsEXT -> Int
$calignment :: ConditionalRenderingFlagsEXT -> Int
sizeOf :: ConditionalRenderingFlagsEXT -> Int
$csizeOf :: ConditionalRenderingFlagsEXT -> Int
Storable, ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT -> Zero ConditionalRenderingFlagsEXT
forall a. a -> Zero a
zero :: ConditionalRenderingFlagsEXT
$czero :: ConditionalRenderingFlagsEXT
Zero, Eq ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT
Eq ConditionalRenderingFlagsEXT =>
(ConditionalRenderingFlagsEXT
 -> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> ConditionalRenderingFlagsEXT
-> (Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT -> Int -> Bool)
-> (ConditionalRenderingFlagsEXT -> Maybe Int)
-> (ConditionalRenderingFlagsEXT -> Int)
-> (ConditionalRenderingFlagsEXT -> Bool)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT
    -> Int -> ConditionalRenderingFlagsEXT)
-> (ConditionalRenderingFlagsEXT -> Int)
-> Bits ConditionalRenderingFlagsEXT
Int -> ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT -> Bool
ConditionalRenderingFlagsEXT -> Int
ConditionalRenderingFlagsEXT -> Maybe Int
ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT -> Int -> Bool
ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: ConditionalRenderingFlagsEXT -> Int
$cpopCount :: ConditionalRenderingFlagsEXT -> Int
rotateR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$crotateR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
rotateL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$crotateL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
unsafeShiftR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cunsafeShiftR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
shiftR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cshiftR :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
unsafeShiftL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cunsafeShiftL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
shiftL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cshiftL :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
isSigned :: ConditionalRenderingFlagsEXT -> Bool
$cisSigned :: ConditionalRenderingFlagsEXT -> Bool
bitSize :: ConditionalRenderingFlagsEXT -> Int
$cbitSize :: ConditionalRenderingFlagsEXT -> Int
bitSizeMaybe :: ConditionalRenderingFlagsEXT -> Maybe Int
$cbitSizeMaybe :: ConditionalRenderingFlagsEXT -> Maybe Int
testBit :: ConditionalRenderingFlagsEXT -> Int -> Bool
$ctestBit :: ConditionalRenderingFlagsEXT -> Int -> Bool
complementBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$ccomplementBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
clearBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cclearBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
setBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$csetBit :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
bit :: Int -> ConditionalRenderingFlagsEXT
$cbit :: Int -> ConditionalRenderingFlagsEXT
zeroBits :: ConditionalRenderingFlagsEXT
$czeroBits :: ConditionalRenderingFlagsEXT
rotate :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$crotate :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
shift :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
$cshift :: ConditionalRenderingFlagsEXT -> Int -> ConditionalRenderingFlagsEXT
complement :: ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$ccomplement :: ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
xor :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$cxor :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
.|. :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$c.|. :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
.&. :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$c.&. :: ConditionalRenderingFlagsEXT
-> ConditionalRenderingFlagsEXT -> ConditionalRenderingFlagsEXT
$cp1Bits :: Eq ConditionalRenderingFlagsEXT
Bits)
pattern $bCONDITIONAL_RENDERING_INVERTED_BIT_EXT :: ConditionalRenderingFlagsEXT
$mCONDITIONAL_RENDERING_INVERTED_BIT_EXT :: forall r.
ConditionalRenderingFlagsEXT -> (Void# -> r) -> (Void# -> r) -> r
CONDITIONAL_RENDERING_INVERTED_BIT_EXT = ConditionalRenderingFlagBitsEXT 0x00000001
type ConditionalRenderingFlagsEXT = ConditionalRenderingFlagBitsEXT
instance Show ConditionalRenderingFlagBitsEXT where
  showsPrec :: Int -> ConditionalRenderingFlagsEXT -> ShowS
showsPrec p :: Int
p = \case
    CONDITIONAL_RENDERING_INVERTED_BIT_EXT -> String -> ShowS
showString "CONDITIONAL_RENDERING_INVERTED_BIT_EXT"
    ConditionalRenderingFlagBitsEXT x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "ConditionalRenderingFlagBitsEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)
instance Read ConditionalRenderingFlagBitsEXT where
  readPrec :: ReadPrec ConditionalRenderingFlagsEXT
readPrec = ReadPrec ConditionalRenderingFlagsEXT
-> ReadPrec ConditionalRenderingFlagsEXT
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec ConditionalRenderingFlagsEXT)]
-> ReadPrec ConditionalRenderingFlagsEXT
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("CONDITIONAL_RENDERING_INVERTED_BIT_EXT", ConditionalRenderingFlagsEXT
-> ReadPrec ConditionalRenderingFlagsEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConditionalRenderingFlagsEXT
CONDITIONAL_RENDERING_INVERTED_BIT_EXT)]
                     ReadPrec ConditionalRenderingFlagsEXT
-> ReadPrec ConditionalRenderingFlagsEXT
-> ReadPrec ConditionalRenderingFlagsEXT
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec ConditionalRenderingFlagsEXT
-> ReadPrec ConditionalRenderingFlagsEXT
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "ConditionalRenderingFlagBitsEXT")
                       Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
                       ConditionalRenderingFlagsEXT
-> ReadPrec ConditionalRenderingFlagsEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> ConditionalRenderingFlagsEXT
ConditionalRenderingFlagBitsEXT Flags
v)))
type EXT_CONDITIONAL_RENDERING_SPEC_VERSION = 2
pattern EXT_CONDITIONAL_RENDERING_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_CONDITIONAL_RENDERING_SPEC_VERSION :: a
$mEXT_CONDITIONAL_RENDERING_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_CONDITIONAL_RENDERING_SPEC_VERSION = 2
type EXT_CONDITIONAL_RENDERING_EXTENSION_NAME = "VK_EXT_conditional_rendering"
pattern EXT_CONDITIONAL_RENDERING_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_CONDITIONAL_RENDERING_EXTENSION_NAME :: a
$mEXT_CONDITIONAL_RENDERING_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_CONDITIONAL_RENDERING_EXTENSION_NAME = "VK_EXT_conditional_rendering"