{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_conditional_rendering ( cmdBeginConditionalRenderingEXT
, cmdUseConditionalRenderingEXT
, cmdEndConditionalRenderingEXT
, ConditionalRenderingBeginInfoEXT(..)
, CommandBufferInheritanceConditionalRenderingInfoEXT(..)
, PhysicalDeviceConditionalRenderingFeaturesEXT(..)
, ConditionalRenderingFlagsEXT
, ConditionalRenderingFlagBitsEXT( CONDITIONAL_RENDERING_INVERTED_BIT_EXT
, ..
)
, EXT_CONDITIONAL_RENDERING_SPEC_VERSION
, pattern EXT_CONDITIONAL_RENDERING_SPEC_VERSION
, EXT_CONDITIONAL_RENDERING_EXTENSION_NAME
, pattern EXT_CONDITIONAL_RENDERING_EXTENSION_NAME
) where
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
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 GHC.Show (showString)
import Numeric (showHex)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import 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 GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
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(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.Core10.Enums.StructureType (StructureType)
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 :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io ()
cmdBeginConditionalRenderingEXT CommandBuffer
commandBuffer
ConditionalRenderingBeginInfoEXT
conditionalRenderingBegin = 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 vkCmdBeginConditionalRenderingEXTPtr :: FunPtr
(Ptr CommandBuffer_T
-> ("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ())
vkCmdBeginConditionalRenderingEXTPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> ("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ())
pVkCmdBeginConditionalRenderingEXT (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
-> ("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ())
vkCmdBeginConditionalRenderingEXTPtr 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 vkCmdBeginConditionalRenderingEXT is null" forall a. Maybe a
Nothing 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 <- 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. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ConditionalRenderingBeginInfoEXT
conditionalRenderingBegin)
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
"vkCmdBeginConditionalRenderingEXT" (Ptr CommandBuffer_T
-> ("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ()
vkCmdBeginConditionalRenderingEXT'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
"pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
cmdUseConditionalRenderingEXT :: forall io r . MonadIO io => CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io r -> io r
cmdUseConditionalRenderingEXT :: forall (io :: * -> *) r.
MonadIO io =>
CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io r -> io r
cmdUseConditionalRenderingEXT CommandBuffer
commandBuffer ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin io r
a =
(forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> ConditionalRenderingBeginInfoEXT -> io ()
cmdBeginConditionalRenderingEXT CommandBuffer
commandBuffer
ConditionalRenderingBeginInfoEXT
pConditionalRenderingBegin) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> io r
a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (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 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> io ()
cmdEndConditionalRenderingEXT CommandBuffer
commandBuffer = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let vkCmdEndConditionalRenderingEXTPtr :: FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndConditionalRenderingEXTPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> IO ())
pVkCmdEndConditionalRenderingEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdEndConditionalRenderingEXTPtr 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 vkCmdEndConditionalRenderingEXT is null" forall a. Maybe a
Nothing 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
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdEndConditionalRenderingEXT" (Ptr CommandBuffer_T -> IO ()
vkCmdEndConditionalRenderingEXT'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
data ConditionalRenderingBeginInfoEXT = ConditionalRenderingBeginInfoEXT
{
ConditionalRenderingBeginInfoEXT -> Buffer
buffer :: Buffer
,
ConditionalRenderingBeginInfoEXT -> DeviceSize
offset :: DeviceSize
,
ConditionalRenderingBeginInfoEXT -> ConditionalRenderingFlagBitsEXT
flags :: ConditionalRenderingFlagsEXT
}
deriving (Typeable, ConditionalRenderingBeginInfoEXT
-> ConditionalRenderingBeginInfoEXT -> Bool
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 :: forall b.
ConditionalRenderingBeginInfoEXT
-> (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO b)
-> IO b
withCStruct ConditionalRenderingBeginInfoEXT
x ("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \"pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p -> 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 :: forall b.
("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> ConditionalRenderingBeginInfoEXT -> IO b -> IO b
pokeCStruct "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p ConditionalRenderingBeginInfoEXT{DeviceSize
Buffer
ConditionalRenderingFlagBitsEXT
flags :: ConditionalRenderingFlagBitsEXT
offset :: DeviceSize
buffer :: Buffer
$sel:flags:ConditionalRenderingBeginInfoEXT :: ConditionalRenderingBeginInfoEXT -> ConditionalRenderingFlagBitsEXT
$sel:offset:ConditionalRenderingBeginInfoEXT :: ConditionalRenderingBeginInfoEXT -> DeviceSize
$sel:buffer:ConditionalRenderingBeginInfoEXT :: ConditionalRenderingBeginInfoEXT -> Buffer
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
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 (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer)) (Buffer
buffer)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (DeviceSize
offset)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr ConditionalRenderingFlagsEXT)) (ConditionalRenderingFlagBitsEXT
flags)
IO b
f
cStructSize :: Int
cStructSize = Int
40
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO b -> IO b
pokeZeroCStruct "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
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 (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ConditionalRenderingBeginInfoEXT where
peekCStruct :: ("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ConditionalRenderingBeginInfoEXT
peekCStruct "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p = do
Buffer
buffer <- forall a. Storable a => Ptr a -> IO a
peek @Buffer (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer))
DeviceSize
offset <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize))
ConditionalRenderingFlagBitsEXT
flags <- forall a. Storable a => Ptr a -> IO a
peek @ConditionalRenderingFlagsEXT (("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr ConditionalRenderingFlagsEXT))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Buffer
-> DeviceSize
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingBeginInfoEXT
ConditionalRenderingBeginInfoEXT
Buffer
buffer DeviceSize
offset ConditionalRenderingFlagBitsEXT
flags
instance Storable ConditionalRenderingBeginInfoEXT where
sizeOf :: ConditionalRenderingBeginInfoEXT -> Int
sizeOf ~ConditionalRenderingBeginInfoEXT
_ = Int
40
alignment :: ConditionalRenderingBeginInfoEXT -> Int
alignment ~ConditionalRenderingBeginInfoEXT
_ = Int
8
peek :: ("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> IO ConditionalRenderingBeginInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT)
-> ConditionalRenderingBeginInfoEXT -> IO ()
poke "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
ptr ConditionalRenderingBeginInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pConditionalRenderingBegin"
::: Ptr ConditionalRenderingBeginInfoEXT
ptr ConditionalRenderingBeginInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ConditionalRenderingBeginInfoEXT where
zero :: ConditionalRenderingBeginInfoEXT
zero = Buffer
-> DeviceSize
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingBeginInfoEXT
ConditionalRenderingBeginInfoEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data CommandBufferInheritanceConditionalRenderingInfoEXT = CommandBufferInheritanceConditionalRenderingInfoEXT
{
CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
conditionalRenderingEnable :: Bool }
deriving (Typeable, CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
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 :: forall b.
CommandBufferInheritanceConditionalRenderingInfoEXT
-> (Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO b)
-> IO b
withCStruct CommandBufferInheritanceConditionalRenderingInfoEXT
x Ptr CommandBufferInheritanceConditionalRenderingInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p -> 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 :: forall b.
Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO b
-> IO b
pokeCStruct Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p CommandBufferInheritanceConditionalRenderingInfoEXT{Bool
conditionalRenderingEnable :: Bool
$sel:conditionalRenderingEnable:CommandBufferInheritanceConditionalRenderingInfoEXT :: CommandBufferInheritanceConditionalRenderingInfoEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_CONDITIONAL_RENDERING_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
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 CommandBufferInheritanceConditionalRenderingInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
conditionalRenderingEnable))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO b -> IO b
pokeZeroCStruct Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_CONDITIONAL_RENDERING_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
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 CommandBufferInheritanceConditionalRenderingInfoEXT
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 CommandBufferInheritanceConditionalRenderingInfoEXT where
peekCStruct :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO CommandBufferInheritanceConditionalRenderingInfoEXT
peekCStruct Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
p = do
Bool32
conditionalRenderingEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
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 -> CommandBufferInheritanceConditionalRenderingInfoEXT
CommandBufferInheritanceConditionalRenderingInfoEXT
(Bool32 -> Bool
bool32ToBool Bool32
conditionalRenderingEnable)
instance Storable CommandBufferInheritanceConditionalRenderingInfoEXT where
sizeOf :: CommandBufferInheritanceConditionalRenderingInfoEXT -> Int
sizeOf ~CommandBufferInheritanceConditionalRenderingInfoEXT
_ = Int
24
alignment :: CommandBufferInheritanceConditionalRenderingInfoEXT -> Int
alignment ~CommandBufferInheritanceConditionalRenderingInfoEXT
_ = Int
8
peek :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> IO CommandBufferInheritanceConditionalRenderingInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
-> CommandBufferInheritanceConditionalRenderingInfoEXT -> IO ()
poke Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
ptr CommandBufferInheritanceConditionalRenderingInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CommandBufferInheritanceConditionalRenderingInfoEXT
ptr CommandBufferInheritanceConditionalRenderingInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero CommandBufferInheritanceConditionalRenderingInfoEXT where
zero :: CommandBufferInheritanceConditionalRenderingInfoEXT
zero = Bool -> CommandBufferInheritanceConditionalRenderingInfoEXT
CommandBufferInheritanceConditionalRenderingInfoEXT
forall a. Zero a => a
zero
data PhysicalDeviceConditionalRenderingFeaturesEXT = PhysicalDeviceConditionalRenderingFeaturesEXT
{
PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
conditionalRendering :: Bool
,
PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
inheritedConditionalRendering :: Bool
}
deriving (Typeable, PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
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 :: forall b.
PhysicalDeviceConditionalRenderingFeaturesEXT
-> (Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceConditionalRenderingFeaturesEXT
x Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p -> 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 :: forall b.
Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p PhysicalDeviceConditionalRenderingFeaturesEXT{Bool
inheritedConditionalRendering :: Bool
conditionalRendering :: Bool
$sel:inheritedConditionalRendering:PhysicalDeviceConditionalRenderingFeaturesEXT :: PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
$sel:conditionalRendering:PhysicalDeviceConditionalRenderingFeaturesEXT :: PhysicalDeviceConditionalRenderingFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
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 PhysicalDeviceConditionalRenderingFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
conditionalRendering))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
inheritedConditionalRendering))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceConditionalRenderingFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
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 PhysicalDeviceConditionalRenderingFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceConditionalRenderingFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> IO PhysicalDeviceConditionalRenderingFeaturesEXT
peekCStruct Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p = do
Bool32
conditionalRendering <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
inheritedConditionalRendering <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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
_ = Int
24
alignment :: PhysicalDeviceConditionalRenderingFeaturesEXT -> Int
alignment ~PhysicalDeviceConditionalRenderingFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> IO PhysicalDeviceConditionalRenderingFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
-> PhysicalDeviceConditionalRenderingFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
ptr PhysicalDeviceConditionalRenderingFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceConditionalRenderingFeaturesEXT
ptr PhysicalDeviceConditionalRenderingFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceConditionalRenderingFeaturesEXT where
zero :: PhysicalDeviceConditionalRenderingFeaturesEXT
zero = Bool -> Bool -> PhysicalDeviceConditionalRenderingFeaturesEXT
PhysicalDeviceConditionalRenderingFeaturesEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type ConditionalRenderingFlagsEXT = ConditionalRenderingFlagBitsEXT
newtype ConditionalRenderingFlagBitsEXT = ConditionalRenderingFlagBitsEXT Flags
deriving newtype (ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
$c/= :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
== :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
$c== :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
Eq, Eq ConditionalRenderingFlagBitsEXT
ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Ordering
ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
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 :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
$cmin :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
max :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
$cmax :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
>= :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
$c>= :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
> :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
$c> :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
<= :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
$c<= :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
< :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
$c< :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Bool
compare :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Ordering
$ccompare :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> Ordering
Ord, Ptr ConditionalRenderingFlagBitsEXT
-> IO ConditionalRenderingFlagBitsEXT
Ptr ConditionalRenderingFlagBitsEXT
-> Int -> IO ConditionalRenderingFlagBitsEXT
Ptr ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT -> IO ()
Ptr ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> IO ()
ConditionalRenderingFlagBitsEXT -> Int
forall b. Ptr b -> Int -> IO ConditionalRenderingFlagBitsEXT
forall b. Ptr b -> Int -> ConditionalRenderingFlagBitsEXT -> 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 ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> IO ()
$cpoke :: Ptr ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT -> IO ()
peek :: Ptr ConditionalRenderingFlagBitsEXT
-> IO ConditionalRenderingFlagBitsEXT
$cpeek :: Ptr ConditionalRenderingFlagBitsEXT
-> IO ConditionalRenderingFlagBitsEXT
pokeByteOff :: forall b. Ptr b -> Int -> ConditionalRenderingFlagBitsEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ConditionalRenderingFlagBitsEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO ConditionalRenderingFlagBitsEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ConditionalRenderingFlagBitsEXT
pokeElemOff :: Ptr ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT -> IO ()
$cpokeElemOff :: Ptr ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT -> IO ()
peekElemOff :: Ptr ConditionalRenderingFlagBitsEXT
-> Int -> IO ConditionalRenderingFlagBitsEXT
$cpeekElemOff :: Ptr ConditionalRenderingFlagBitsEXT
-> Int -> IO ConditionalRenderingFlagBitsEXT
alignment :: ConditionalRenderingFlagBitsEXT -> Int
$calignment :: ConditionalRenderingFlagBitsEXT -> Int
sizeOf :: ConditionalRenderingFlagBitsEXT -> Int
$csizeOf :: ConditionalRenderingFlagBitsEXT -> Int
Storable, ConditionalRenderingFlagBitsEXT
forall a. a -> Zero a
zero :: ConditionalRenderingFlagBitsEXT
$czero :: ConditionalRenderingFlagBitsEXT
Zero, Eq ConditionalRenderingFlagBitsEXT
ConditionalRenderingFlagBitsEXT
Int -> ConditionalRenderingFlagBitsEXT
ConditionalRenderingFlagBitsEXT -> Bool
ConditionalRenderingFlagBitsEXT -> Int
ConditionalRenderingFlagBitsEXT -> Maybe Int
ConditionalRenderingFlagBitsEXT -> ConditionalRenderingFlagBitsEXT
ConditionalRenderingFlagBitsEXT -> Int -> Bool
ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
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 :: ConditionalRenderingFlagBitsEXT -> Int
$cpopCount :: ConditionalRenderingFlagBitsEXT -> Int
rotateR :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$crotateR :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
rotateL :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$crotateL :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
unsafeShiftR :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$cunsafeShiftR :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
shiftR :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$cshiftR :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
unsafeShiftL :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$cunsafeShiftL :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
shiftL :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$cshiftL :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
isSigned :: ConditionalRenderingFlagBitsEXT -> Bool
$cisSigned :: ConditionalRenderingFlagBitsEXT -> Bool
bitSize :: ConditionalRenderingFlagBitsEXT -> Int
$cbitSize :: ConditionalRenderingFlagBitsEXT -> Int
bitSizeMaybe :: ConditionalRenderingFlagBitsEXT -> Maybe Int
$cbitSizeMaybe :: ConditionalRenderingFlagBitsEXT -> Maybe Int
testBit :: ConditionalRenderingFlagBitsEXT -> Int -> Bool
$ctestBit :: ConditionalRenderingFlagBitsEXT -> Int -> Bool
complementBit :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$ccomplementBit :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
clearBit :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$cclearBit :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
setBit :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$csetBit :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
bit :: Int -> ConditionalRenderingFlagBitsEXT
$cbit :: Int -> ConditionalRenderingFlagBitsEXT
zeroBits :: ConditionalRenderingFlagBitsEXT
$czeroBits :: ConditionalRenderingFlagBitsEXT
rotate :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$crotate :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
shift :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
$cshift :: ConditionalRenderingFlagBitsEXT
-> Int -> ConditionalRenderingFlagBitsEXT
complement :: ConditionalRenderingFlagBitsEXT -> ConditionalRenderingFlagBitsEXT
$ccomplement :: ConditionalRenderingFlagBitsEXT -> ConditionalRenderingFlagBitsEXT
xor :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
$cxor :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
.|. :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
$c.|. :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
.&. :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
$c.&. :: ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
-> ConditionalRenderingFlagBitsEXT
Bits, Bits ConditionalRenderingFlagBitsEXT
ConditionalRenderingFlagBitsEXT -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: ConditionalRenderingFlagBitsEXT -> Int
$ccountTrailingZeros :: ConditionalRenderingFlagBitsEXT -> Int
countLeadingZeros :: ConditionalRenderingFlagBitsEXT -> Int
$ccountLeadingZeros :: ConditionalRenderingFlagBitsEXT -> Int
finiteBitSize :: ConditionalRenderingFlagBitsEXT -> Int
$cfiniteBitSize :: ConditionalRenderingFlagBitsEXT -> Int
FiniteBits)
pattern $bCONDITIONAL_RENDERING_INVERTED_BIT_EXT :: ConditionalRenderingFlagBitsEXT
$mCONDITIONAL_RENDERING_INVERTED_BIT_EXT :: forall {r}.
ConditionalRenderingFlagBitsEXT
-> ((# #) -> r) -> ((# #) -> r) -> r
CONDITIONAL_RENDERING_INVERTED_BIT_EXT = ConditionalRenderingFlagBitsEXT 0x00000001
conNameConditionalRenderingFlagBitsEXT :: String
conNameConditionalRenderingFlagBitsEXT :: String
conNameConditionalRenderingFlagBitsEXT = String
"ConditionalRenderingFlagBitsEXT"
enumPrefixConditionalRenderingFlagBitsEXT :: String
enumPrefixConditionalRenderingFlagBitsEXT :: String
enumPrefixConditionalRenderingFlagBitsEXT = String
"CONDITIONAL_RENDERING_INVERTED_BIT_EXT"
showTableConditionalRenderingFlagBitsEXT :: [(ConditionalRenderingFlagBitsEXT, String)]
showTableConditionalRenderingFlagBitsEXT :: [(ConditionalRenderingFlagBitsEXT, String)]
showTableConditionalRenderingFlagBitsEXT =
[
( ConditionalRenderingFlagBitsEXT
CONDITIONAL_RENDERING_INVERTED_BIT_EXT
, String
""
)
]
instance Show ConditionalRenderingFlagBitsEXT where
showsPrec :: Int -> ConditionalRenderingFlagBitsEXT -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixConditionalRenderingFlagBitsEXT
[(ConditionalRenderingFlagBitsEXT, String)]
showTableConditionalRenderingFlagBitsEXT
String
conNameConditionalRenderingFlagBitsEXT
(\(ConditionalRenderingFlagBitsEXT Flags
x) -> Flags
x)
(\Flags
x -> String -> ShowS
showString String
"0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)
instance Read ConditionalRenderingFlagBitsEXT where
readPrec :: ReadPrec ConditionalRenderingFlagBitsEXT
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixConditionalRenderingFlagBitsEXT
[(ConditionalRenderingFlagBitsEXT, String)]
showTableConditionalRenderingFlagBitsEXT
String
conNameConditionalRenderingFlagBitsEXT
Flags -> ConditionalRenderingFlagBitsEXT
ConditionalRenderingFlagBitsEXT
type EXT_CONDITIONAL_RENDERING_SPEC_VERSION = 2
pattern EXT_CONDITIONAL_RENDERING_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_CONDITIONAL_RENDERING_SPEC_VERSION :: forall a. Integral a => a
$mEXT_CONDITIONAL_RENDERING_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> 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 :: forall a. (Eq a, IsString a) => a
$mEXT_CONDITIONAL_RENDERING_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_CONDITIONAL_RENDERING_EXTENSION_NAME = "VK_EXT_conditional_rendering"