{-# language CPP #-}
module Vulkan.Extensions.VK_NV_coverage_reduction_mode ( getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV
, PhysicalDeviceCoverageReductionModeFeaturesNV(..)
, PipelineCoverageReductionStateCreateInfoNV(..)
, FramebufferMixedSamplesCombinationNV(..)
, PipelineCoverageReductionStateCreateFlagsNV(..)
, CoverageReductionModeNV( COVERAGE_REDUCTION_MODE_MERGE_NV
, COVERAGE_REDUCTION_MODE_TRUNCATE_NV
, ..
)
, NV_COVERAGE_REDUCTION_MODE_SPEC_VERSION
, pattern NV_COVERAGE_REDUCTION_MODE_SPEC_VERSION
, NV_COVERAGE_REDUCTION_MODE_EXTENSION_NAME
, pattern NV_COVERAGE_REDUCTION_MODE_EXTENSION_NAME
) where
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
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 GHC.Show (showsPrec)
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 Data.Vector (generateM)
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.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import Data.Word (Word32)
import Text.Read.Lex (Lexeme(Ident))
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.BaseType (bool32ToBool)
import Vulkan.Core10.BaseType (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.BaseType (Bool32)
import Vulkan.Core10.BaseType (Flags)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_FRAMEBUFFER_MIXED_SAMPLES_COMBINATION_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_COVERAGE_REDUCTION_MODE_FEATURES_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_COVERAGE_REDUCTION_STATE_CREATE_INFO_NV))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV
:: FunPtr (Ptr PhysicalDevice_T -> Ptr Word32 -> Ptr FramebufferMixedSamplesCombinationNV -> IO Result) -> Ptr PhysicalDevice_T -> Ptr Word32 -> Ptr FramebufferMixedSamplesCombinationNV -> IO Result
getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV :: forall io . MonadIO io => PhysicalDevice -> io (Result, ("combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV :: PhysicalDevice
-> io
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV physicalDevice :: PhysicalDevice
physicalDevice = IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> io
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> io
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> (ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> io
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> io
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> io
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall a b. (a -> b) -> a -> b
$ do
let vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNVPtr :: FunPtr
(Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result)
vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNVPtr = InstanceCmds
-> FunPtr
(Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result)
pVkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
IO ()
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
())
-> IO ()
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result)
vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNVPtr FunPtr
(Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result)
-> FunPtr
(Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result)
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 vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' :: Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result
vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' = FunPtr
(Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result)
-> Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result
mkVkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV FunPtr
(Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result)
vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNVPtr
let physicalDevice' :: Ptr PhysicalDevice_T
physicalDevice' = PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)
"pCombinationCount" ::: Ptr Word32
pPCombinationCount <- ((("pCombinationCount" ::: Ptr Word32)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
("pCombinationCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCombinationCount" ::: Ptr Word32)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
("pCombinationCount" ::: Ptr Word32))
-> ((("pCombinationCount" ::: Ptr Word32)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
("pCombinationCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pCombinationCount" ::: Ptr Word32)
-> (("pCombinationCount" ::: Ptr Word32) -> IO ())
-> (("pCombinationCount" ::: Ptr Word32)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pCombinationCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pCombinationCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Result)
-> IO Result
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result
vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' Ptr PhysicalDevice_T
physicalDevice' ("pCombinationCount" ::: Ptr Word32
pPCombinationCount) ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
forall a. Ptr a
nullPtr)
IO ()
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
())
-> IO ()
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
Word32
pCombinationCount <- IO Word32
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Word32)
-> IO Word32
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Word32
forall a b. (a -> b) -> a -> b
$ ("pCombinationCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pCombinationCount" ::: Ptr Word32
pPCombinationCount
"pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
pPCombinations <- ((("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV))
-> ((("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
forall a b. (a -> b) -> a -> b
$ IO ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO ())
-> (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int
-> IO
("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
forall a. Int -> IO (Ptr a)
callocBytes @FramebufferMixedSamplesCombinationNV ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pCombinationCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 32)) ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO ()
forall a. Ptr a -> IO ()
free
[()]
_ <- (Int
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
())
-> [Int]
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
[()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((()
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((()
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
())
-> ((()
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
()
forall a b. (a -> b) -> a -> b
$ ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
pPCombinations ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int
-> "pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 32) :: Ptr FramebufferMixedSamplesCombinationNV) (IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ((()
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> (()
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((()
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> ()
-> IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pCombinationCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
Result
r' <- IO Result
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Result)
-> IO Result
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pCombinationCount" ::: Ptr Word32)
-> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO Result
vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' Ptr PhysicalDevice_T
physicalDevice' ("pCombinationCount" ::: Ptr Word32
pPCombinationCount) (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
pPCombinations))
IO ()
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
())
-> IO ()
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
Word32
pCombinationCount' <- IO Word32
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Word32)
-> IO Word32
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
Word32
forall a b. (a -> b) -> a -> b
$ ("pCombinationCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pCombinationCount" ::: Ptr Word32
pPCombinationCount
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV
pCombinations' <- IO ("combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
("combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO
("combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
("combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> IO
("combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
("combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO FramebufferMixedSamplesCombinationNV)
-> IO
("combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pCombinationCount')) (\i :: Int
i -> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO FramebufferMixedSamplesCombinationNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @FramebufferMixedSamplesCombinationNV ((("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
pPCombinations) ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int
-> "pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr FramebufferMixedSamplesCombinationNV)))
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV))
-> (Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
-> ContT
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
IO
(Result,
"combinations" ::: Vector FramebufferMixedSamplesCombinationNV)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "combinations" ::: Vector FramebufferMixedSamplesCombinationNV
pCombinations')
data PhysicalDeviceCoverageReductionModeFeaturesNV = PhysicalDeviceCoverageReductionModeFeaturesNV
{
PhysicalDeviceCoverageReductionModeFeaturesNV -> Bool
coverageReductionMode :: Bool }
deriving (Typeable)
deriving instance Show PhysicalDeviceCoverageReductionModeFeaturesNV
instance ToCStruct PhysicalDeviceCoverageReductionModeFeaturesNV where
withCStruct :: PhysicalDeviceCoverageReductionModeFeaturesNV
-> (Ptr PhysicalDeviceCoverageReductionModeFeaturesNV -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceCoverageReductionModeFeaturesNV
x f :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceCoverageReductionModeFeaturesNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceCoverageReductionModeFeaturesNV -> IO b)
-> IO b)
-> (Ptr PhysicalDeviceCoverageReductionModeFeaturesNV -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p -> Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> PhysicalDeviceCoverageReductionModeFeaturesNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p PhysicalDeviceCoverageReductionModeFeaturesNV
x (Ptr PhysicalDeviceCoverageReductionModeFeaturesNV -> IO b
f Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p)
pokeCStruct :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> PhysicalDeviceCoverageReductionModeFeaturesNV -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p PhysicalDeviceCoverageReductionModeFeaturesNV{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COVERAGE_REDUCTION_MODE_FEATURES_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> 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 PhysicalDeviceCoverageReductionModeFeaturesNV
p Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
coverageReductionMode))
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_COVERAGE_REDUCTION_MODE_FEATURES_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> 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 PhysicalDeviceCoverageReductionModeFeaturesNV
p Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> 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 PhysicalDeviceCoverageReductionModeFeaturesNV where
peekCStruct :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> IO PhysicalDeviceCoverageReductionModeFeaturesNV
peekCStruct p :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p = do
Bool32
coverageReductionMode <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
p Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
PhysicalDeviceCoverageReductionModeFeaturesNV
-> IO PhysicalDeviceCoverageReductionModeFeaturesNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceCoverageReductionModeFeaturesNV
-> IO PhysicalDeviceCoverageReductionModeFeaturesNV)
-> PhysicalDeviceCoverageReductionModeFeaturesNV
-> IO PhysicalDeviceCoverageReductionModeFeaturesNV
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceCoverageReductionModeFeaturesNV
PhysicalDeviceCoverageReductionModeFeaturesNV
(Bool32 -> Bool
bool32ToBool Bool32
coverageReductionMode)
instance Storable PhysicalDeviceCoverageReductionModeFeaturesNV where
sizeOf :: PhysicalDeviceCoverageReductionModeFeaturesNV -> Int
sizeOf ~PhysicalDeviceCoverageReductionModeFeaturesNV
_ = 24
alignment :: PhysicalDeviceCoverageReductionModeFeaturesNV -> Int
alignment ~PhysicalDeviceCoverageReductionModeFeaturesNV
_ = 8
peek :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> IO PhysicalDeviceCoverageReductionModeFeaturesNV
peek = Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> IO PhysicalDeviceCoverageReductionModeFeaturesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> PhysicalDeviceCoverageReductionModeFeaturesNV -> IO ()
poke ptr :: Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
ptr poked :: PhysicalDeviceCoverageReductionModeFeaturesNV
poked = Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
-> PhysicalDeviceCoverageReductionModeFeaturesNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceCoverageReductionModeFeaturesNV
ptr PhysicalDeviceCoverageReductionModeFeaturesNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceCoverageReductionModeFeaturesNV where
zero :: PhysicalDeviceCoverageReductionModeFeaturesNV
zero = Bool -> PhysicalDeviceCoverageReductionModeFeaturesNV
PhysicalDeviceCoverageReductionModeFeaturesNV
Bool
forall a. Zero a => a
zero
data PipelineCoverageReductionStateCreateInfoNV = PipelineCoverageReductionStateCreateInfoNV
{
PipelineCoverageReductionStateCreateInfoNV
-> PipelineCoverageReductionStateCreateFlagsNV
flags :: PipelineCoverageReductionStateCreateFlagsNV
,
PipelineCoverageReductionStateCreateInfoNV
-> CoverageReductionModeNV
coverageReductionMode :: CoverageReductionModeNV
}
deriving (Typeable)
deriving instance Show PipelineCoverageReductionStateCreateInfoNV
instance ToCStruct PipelineCoverageReductionStateCreateInfoNV where
withCStruct :: PipelineCoverageReductionStateCreateInfoNV
-> (Ptr PipelineCoverageReductionStateCreateInfoNV -> IO b) -> IO b
withCStruct x :: PipelineCoverageReductionStateCreateInfoNV
x f :: Ptr PipelineCoverageReductionStateCreateInfoNV -> IO b
f = Int
-> Int
-> (Ptr PipelineCoverageReductionStateCreateInfoNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PipelineCoverageReductionStateCreateInfoNV -> IO b) -> IO b)
-> (Ptr PipelineCoverageReductionStateCreateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PipelineCoverageReductionStateCreateInfoNV
p -> Ptr PipelineCoverageReductionStateCreateInfoNV
-> PipelineCoverageReductionStateCreateInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineCoverageReductionStateCreateInfoNV
p PipelineCoverageReductionStateCreateInfoNV
x (Ptr PipelineCoverageReductionStateCreateInfoNV -> IO b
f Ptr PipelineCoverageReductionStateCreateInfoNV
p)
pokeCStruct :: Ptr PipelineCoverageReductionStateCreateInfoNV
-> PipelineCoverageReductionStateCreateInfoNV -> IO b -> IO b
pokeCStruct p :: Ptr PipelineCoverageReductionStateCreateInfoNV
p PipelineCoverageReductionStateCreateInfoNV{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCoverageReductionStateCreateInfoNV
p Ptr PipelineCoverageReductionStateCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COVERAGE_REDUCTION_STATE_CREATE_INFO_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCoverageReductionStateCreateInfoNV
p Ptr PipelineCoverageReductionStateCreateInfoNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCoverageReductionStateCreateInfoNV
p Ptr PipelineCoverageReductionStateCreateInfoNV
-> Int -> Ptr PipelineCoverageReductionStateCreateFlagsNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineCoverageReductionStateCreateFlagsNV)) (PipelineCoverageReductionStateCreateFlagsNV
flags)
Ptr CoverageReductionModeNV -> CoverageReductionModeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCoverageReductionStateCreateInfoNV
p Ptr PipelineCoverageReductionStateCreateInfoNV
-> Int -> Ptr CoverageReductionModeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr CoverageReductionModeNV)) (CoverageReductionModeNV
coverageReductionMode)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr PipelineCoverageReductionStateCreateInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr PipelineCoverageReductionStateCreateInfoNV
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCoverageReductionStateCreateInfoNV
p Ptr PipelineCoverageReductionStateCreateInfoNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COVERAGE_REDUCTION_STATE_CREATE_INFO_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCoverageReductionStateCreateInfoNV
p Ptr PipelineCoverageReductionStateCreateInfoNV
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr CoverageReductionModeNV -> CoverageReductionModeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineCoverageReductionStateCreateInfoNV
p Ptr PipelineCoverageReductionStateCreateInfoNV
-> Int -> Ptr CoverageReductionModeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr CoverageReductionModeNV)) (CoverageReductionModeNV
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PipelineCoverageReductionStateCreateInfoNV where
peekCStruct :: Ptr PipelineCoverageReductionStateCreateInfoNV
-> IO PipelineCoverageReductionStateCreateInfoNV
peekCStruct p :: Ptr PipelineCoverageReductionStateCreateInfoNV
p = do
PipelineCoverageReductionStateCreateFlagsNV
flags <- Ptr PipelineCoverageReductionStateCreateFlagsNV
-> IO PipelineCoverageReductionStateCreateFlagsNV
forall a. Storable a => Ptr a -> IO a
peek @PipelineCoverageReductionStateCreateFlagsNV ((Ptr PipelineCoverageReductionStateCreateInfoNV
p Ptr PipelineCoverageReductionStateCreateInfoNV
-> Int -> Ptr PipelineCoverageReductionStateCreateFlagsNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineCoverageReductionStateCreateFlagsNV))
CoverageReductionModeNV
coverageReductionMode <- Ptr CoverageReductionModeNV -> IO CoverageReductionModeNV
forall a. Storable a => Ptr a -> IO a
peek @CoverageReductionModeNV ((Ptr PipelineCoverageReductionStateCreateInfoNV
p Ptr PipelineCoverageReductionStateCreateInfoNV
-> Int -> Ptr CoverageReductionModeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr CoverageReductionModeNV))
PipelineCoverageReductionStateCreateInfoNV
-> IO PipelineCoverageReductionStateCreateInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineCoverageReductionStateCreateInfoNV
-> IO PipelineCoverageReductionStateCreateInfoNV)
-> PipelineCoverageReductionStateCreateInfoNV
-> IO PipelineCoverageReductionStateCreateInfoNV
forall a b. (a -> b) -> a -> b
$ PipelineCoverageReductionStateCreateFlagsNV
-> CoverageReductionModeNV
-> PipelineCoverageReductionStateCreateInfoNV
PipelineCoverageReductionStateCreateInfoNV
PipelineCoverageReductionStateCreateFlagsNV
flags CoverageReductionModeNV
coverageReductionMode
instance Storable PipelineCoverageReductionStateCreateInfoNV where
sizeOf :: PipelineCoverageReductionStateCreateInfoNV -> Int
sizeOf ~PipelineCoverageReductionStateCreateInfoNV
_ = 24
alignment :: PipelineCoverageReductionStateCreateInfoNV -> Int
alignment ~PipelineCoverageReductionStateCreateInfoNV
_ = 8
peek :: Ptr PipelineCoverageReductionStateCreateInfoNV
-> IO PipelineCoverageReductionStateCreateInfoNV
peek = Ptr PipelineCoverageReductionStateCreateInfoNV
-> IO PipelineCoverageReductionStateCreateInfoNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PipelineCoverageReductionStateCreateInfoNV
-> PipelineCoverageReductionStateCreateInfoNV -> IO ()
poke ptr :: Ptr PipelineCoverageReductionStateCreateInfoNV
ptr poked :: PipelineCoverageReductionStateCreateInfoNV
poked = Ptr PipelineCoverageReductionStateCreateInfoNV
-> PipelineCoverageReductionStateCreateInfoNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineCoverageReductionStateCreateInfoNV
ptr PipelineCoverageReductionStateCreateInfoNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PipelineCoverageReductionStateCreateInfoNV where
zero :: PipelineCoverageReductionStateCreateInfoNV
zero = PipelineCoverageReductionStateCreateFlagsNV
-> CoverageReductionModeNV
-> PipelineCoverageReductionStateCreateInfoNV
PipelineCoverageReductionStateCreateInfoNV
PipelineCoverageReductionStateCreateFlagsNV
forall a. Zero a => a
zero
CoverageReductionModeNV
forall a. Zero a => a
zero
data FramebufferMixedSamplesCombinationNV = FramebufferMixedSamplesCombinationNV
{
FramebufferMixedSamplesCombinationNV -> CoverageReductionModeNV
coverageReductionMode :: CoverageReductionModeNV
,
FramebufferMixedSamplesCombinationNV -> SampleCountFlagBits
rasterizationSamples :: SampleCountFlagBits
,
FramebufferMixedSamplesCombinationNV -> SampleCountFlagBits
depthStencilSamples :: SampleCountFlags
,
FramebufferMixedSamplesCombinationNV -> SampleCountFlagBits
colorSamples :: SampleCountFlags
}
deriving (Typeable)
deriving instance Show FramebufferMixedSamplesCombinationNV
instance ToCStruct FramebufferMixedSamplesCombinationNV where
withCStruct :: FramebufferMixedSamplesCombinationNV
-> (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO b)
-> IO b
withCStruct x :: FramebufferMixedSamplesCombinationNV
x f :: ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO b
f = Int
-> Int
-> (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO b)
-> IO b)
-> (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p -> ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> FramebufferMixedSamplesCombinationNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p FramebufferMixedSamplesCombinationNV
x (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO b
f "pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p)
pokeCStruct :: ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> FramebufferMixedSamplesCombinationNV -> IO b -> IO b
pokeCStruct p :: "pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p FramebufferMixedSamplesCombinationNV{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FRAMEBUFFER_MIXED_SAMPLES_COMBINATION_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr CoverageReductionModeNV -> CoverageReductionModeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr CoverageReductionModeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CoverageReductionModeNV)) (CoverageReductionModeNV
coverageReductionMode)
Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
rasterizationSamples)
Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlags)) (SampleCountFlagBits
depthStencilSamples)
Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr SampleCountFlags)) (SampleCountFlagBits
colorSamples)
IO b
f
cStructSize :: Int
cStructSize = 32
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO b -> IO b
pokeZeroCStruct p :: "pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FRAMEBUFFER_MIXED_SAMPLES_COMBINATION_NV)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr CoverageReductionModeNV -> CoverageReductionModeNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr CoverageReductionModeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CoverageReductionModeNV)) (CoverageReductionModeNV
forall a. Zero a => a
zero)
Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
forall a. Zero a => a
zero)
Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlags)) (SampleCountFlagBits
forall a. Zero a => a
zero)
Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr SampleCountFlags)) (SampleCountFlagBits
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct FramebufferMixedSamplesCombinationNV where
peekCStruct :: ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO FramebufferMixedSamplesCombinationNV
peekCStruct p :: "pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p = do
CoverageReductionModeNV
coverageReductionMode <- Ptr CoverageReductionModeNV -> IO CoverageReductionModeNV
forall a. Storable a => Ptr a -> IO a
peek @CoverageReductionModeNV (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr CoverageReductionModeNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CoverageReductionModeNV))
SampleCountFlagBits
rasterizationSamples <- Ptr SampleCountFlagBits -> IO SampleCountFlagBits
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlagBits (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr SampleCountFlagBits))
SampleCountFlagBits
depthStencilSamples <- Ptr SampleCountFlagBits -> IO SampleCountFlagBits
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlags))
SampleCountFlagBits
colorSamples <- Ptr SampleCountFlagBits -> IO SampleCountFlagBits
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags (("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
p ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr SampleCountFlags))
FramebufferMixedSamplesCombinationNV
-> IO FramebufferMixedSamplesCombinationNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FramebufferMixedSamplesCombinationNV
-> IO FramebufferMixedSamplesCombinationNV)
-> FramebufferMixedSamplesCombinationNV
-> IO FramebufferMixedSamplesCombinationNV
forall a b. (a -> b) -> a -> b
$ CoverageReductionModeNV
-> SampleCountFlagBits
-> SampleCountFlagBits
-> SampleCountFlagBits
-> FramebufferMixedSamplesCombinationNV
FramebufferMixedSamplesCombinationNV
CoverageReductionModeNV
coverageReductionMode SampleCountFlagBits
rasterizationSamples SampleCountFlagBits
depthStencilSamples SampleCountFlagBits
colorSamples
instance Storable FramebufferMixedSamplesCombinationNV where
sizeOf :: FramebufferMixedSamplesCombinationNV -> Int
sizeOf ~FramebufferMixedSamplesCombinationNV
_ = 32
alignment :: FramebufferMixedSamplesCombinationNV -> Int
alignment ~FramebufferMixedSamplesCombinationNV
_ = 8
peek :: ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO FramebufferMixedSamplesCombinationNV
peek = ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> IO FramebufferMixedSamplesCombinationNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> FramebufferMixedSamplesCombinationNV -> IO ()
poke ptr :: "pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
ptr poked :: FramebufferMixedSamplesCombinationNV
poked = ("pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV)
-> FramebufferMixedSamplesCombinationNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCombinations" ::: Ptr FramebufferMixedSamplesCombinationNV
ptr FramebufferMixedSamplesCombinationNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero FramebufferMixedSamplesCombinationNV where
zero :: FramebufferMixedSamplesCombinationNV
zero = CoverageReductionModeNV
-> SampleCountFlagBits
-> SampleCountFlagBits
-> SampleCountFlagBits
-> FramebufferMixedSamplesCombinationNV
FramebufferMixedSamplesCombinationNV
CoverageReductionModeNV
forall a. Zero a => a
zero
SampleCountFlagBits
forall a. Zero a => a
zero
SampleCountFlagBits
forall a. Zero a => a
zero
SampleCountFlagBits
forall a. Zero a => a
zero
newtype PipelineCoverageReductionStateCreateFlagsNV = PipelineCoverageReductionStateCreateFlagsNV Flags
deriving newtype (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
(PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool)
-> Eq PipelineCoverageReductionStateCreateFlagsNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
$c/= :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
== :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
$c== :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
Eq, Eq PipelineCoverageReductionStateCreateFlagsNV
Eq PipelineCoverageReductionStateCreateFlagsNV =>
(PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Ordering)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV)
-> Ord PipelineCoverageReductionStateCreateFlagsNV
PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Ordering
PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
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 :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
$cmin :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
max :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
$cmax :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
>= :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
$c>= :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
> :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
$c> :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
<= :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
$c<= :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
< :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
$c< :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Bool
compare :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Ordering
$ccompare :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> Ordering
$cp1Ord :: Eq PipelineCoverageReductionStateCreateFlagsNV
Ord, Ptr b -> Int -> IO PipelineCoverageReductionStateCreateFlagsNV
Ptr b
-> Int -> PipelineCoverageReductionStateCreateFlagsNV -> IO ()
Ptr PipelineCoverageReductionStateCreateFlagsNV
-> IO PipelineCoverageReductionStateCreateFlagsNV
Ptr PipelineCoverageReductionStateCreateFlagsNV
-> Int -> IO PipelineCoverageReductionStateCreateFlagsNV
Ptr PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV -> IO ()
Ptr PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> IO ()
PipelineCoverageReductionStateCreateFlagsNV -> Int
(PipelineCoverageReductionStateCreateFlagsNV -> Int)
-> (PipelineCoverageReductionStateCreateFlagsNV -> Int)
-> (Ptr PipelineCoverageReductionStateCreateFlagsNV
-> Int -> IO PipelineCoverageReductionStateCreateFlagsNV)
-> (Ptr PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV -> IO ())
-> (forall b.
Ptr b -> Int -> IO PipelineCoverageReductionStateCreateFlagsNV)
-> (forall b.
Ptr b
-> Int -> PipelineCoverageReductionStateCreateFlagsNV -> IO ())
-> (Ptr PipelineCoverageReductionStateCreateFlagsNV
-> IO PipelineCoverageReductionStateCreateFlagsNV)
-> (Ptr PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> IO ())
-> Storable PipelineCoverageReductionStateCreateFlagsNV
forall b.
Ptr b -> Int -> IO PipelineCoverageReductionStateCreateFlagsNV
forall b.
Ptr b
-> Int -> PipelineCoverageReductionStateCreateFlagsNV -> 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 PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> IO ()
$cpoke :: Ptr PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV -> IO ()
peek :: Ptr PipelineCoverageReductionStateCreateFlagsNV
-> IO PipelineCoverageReductionStateCreateFlagsNV
$cpeek :: Ptr PipelineCoverageReductionStateCreateFlagsNV
-> IO PipelineCoverageReductionStateCreateFlagsNV
pokeByteOff :: Ptr b
-> Int -> PipelineCoverageReductionStateCreateFlagsNV -> IO ()
$cpokeByteOff :: forall b.
Ptr b
-> Int -> PipelineCoverageReductionStateCreateFlagsNV -> IO ()
peekByteOff :: Ptr b -> Int -> IO PipelineCoverageReductionStateCreateFlagsNV
$cpeekByteOff :: forall b.
Ptr b -> Int -> IO PipelineCoverageReductionStateCreateFlagsNV
pokeElemOff :: Ptr PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV -> IO ()
$cpokeElemOff :: Ptr PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV -> IO ()
peekElemOff :: Ptr PipelineCoverageReductionStateCreateFlagsNV
-> Int -> IO PipelineCoverageReductionStateCreateFlagsNV
$cpeekElemOff :: Ptr PipelineCoverageReductionStateCreateFlagsNV
-> Int -> IO PipelineCoverageReductionStateCreateFlagsNV
alignment :: PipelineCoverageReductionStateCreateFlagsNV -> Int
$calignment :: PipelineCoverageReductionStateCreateFlagsNV -> Int
sizeOf :: PipelineCoverageReductionStateCreateFlagsNV -> Int
$csizeOf :: PipelineCoverageReductionStateCreateFlagsNV -> Int
Storable, PipelineCoverageReductionStateCreateFlagsNV
PipelineCoverageReductionStateCreateFlagsNV
-> Zero PipelineCoverageReductionStateCreateFlagsNV
forall a. a -> Zero a
zero :: PipelineCoverageReductionStateCreateFlagsNV
$czero :: PipelineCoverageReductionStateCreateFlagsNV
Zero, Eq PipelineCoverageReductionStateCreateFlagsNV
PipelineCoverageReductionStateCreateFlagsNV
Eq PipelineCoverageReductionStateCreateFlagsNV =>
(PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> PipelineCoverageReductionStateCreateFlagsNV
-> (Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV -> Int -> Bool)
-> (PipelineCoverageReductionStateCreateFlagsNV -> Maybe Int)
-> (PipelineCoverageReductionStateCreateFlagsNV -> Int)
-> (PipelineCoverageReductionStateCreateFlagsNV -> Bool)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV)
-> (PipelineCoverageReductionStateCreateFlagsNV -> Int)
-> Bits PipelineCoverageReductionStateCreateFlagsNV
Int -> PipelineCoverageReductionStateCreateFlagsNV
PipelineCoverageReductionStateCreateFlagsNV -> Bool
PipelineCoverageReductionStateCreateFlagsNV -> Int
PipelineCoverageReductionStateCreateFlagsNV -> Maybe Int
PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
PipelineCoverageReductionStateCreateFlagsNV -> Int -> Bool
PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
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 :: PipelineCoverageReductionStateCreateFlagsNV -> Int
$cpopCount :: PipelineCoverageReductionStateCreateFlagsNV -> Int
rotateR :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$crotateR :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
rotateL :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$crotateL :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
unsafeShiftR :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$cunsafeShiftR :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
shiftR :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$cshiftR :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
unsafeShiftL :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$cunsafeShiftL :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
shiftL :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$cshiftL :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
isSigned :: PipelineCoverageReductionStateCreateFlagsNV -> Bool
$cisSigned :: PipelineCoverageReductionStateCreateFlagsNV -> Bool
bitSize :: PipelineCoverageReductionStateCreateFlagsNV -> Int
$cbitSize :: PipelineCoverageReductionStateCreateFlagsNV -> Int
bitSizeMaybe :: PipelineCoverageReductionStateCreateFlagsNV -> Maybe Int
$cbitSizeMaybe :: PipelineCoverageReductionStateCreateFlagsNV -> Maybe Int
testBit :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> Bool
$ctestBit :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> Bool
complementBit :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$ccomplementBit :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
clearBit :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$cclearBit :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
setBit :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$csetBit :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
bit :: Int -> PipelineCoverageReductionStateCreateFlagsNV
$cbit :: Int -> PipelineCoverageReductionStateCreateFlagsNV
zeroBits :: PipelineCoverageReductionStateCreateFlagsNV
$czeroBits :: PipelineCoverageReductionStateCreateFlagsNV
rotate :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$crotate :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
shift :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
$cshift :: PipelineCoverageReductionStateCreateFlagsNV
-> Int -> PipelineCoverageReductionStateCreateFlagsNV
complement :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
$ccomplement :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
xor :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
$cxor :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
.|. :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
$c.|. :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
.&. :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
$c.&. :: PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
-> PipelineCoverageReductionStateCreateFlagsNV
$cp1Bits :: Eq PipelineCoverageReductionStateCreateFlagsNV
Bits)
instance Show PipelineCoverageReductionStateCreateFlagsNV where
showsPrec :: Int -> PipelineCoverageReductionStateCreateFlagsNV -> ShowS
showsPrec p :: Int
p = \case
PipelineCoverageReductionStateCreateFlagsNV x :: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PipelineCoverageReductionStateCreateFlagsNV 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word32
x)
instance Read PipelineCoverageReductionStateCreateFlagsNV where
readPrec :: ReadPrec PipelineCoverageReductionStateCreateFlagsNV
readPrec = ReadPrec PipelineCoverageReductionStateCreateFlagsNV
-> ReadPrec PipelineCoverageReductionStateCreateFlagsNV
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec PipelineCoverageReductionStateCreateFlagsNV)]
-> ReadPrec PipelineCoverageReductionStateCreateFlagsNV
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose []
ReadPrec PipelineCoverageReductionStateCreateFlagsNV
-> ReadPrec PipelineCoverageReductionStateCreateFlagsNV
-> ReadPrec PipelineCoverageReductionStateCreateFlagsNV
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int
-> ReadPrec PipelineCoverageReductionStateCreateFlagsNV
-> ReadPrec PipelineCoverageReductionStateCreateFlagsNV
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "PipelineCoverageReductionStateCreateFlagsNV")
Word32
v <- ReadPrec Word32 -> ReadPrec Word32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word32
forall a. Read a => ReadPrec a
readPrec
PipelineCoverageReductionStateCreateFlagsNV
-> ReadPrec PipelineCoverageReductionStateCreateFlagsNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word32 -> PipelineCoverageReductionStateCreateFlagsNV
PipelineCoverageReductionStateCreateFlagsNV Word32
v)))
newtype CoverageReductionModeNV = CoverageReductionModeNV Int32
deriving newtype (CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
(CoverageReductionModeNV -> CoverageReductionModeNV -> Bool)
-> (CoverageReductionModeNV -> CoverageReductionModeNV -> Bool)
-> Eq CoverageReductionModeNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
$c/= :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
== :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
$c== :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
Eq, Eq CoverageReductionModeNV
Eq CoverageReductionModeNV =>
(CoverageReductionModeNV -> CoverageReductionModeNV -> Ordering)
-> (CoverageReductionModeNV -> CoverageReductionModeNV -> Bool)
-> (CoverageReductionModeNV -> CoverageReductionModeNV -> Bool)
-> (CoverageReductionModeNV -> CoverageReductionModeNV -> Bool)
-> (CoverageReductionModeNV -> CoverageReductionModeNV -> Bool)
-> (CoverageReductionModeNV
-> CoverageReductionModeNV -> CoverageReductionModeNV)
-> (CoverageReductionModeNV
-> CoverageReductionModeNV -> CoverageReductionModeNV)
-> Ord CoverageReductionModeNV
CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
CoverageReductionModeNV -> CoverageReductionModeNV -> Ordering
CoverageReductionModeNV
-> CoverageReductionModeNV -> CoverageReductionModeNV
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 :: CoverageReductionModeNV
-> CoverageReductionModeNV -> CoverageReductionModeNV
$cmin :: CoverageReductionModeNV
-> CoverageReductionModeNV -> CoverageReductionModeNV
max :: CoverageReductionModeNV
-> CoverageReductionModeNV -> CoverageReductionModeNV
$cmax :: CoverageReductionModeNV
-> CoverageReductionModeNV -> CoverageReductionModeNV
>= :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
$c>= :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
> :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
$c> :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
<= :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
$c<= :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
< :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
$c< :: CoverageReductionModeNV -> CoverageReductionModeNV -> Bool
compare :: CoverageReductionModeNV -> CoverageReductionModeNV -> Ordering
$ccompare :: CoverageReductionModeNV -> CoverageReductionModeNV -> Ordering
$cp1Ord :: Eq CoverageReductionModeNV
Ord, Ptr b -> Int -> IO CoverageReductionModeNV
Ptr b -> Int -> CoverageReductionModeNV -> IO ()
Ptr CoverageReductionModeNV -> IO CoverageReductionModeNV
Ptr CoverageReductionModeNV -> Int -> IO CoverageReductionModeNV
Ptr CoverageReductionModeNV
-> Int -> CoverageReductionModeNV -> IO ()
Ptr CoverageReductionModeNV -> CoverageReductionModeNV -> IO ()
CoverageReductionModeNV -> Int
(CoverageReductionModeNV -> Int)
-> (CoverageReductionModeNV -> Int)
-> (Ptr CoverageReductionModeNV
-> Int -> IO CoverageReductionModeNV)
-> (Ptr CoverageReductionModeNV
-> Int -> CoverageReductionModeNV -> IO ())
-> (forall b. Ptr b -> Int -> IO CoverageReductionModeNV)
-> (forall b. Ptr b -> Int -> CoverageReductionModeNV -> IO ())
-> (Ptr CoverageReductionModeNV -> IO CoverageReductionModeNV)
-> (Ptr CoverageReductionModeNV
-> CoverageReductionModeNV -> IO ())
-> Storable CoverageReductionModeNV
forall b. Ptr b -> Int -> IO CoverageReductionModeNV
forall b. Ptr b -> Int -> CoverageReductionModeNV -> 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 CoverageReductionModeNV -> CoverageReductionModeNV -> IO ()
$cpoke :: Ptr CoverageReductionModeNV -> CoverageReductionModeNV -> IO ()
peek :: Ptr CoverageReductionModeNV -> IO CoverageReductionModeNV
$cpeek :: Ptr CoverageReductionModeNV -> IO CoverageReductionModeNV
pokeByteOff :: Ptr b -> Int -> CoverageReductionModeNV -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CoverageReductionModeNV -> IO ()
peekByteOff :: Ptr b -> Int -> IO CoverageReductionModeNV
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CoverageReductionModeNV
pokeElemOff :: Ptr CoverageReductionModeNV
-> Int -> CoverageReductionModeNV -> IO ()
$cpokeElemOff :: Ptr CoverageReductionModeNV
-> Int -> CoverageReductionModeNV -> IO ()
peekElemOff :: Ptr CoverageReductionModeNV -> Int -> IO CoverageReductionModeNV
$cpeekElemOff :: Ptr CoverageReductionModeNV -> Int -> IO CoverageReductionModeNV
alignment :: CoverageReductionModeNV -> Int
$calignment :: CoverageReductionModeNV -> Int
sizeOf :: CoverageReductionModeNV -> Int
$csizeOf :: CoverageReductionModeNV -> Int
Storable, CoverageReductionModeNV
CoverageReductionModeNV -> Zero CoverageReductionModeNV
forall a. a -> Zero a
zero :: CoverageReductionModeNV
$czero :: CoverageReductionModeNV
Zero)
pattern $bCOVERAGE_REDUCTION_MODE_MERGE_NV :: CoverageReductionModeNV
$mCOVERAGE_REDUCTION_MODE_MERGE_NV :: forall r.
CoverageReductionModeNV -> (Void# -> r) -> (Void# -> r) -> r
COVERAGE_REDUCTION_MODE_MERGE_NV = CoverageReductionModeNV 0
pattern $bCOVERAGE_REDUCTION_MODE_TRUNCATE_NV :: CoverageReductionModeNV
$mCOVERAGE_REDUCTION_MODE_TRUNCATE_NV :: forall r.
CoverageReductionModeNV -> (Void# -> r) -> (Void# -> r) -> r
COVERAGE_REDUCTION_MODE_TRUNCATE_NV = CoverageReductionModeNV 1
{-# complete COVERAGE_REDUCTION_MODE_MERGE_NV,
COVERAGE_REDUCTION_MODE_TRUNCATE_NV :: CoverageReductionModeNV #-}
instance Show CoverageReductionModeNV where
showsPrec :: Int -> CoverageReductionModeNV -> ShowS
showsPrec p :: Int
p = \case
COVERAGE_REDUCTION_MODE_MERGE_NV -> String -> ShowS
showString "COVERAGE_REDUCTION_MODE_MERGE_NV"
COVERAGE_REDUCTION_MODE_TRUNCATE_NV -> String -> ShowS
showString "COVERAGE_REDUCTION_MODE_TRUNCATE_NV"
CoverageReductionModeNV x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "CoverageReductionModeNV " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)
instance Read CoverageReductionModeNV where
readPrec :: ReadPrec CoverageReductionModeNV
readPrec = ReadPrec CoverageReductionModeNV
-> ReadPrec CoverageReductionModeNV
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec CoverageReductionModeNV)]
-> ReadPrec CoverageReductionModeNV
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("COVERAGE_REDUCTION_MODE_MERGE_NV", CoverageReductionModeNV -> ReadPrec CoverageReductionModeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure CoverageReductionModeNV
COVERAGE_REDUCTION_MODE_MERGE_NV)
, ("COVERAGE_REDUCTION_MODE_TRUNCATE_NV", CoverageReductionModeNV -> ReadPrec CoverageReductionModeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure CoverageReductionModeNV
COVERAGE_REDUCTION_MODE_TRUNCATE_NV)]
ReadPrec CoverageReductionModeNV
-> ReadPrec CoverageReductionModeNV
-> ReadPrec CoverageReductionModeNV
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int
-> ReadPrec CoverageReductionModeNV
-> ReadPrec CoverageReductionModeNV
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "CoverageReductionModeNV")
Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
CoverageReductionModeNV -> ReadPrec CoverageReductionModeNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> CoverageReductionModeNV
CoverageReductionModeNV Int32
v)))
type NV_COVERAGE_REDUCTION_MODE_SPEC_VERSION = 1
pattern NV_COVERAGE_REDUCTION_MODE_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_COVERAGE_REDUCTION_MODE_SPEC_VERSION :: a
$mNV_COVERAGE_REDUCTION_MODE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_COVERAGE_REDUCTION_MODE_SPEC_VERSION = 1
type NV_COVERAGE_REDUCTION_MODE_EXTENSION_NAME = "VK_NV_coverage_reduction_mode"
pattern NV_COVERAGE_REDUCTION_MODE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_COVERAGE_REDUCTION_MODE_EXTENSION_NAME :: a
$mNV_COVERAGE_REDUCTION_MODE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_COVERAGE_REDUCTION_MODE_EXTENSION_NAME = "VK_NV_coverage_reduction_mode"