{-# language CPP #-}
module Graphics.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.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 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 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 Graphics.Vulkan.CStruct.Utils (advancePtrBytes)
import Graphics.Vulkan.Core10.BaseType (bool32ToBool)
import Graphics.Vulkan.Core10.BaseType (boolToBool32)
import Graphics.Vulkan.NamedType ((:::))
import Graphics.Vulkan.Core10.BaseType (Bool32)
import Graphics.Vulkan.Core10.BaseType (Flags)
import Graphics.Vulkan.CStruct (FromCStruct)
import Graphics.Vulkan.CStruct (FromCStruct(..))
import Graphics.Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV))
import Graphics.Vulkan.Core10.Handles (PhysicalDevice)
import Graphics.Vulkan.Core10.Handles (PhysicalDevice(..))
import Graphics.Vulkan.Core10.Handles (PhysicalDevice_T)
import Graphics.Vulkan.Core10.Enums.Result (Result)
import Graphics.Vulkan.Core10.Enums.Result (Result(..))
import Graphics.Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import Graphics.Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlags)
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType)
import Graphics.Vulkan.CStruct (ToCStruct)
import Graphics.Vulkan.CStruct (ToCStruct(..))
import Graphics.Vulkan.Exception (VulkanException(..))
import Graphics.Vulkan.Zero (Zero)
import Graphics.Vulkan.Zero (Zero(..))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_FRAMEBUFFER_MIXED_SAMPLES_COMBINATION_NV))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_COVERAGE_REDUCTION_MODE_FEATURES_NV))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_COVERAGE_REDUCTION_STATE_CREATE_INFO_NV))
import Graphics.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 = liftIO . evalContT $ do
  let vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' = mkVkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV (pVkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV (instanceCmds (physicalDevice :: PhysicalDevice)))
  let physicalDevice' = physicalDeviceHandle (physicalDevice)
  pPCombinationCount <- ContT $ bracket (callocBytes @Word32 4) free
  r <- lift $ vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' physicalDevice' (pPCombinationCount) (nullPtr)
  lift $ when (r < SUCCESS) (throwIO (VulkanException r))
  pCombinationCount <- lift $ peek @Word32 pPCombinationCount
  pPCombinations <- ContT $ bracket (callocBytes @FramebufferMixedSamplesCombinationNV ((fromIntegral (pCombinationCount)) * 32)) free
  _ <- traverse (\i -> ContT $ pokeZeroCStruct (pPCombinations `advancePtrBytes` (i * 32) :: Ptr FramebufferMixedSamplesCombinationNV) . ($ ())) [0..(fromIntegral (pCombinationCount)) - 1]
  r' <- lift $ vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV' physicalDevice' (pPCombinationCount) ((pPCombinations))
  lift $ when (r' < SUCCESS) (throwIO (VulkanException r'))
  pCombinationCount' <- lift $ peek @Word32 pPCombinationCount
  pCombinations' <- lift $ generateM (fromIntegral (pCombinationCount')) (\i -> peekCStruct @FramebufferMixedSamplesCombinationNV (((pPCombinations) `advancePtrBytes` (32 * (i)) :: Ptr FramebufferMixedSamplesCombinationNV)))
  pure $ ((r'), pCombinations')
data PhysicalDeviceCoverageReductionModeFeaturesNV = PhysicalDeviceCoverageReductionModeFeaturesNV
  { 
    
    
    coverageReductionMode :: Bool }
  deriving (Typeable)
deriving instance Show PhysicalDeviceCoverageReductionModeFeaturesNV
instance ToCStruct PhysicalDeviceCoverageReductionModeFeaturesNV where
  withCStruct x f = allocaBytesAligned 24 8 $ \p -> pokeCStruct p x (f p)
  pokeCStruct p PhysicalDeviceCoverageReductionModeFeaturesNV{..} f = do
    poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PHYSICAL_DEVICE_COVERAGE_REDUCTION_MODE_FEATURES_NV)
    poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
    poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (coverageReductionMode))
    f
  cStructSize = 24
  cStructAlignment = 8
  pokeZeroCStruct p f = do
    poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PHYSICAL_DEVICE_COVERAGE_REDUCTION_MODE_FEATURES_NV)
    poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
    poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (zero))
    f
instance FromCStruct PhysicalDeviceCoverageReductionModeFeaturesNV where
  peekCStruct p = do
    coverageReductionMode <- peek @Bool32 ((p `plusPtr` 16 :: Ptr Bool32))
    pure $ PhysicalDeviceCoverageReductionModeFeaturesNV
             (bool32ToBool coverageReductionMode)
instance Storable PhysicalDeviceCoverageReductionModeFeaturesNV where
  sizeOf ~_ = 24
  alignment ~_ = 8
  peek = peekCStruct
  poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero PhysicalDeviceCoverageReductionModeFeaturesNV where
  zero = PhysicalDeviceCoverageReductionModeFeaturesNV
           zero
data PipelineCoverageReductionStateCreateInfoNV = PipelineCoverageReductionStateCreateInfoNV
  { 
    flags :: PipelineCoverageReductionStateCreateFlagsNV
  , 
    
    coverageReductionMode :: CoverageReductionModeNV
  }
  deriving (Typeable)
deriving instance Show PipelineCoverageReductionStateCreateInfoNV
instance ToCStruct PipelineCoverageReductionStateCreateInfoNV where
  withCStruct x f = allocaBytesAligned 24 8 $ \p -> pokeCStruct p x (f p)
  pokeCStruct p PipelineCoverageReductionStateCreateInfoNV{..} f = do
    poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PIPELINE_COVERAGE_REDUCTION_STATE_CREATE_INFO_NV)
    poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
    poke ((p `plusPtr` 16 :: Ptr PipelineCoverageReductionStateCreateFlagsNV)) (flags)
    poke ((p `plusPtr` 20 :: Ptr CoverageReductionModeNV)) (coverageReductionMode)
    f
  cStructSize = 24
  cStructAlignment = 8
  pokeZeroCStruct p f = do
    poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PIPELINE_COVERAGE_REDUCTION_STATE_CREATE_INFO_NV)
    poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
    poke ((p `plusPtr` 20 :: Ptr CoverageReductionModeNV)) (zero)
    f
instance FromCStruct PipelineCoverageReductionStateCreateInfoNV where
  peekCStruct p = do
    flags <- peek @PipelineCoverageReductionStateCreateFlagsNV ((p `plusPtr` 16 :: Ptr PipelineCoverageReductionStateCreateFlagsNV))
    coverageReductionMode <- peek @CoverageReductionModeNV ((p `plusPtr` 20 :: Ptr CoverageReductionModeNV))
    pure $ PipelineCoverageReductionStateCreateInfoNV
             flags coverageReductionMode
instance Storable PipelineCoverageReductionStateCreateInfoNV where
  sizeOf ~_ = 24
  alignment ~_ = 8
  peek = peekCStruct
  poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero PipelineCoverageReductionStateCreateInfoNV where
  zero = PipelineCoverageReductionStateCreateInfoNV
           zero
           zero
data FramebufferMixedSamplesCombinationNV = FramebufferMixedSamplesCombinationNV
  { 
    
    coverageReductionMode :: CoverageReductionModeNV
  , 
    
    rasterizationSamples :: SampleCountFlagBits
  , 
    
    
    depthStencilSamples :: SampleCountFlags
  , 
    
    
    colorSamples :: SampleCountFlags
  }
  deriving (Typeable)
deriving instance Show FramebufferMixedSamplesCombinationNV
instance ToCStruct FramebufferMixedSamplesCombinationNV where
  withCStruct x f = allocaBytesAligned 32 8 $ \p -> pokeCStruct p x (f p)
  pokeCStruct p FramebufferMixedSamplesCombinationNV{..} f = do
    poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_FRAMEBUFFER_MIXED_SAMPLES_COMBINATION_NV)
    poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
    poke ((p `plusPtr` 16 :: Ptr CoverageReductionModeNV)) (coverageReductionMode)
    poke ((p `plusPtr` 20 :: Ptr SampleCountFlagBits)) (rasterizationSamples)
    poke ((p `plusPtr` 24 :: Ptr SampleCountFlags)) (depthStencilSamples)
    poke ((p `plusPtr` 28 :: Ptr SampleCountFlags)) (colorSamples)
    f
  cStructSize = 32
  cStructAlignment = 8
  pokeZeroCStruct p f = do
    poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_FRAMEBUFFER_MIXED_SAMPLES_COMBINATION_NV)
    poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
    poke ((p `plusPtr` 16 :: Ptr CoverageReductionModeNV)) (zero)
    poke ((p `plusPtr` 20 :: Ptr SampleCountFlagBits)) (zero)
    poke ((p `plusPtr` 24 :: Ptr SampleCountFlags)) (zero)
    poke ((p `plusPtr` 28 :: Ptr SampleCountFlags)) (zero)
    f
instance FromCStruct FramebufferMixedSamplesCombinationNV where
  peekCStruct p = do
    coverageReductionMode <- peek @CoverageReductionModeNV ((p `plusPtr` 16 :: Ptr CoverageReductionModeNV))
    rasterizationSamples <- peek @SampleCountFlagBits ((p `plusPtr` 20 :: Ptr SampleCountFlagBits))
    depthStencilSamples <- peek @SampleCountFlags ((p `plusPtr` 24 :: Ptr SampleCountFlags))
    colorSamples <- peek @SampleCountFlags ((p `plusPtr` 28 :: Ptr SampleCountFlags))
    pure $ FramebufferMixedSamplesCombinationNV
             coverageReductionMode rasterizationSamples depthStencilSamples colorSamples
instance Storable FramebufferMixedSamplesCombinationNV where
  sizeOf ~_ = 32
  alignment ~_ = 8
  peek = peekCStruct
  poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero FramebufferMixedSamplesCombinationNV where
  zero = FramebufferMixedSamplesCombinationNV
           zero
           zero
           zero
           zero
newtype PipelineCoverageReductionStateCreateFlagsNV = PipelineCoverageReductionStateCreateFlagsNV Flags
  deriving newtype (Eq, Ord, Storable, Zero, Bits)
instance Show PipelineCoverageReductionStateCreateFlagsNV where
  showsPrec p = \case
    PipelineCoverageReductionStateCreateFlagsNV x -> showParen (p >= 11) (showString "PipelineCoverageReductionStateCreateFlagsNV 0x" . showHex x)
instance Read PipelineCoverageReductionStateCreateFlagsNV where
  readPrec = parens (choose []
                     +++
                     prec 10 (do
                       expectP (Ident "PipelineCoverageReductionStateCreateFlagsNV")
                       v <- step readPrec
                       pure (PipelineCoverageReductionStateCreateFlagsNV v)))
newtype CoverageReductionModeNV = CoverageReductionModeNV Int32
  deriving newtype (Eq, Ord, Storable, Zero)
pattern COVERAGE_REDUCTION_MODE_MERGE_NV = CoverageReductionModeNV 0
pattern COVERAGE_REDUCTION_MODE_TRUNCATE_NV = CoverageReductionModeNV 1
{-# complete COVERAGE_REDUCTION_MODE_MERGE_NV,
             COVERAGE_REDUCTION_MODE_TRUNCATE_NV :: CoverageReductionModeNV #-}
instance Show CoverageReductionModeNV where
  showsPrec p = \case
    COVERAGE_REDUCTION_MODE_MERGE_NV -> showString "COVERAGE_REDUCTION_MODE_MERGE_NV"
    COVERAGE_REDUCTION_MODE_TRUNCATE_NV -> showString "COVERAGE_REDUCTION_MODE_TRUNCATE_NV"
    CoverageReductionModeNV x -> showParen (p >= 11) (showString "CoverageReductionModeNV " . showsPrec 11 x)
instance Read CoverageReductionModeNV where
  readPrec = parens (choose [("COVERAGE_REDUCTION_MODE_MERGE_NV", pure COVERAGE_REDUCTION_MODE_MERGE_NV)
                            , ("COVERAGE_REDUCTION_MODE_TRUNCATE_NV", pure COVERAGE_REDUCTION_MODE_TRUNCATE_NV)]
                     +++
                     prec 10 (do
                       expectP (Ident "CoverageReductionModeNV")
                       v <- step readPrec
                       pure (CoverageReductionModeNV v)))
type NV_COVERAGE_REDUCTION_MODE_SPEC_VERSION = 1
pattern NV_COVERAGE_REDUCTION_MODE_SPEC_VERSION :: forall a . Integral a => a
pattern 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 NV_COVERAGE_REDUCTION_MODE_EXTENSION_NAME = "VK_NV_coverage_reduction_mode"