{-# OPTIONS_GHC -fno-warn-missing-pattern-synonym-signatures#-}
{-# OPTIONS_HADDOCK ignore-exports#-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE PatternSynonyms            #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE Strict                     #-}
{-# LANGUAGE TypeSynonymInstances       #-}
module Graphics.Vulkan.Types.Enum.Performance
       (VkPerformanceConfigurationTypeINTEL(VkPerformanceConfigurationTypeINTEL,
                                            VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL),
        VkPerformanceCounterDescriptionBitmaskKHR(VkPerformanceCounterDescriptionBitmaskKHR,
                                                  VkPerformanceCounterDescriptionFlagsKHR,
                                                  VkPerformanceCounterDescriptionFlagBitsKHR,
                                                  VK_PERFORMANCE_COUNTER_DESCRIPTION_PERFORMANCE_IMPACTING_KHR,
                                                  VK_PERFORMANCE_COUNTER_DESCRIPTION_CONCURRENTLY_IMPACTED_KHR),
        VkPerformanceCounterDescriptionFlagsKHR,
        VkPerformanceCounterDescriptionFlagBitsKHR,
        pattern VK_QUERY_SCOPE_COMMAND_BUFFER_KHR,
        pattern VK_QUERY_SCOPE_RENDER_PASS_KHR,
        pattern VK_QUERY_SCOPE_COMMAND_KHR,
        VkPerformanceCounterScopeKHR(VkPerformanceCounterScopeKHR,
                                     VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR,
                                     VK_PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR,
                                     VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR),
        VkPerformanceCounterStorageKHR(VkPerformanceCounterStorageKHR,
                                       VK_PERFORMANCE_COUNTER_STORAGE_INT32_KHR,
                                       VK_PERFORMANCE_COUNTER_STORAGE_INT64_KHR,
                                       VK_PERFORMANCE_COUNTER_STORAGE_UINT32_KHR,
                                       VK_PERFORMANCE_COUNTER_STORAGE_UINT64_KHR,
                                       VK_PERFORMANCE_COUNTER_STORAGE_FLOAT32_KHR,
                                       VK_PERFORMANCE_COUNTER_STORAGE_FLOAT64_KHR),
        VkPerformanceCounterUnitKHR(VkPerformanceCounterUnitKHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_GENERIC_KHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_PERCENTAGE_KHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_NANOSECONDS_KHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_BYTES_KHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_BYTES_PER_SECOND_KHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_KELVIN_KHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_WATTS_KHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_VOLTS_KHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_AMPS_KHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_HERTZ_KHR,
                                    VK_PERFORMANCE_COUNTER_UNIT_CYCLES_KHR),
        VkPerformanceOverrideTypeINTEL(VkPerformanceOverrideTypeINTEL,
                                       VK_PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL,
                                       VK_PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL),
        VkPerformanceParameterTypeINTEL(VkPerformanceParameterTypeINTEL,
                                        VK_PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL,
                                        VK_PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL),
        VkPerformanceValueTypeINTEL(VkPerformanceValueTypeINTEL,
                                    VK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL,
                                    VK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL,
                                    VK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL,
                                    VK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL,
                                    VK_PERFORMANCE_VALUE_TYPE_STRING_INTEL))
       where
import Data.Bits                       (Bits, FiniteBits)
import Foreign.Storable                (Storable)
import GHC.Read                        (choose, expectP)
import Graphics.Vulkan.Marshal         (FlagBit, FlagMask, FlagType, Int32)
import Graphics.Vulkan.Types.BaseTypes (VkFlags (..))
import Text.ParserCombinators.ReadPrec (prec, step, (+++))
import Text.Read                       (Read (..), parens)
import Text.Read.Lex                   (Lexeme (..))

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkPerformanceConfigurationTypeINTEL VkPerformanceConfigurationTypeINTEL registry at www.khronos.org>
newtype VkPerformanceConfigurationTypeINTEL = VkPerformanceConfigurationTypeINTEL Int32
                                              deriving (VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
(VkPerformanceConfigurationTypeINTEL
 -> VkPerformanceConfigurationTypeINTEL -> Bool)
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL -> Bool)
-> Eq VkPerformanceConfigurationTypeINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
$c/= :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
== :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
$c== :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
Eq, Eq VkPerformanceConfigurationTypeINTEL
Eq VkPerformanceConfigurationTypeINTEL
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL -> Ordering)
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL -> Bool)
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL -> Bool)
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL -> Bool)
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL -> Bool)
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL)
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL)
-> Ord VkPerformanceConfigurationTypeINTEL
VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Ordering
VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
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 :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
$cmin :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
max :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
$cmax :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
>= :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
$c>= :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
> :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
$c> :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
<= :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
$c<= :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
< :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
$c< :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Bool
compare :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Ordering
$ccompare :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> Ordering
Ord, Int -> VkPerformanceConfigurationTypeINTEL
VkPerformanceConfigurationTypeINTEL -> Int
VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
(VkPerformanceConfigurationTypeINTEL
 -> VkPerformanceConfigurationTypeINTEL)
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL)
-> (Int -> VkPerformanceConfigurationTypeINTEL)
-> (VkPerformanceConfigurationTypeINTEL -> Int)
-> (VkPerformanceConfigurationTypeINTEL
    -> [VkPerformanceConfigurationTypeINTEL])
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL
    -> [VkPerformanceConfigurationTypeINTEL])
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL
    -> [VkPerformanceConfigurationTypeINTEL])
-> (VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL
    -> [VkPerformanceConfigurationTypeINTEL])
-> Enum VkPerformanceConfigurationTypeINTEL
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
$cenumFromThenTo :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
enumFromTo :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
$cenumFromTo :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
enumFromThen :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
$cenumFromThen :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
enumFrom :: VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
$cenumFrom :: VkPerformanceConfigurationTypeINTEL
-> [VkPerformanceConfigurationTypeINTEL]
fromEnum :: VkPerformanceConfigurationTypeINTEL -> Int
$cfromEnum :: VkPerformanceConfigurationTypeINTEL -> Int
toEnum :: Int -> VkPerformanceConfigurationTypeINTEL
$ctoEnum :: Int -> VkPerformanceConfigurationTypeINTEL
pred :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
$cpred :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
succ :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
$csucc :: VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL
Enum, Ptr VkPerformanceConfigurationTypeINTEL
-> IO VkPerformanceConfigurationTypeINTEL
Ptr VkPerformanceConfigurationTypeINTEL
-> Int -> IO VkPerformanceConfigurationTypeINTEL
Ptr VkPerformanceConfigurationTypeINTEL
-> Int -> VkPerformanceConfigurationTypeINTEL -> IO ()
Ptr VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> IO ()
VkPerformanceConfigurationTypeINTEL -> Int
(VkPerformanceConfigurationTypeINTEL -> Int)
-> (VkPerformanceConfigurationTypeINTEL -> Int)
-> (Ptr VkPerformanceConfigurationTypeINTEL
    -> Int -> IO VkPerformanceConfigurationTypeINTEL)
-> (Ptr VkPerformanceConfigurationTypeINTEL
    -> Int -> VkPerformanceConfigurationTypeINTEL -> IO ())
-> (forall b.
    Ptr b -> Int -> IO VkPerformanceConfigurationTypeINTEL)
-> (forall b.
    Ptr b -> Int -> VkPerformanceConfigurationTypeINTEL -> IO ())
-> (Ptr VkPerformanceConfigurationTypeINTEL
    -> IO VkPerformanceConfigurationTypeINTEL)
-> (Ptr VkPerformanceConfigurationTypeINTEL
    -> VkPerformanceConfigurationTypeINTEL -> IO ())
-> Storable VkPerformanceConfigurationTypeINTEL
forall b. Ptr b -> Int -> IO VkPerformanceConfigurationTypeINTEL
forall b.
Ptr b -> Int -> VkPerformanceConfigurationTypeINTEL -> 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 VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> IO ()
$cpoke :: Ptr VkPerformanceConfigurationTypeINTEL
-> VkPerformanceConfigurationTypeINTEL -> IO ()
peek :: Ptr VkPerformanceConfigurationTypeINTEL
-> IO VkPerformanceConfigurationTypeINTEL
$cpeek :: Ptr VkPerformanceConfigurationTypeINTEL
-> IO VkPerformanceConfigurationTypeINTEL
pokeByteOff :: forall b.
Ptr b -> Int -> VkPerformanceConfigurationTypeINTEL -> IO ()
$cpokeByteOff :: forall b.
Ptr b -> Int -> VkPerformanceConfigurationTypeINTEL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceConfigurationTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceConfigurationTypeINTEL
pokeElemOff :: Ptr VkPerformanceConfigurationTypeINTEL
-> Int -> VkPerformanceConfigurationTypeINTEL -> IO ()
$cpokeElemOff :: Ptr VkPerformanceConfigurationTypeINTEL
-> Int -> VkPerformanceConfigurationTypeINTEL -> IO ()
peekElemOff :: Ptr VkPerformanceConfigurationTypeINTEL
-> Int -> IO VkPerformanceConfigurationTypeINTEL
$cpeekElemOff :: Ptr VkPerformanceConfigurationTypeINTEL
-> Int -> IO VkPerformanceConfigurationTypeINTEL
alignment :: VkPerformanceConfigurationTypeINTEL -> Int
$calignment :: VkPerformanceConfigurationTypeINTEL -> Int
sizeOf :: VkPerformanceConfigurationTypeINTEL -> Int
$csizeOf :: VkPerformanceConfigurationTypeINTEL -> Int
Storable)

instance Show VkPerformanceConfigurationTypeINTEL where
    showsPrec :: Int -> VkPerformanceConfigurationTypeINTEL -> ShowS
showsPrec Int
_
      VkPerformanceConfigurationTypeINTEL
VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL
      = String -> ShowS
showString
          String
"VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL"
    showsPrec Int
p (VkPerformanceConfigurationTypeINTEL Int32
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkPerformanceConfigurationTypeINTEL " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
             Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkPerformanceConfigurationTypeINTEL where
    readPrec :: ReadPrec VkPerformanceConfigurationTypeINTEL
readPrec
      = ReadPrec VkPerformanceConfigurationTypeINTEL
-> ReadPrec VkPerformanceConfigurationTypeINTEL
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec VkPerformanceConfigurationTypeINTEL)]
-> ReadPrec VkPerformanceConfigurationTypeINTEL
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL",
               VkPerformanceConfigurationTypeINTEL
-> ReadPrec VkPerformanceConfigurationTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure
                 VkPerformanceConfigurationTypeINTEL
VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL)]
             ReadPrec VkPerformanceConfigurationTypeINTEL
-> ReadPrec VkPerformanceConfigurationTypeINTEL
-> ReadPrec VkPerformanceConfigurationTypeINTEL
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec VkPerformanceConfigurationTypeINTEL
-> ReadPrec VkPerformanceConfigurationTypeINTEL
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkPerformanceConfigurationTypeINTEL") ReadPrec ()
-> ReadPrec VkPerformanceConfigurationTypeINTEL
-> ReadPrec VkPerformanceConfigurationTypeINTEL
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (Int32 -> VkPerformanceConfigurationTypeINTEL
VkPerformanceConfigurationTypeINTEL (Int32 -> VkPerformanceConfigurationTypeINTEL)
-> ReadPrec Int32 -> ReadPrec VkPerformanceConfigurationTypeINTEL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL
        :: VkPerformanceConfigurationTypeINTEL

pattern $bVK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL :: VkPerformanceConfigurationTypeINTEL
$mVK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL :: forall {r}.
VkPerformanceConfigurationTypeINTEL
-> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL
        = VkPerformanceConfigurationTypeINTEL 0

newtype VkPerformanceCounterDescriptionBitmaskKHR (a ::
                                                     FlagType) = VkPerformanceCounterDescriptionBitmaskKHR VkFlags
                                                                 deriving (VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
(VkPerformanceCounterDescriptionBitmaskKHR a
 -> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool)
-> (VkPerformanceCounterDescriptionBitmaskKHR a
    -> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool)
-> Eq (VkPerformanceCounterDescriptionBitmaskKHR a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
/= :: VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
$c/= :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
== :: VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
$c== :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
Eq, Eq (VkPerformanceCounterDescriptionBitmaskKHR a)
Eq (VkPerformanceCounterDescriptionBitmaskKHR a)
-> (VkPerformanceCounterDescriptionBitmaskKHR a
    -> VkPerformanceCounterDescriptionBitmaskKHR a -> Ordering)
-> (VkPerformanceCounterDescriptionBitmaskKHR a
    -> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool)
-> (VkPerformanceCounterDescriptionBitmaskKHR a
    -> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool)
-> (VkPerformanceCounterDescriptionBitmaskKHR a
    -> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool)
-> (VkPerformanceCounterDescriptionBitmaskKHR a
    -> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool)
-> (VkPerformanceCounterDescriptionBitmaskKHR a
    -> VkPerformanceCounterDescriptionBitmaskKHR a
    -> VkPerformanceCounterDescriptionBitmaskKHR a)
-> (VkPerformanceCounterDescriptionBitmaskKHR a
    -> VkPerformanceCounterDescriptionBitmaskKHR a
    -> VkPerformanceCounterDescriptionBitmaskKHR a)
-> Ord (VkPerformanceCounterDescriptionBitmaskKHR a)
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Ordering
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
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
forall (a :: FlagType).
Eq (VkPerformanceCounterDescriptionBitmaskKHR a)
forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Ordering
forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
min :: VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
$cmin :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
max :: VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
$cmax :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a
>= :: VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
$c>= :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
> :: VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
$c> :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
<= :: VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
$c<= :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
< :: VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
$c< :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Bool
compare :: VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Ordering
$ccompare :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a
-> VkPerformanceCounterDescriptionBitmaskKHR a -> Ordering
Ord, Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> Int -> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
VkPerformanceCounterDescriptionBitmaskKHR a -> Int
(VkPerformanceCounterDescriptionBitmaskKHR a -> Int)
-> (VkPerformanceCounterDescriptionBitmaskKHR a -> Int)
-> (Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
    -> Int -> IO (VkPerformanceCounterDescriptionBitmaskKHR a))
-> (Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
    -> Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ())
-> (forall b.
    Ptr b -> Int -> IO (VkPerformanceCounterDescriptionBitmaskKHR a))
-> (forall b.
    Ptr b
    -> Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ())
-> (Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
    -> IO (VkPerformanceCounterDescriptionBitmaskKHR a))
-> (Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
    -> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ())
-> Storable (VkPerformanceCounterDescriptionBitmaskKHR a)
forall b.
Ptr b -> Int -> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
forall b.
Ptr b
-> Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> 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
forall (a :: FlagType).
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
forall (a :: FlagType).
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> Int -> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
forall (a :: FlagType).
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
forall (a :: FlagType).
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a -> Int
forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
forall (a :: FlagType) b.
Ptr b
-> Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
poke :: Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
$cpoke :: forall (a :: FlagType).
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
peek :: Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
$cpeek :: forall (a :: FlagType).
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
pokeByteOff :: forall b.
Ptr b
-> Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
$cpokeByteOff :: forall (a :: FlagType) b.
Ptr b
-> Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
peekByteOff :: forall b.
Ptr b -> Int -> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
$cpeekByteOff :: forall (a :: FlagType) b.
Ptr b -> Int -> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
pokeElemOff :: Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
$cpokeElemOff :: forall (a :: FlagType).
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> IO ()
peekElemOff :: Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> Int -> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
$cpeekElemOff :: forall (a :: FlagType).
Ptr (VkPerformanceCounterDescriptionBitmaskKHR a)
-> Int -> IO (VkPerformanceCounterDescriptionBitmaskKHR a)
alignment :: VkPerformanceCounterDescriptionBitmaskKHR a -> Int
$calignment :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a -> Int
sizeOf :: VkPerformanceCounterDescriptionBitmaskKHR a -> Int
$csizeOf :: forall (a :: FlagType).
VkPerformanceCounterDescriptionBitmaskKHR a -> Int
Storable)

type VkPerformanceCounterDescriptionFlagsKHR =
     VkPerformanceCounterDescriptionBitmaskKHR FlagMask

type VkPerformanceCounterDescriptionFlagBitsKHR =
     VkPerformanceCounterDescriptionBitmaskKHR FlagBit

pattern VkPerformanceCounterDescriptionFlagBitsKHR ::
        VkFlags -> VkPerformanceCounterDescriptionBitmaskKHR FlagBit

pattern $bVkPerformanceCounterDescriptionFlagBitsKHR :: VkFlags -> VkPerformanceCounterDescriptionBitmaskKHR FlagBit
$mVkPerformanceCounterDescriptionFlagBitsKHR :: forall {r}.
VkPerformanceCounterDescriptionBitmaskKHR FlagBit
-> (VkFlags -> r) -> (Void# -> r) -> r
VkPerformanceCounterDescriptionFlagBitsKHR n =
        VkPerformanceCounterDescriptionBitmaskKHR n

pattern VkPerformanceCounterDescriptionFlagsKHR ::
        VkFlags -> VkPerformanceCounterDescriptionBitmaskKHR FlagMask

pattern $bVkPerformanceCounterDescriptionFlagsKHR :: VkFlags -> VkPerformanceCounterDescriptionBitmaskKHR FlagMask
$mVkPerformanceCounterDescriptionFlagsKHR :: forall {r}.
VkPerformanceCounterDescriptionBitmaskKHR FlagMask
-> (VkFlags -> r) -> (Void# -> r) -> r
VkPerformanceCounterDescriptionFlagsKHR n =
        VkPerformanceCounterDescriptionBitmaskKHR n

deriving instance
         Bits (VkPerformanceCounterDescriptionBitmaskKHR FlagMask)

deriving instance
         FiniteBits (VkPerformanceCounterDescriptionBitmaskKHR FlagMask)

instance Show (VkPerformanceCounterDescriptionBitmaskKHR a) where
    showsPrec :: Int -> VkPerformanceCounterDescriptionBitmaskKHR a -> ShowS
showsPrec Int
_
      VkPerformanceCounterDescriptionBitmaskKHR a
VK_PERFORMANCE_COUNTER_DESCRIPTION_PERFORMANCE_IMPACTING_KHR
      = String -> ShowS
showString
          String
"VK_PERFORMANCE_COUNTER_DESCRIPTION_PERFORMANCE_IMPACTING_KHR"
    showsPrec Int
_
      VkPerformanceCounterDescriptionBitmaskKHR a
VK_PERFORMANCE_COUNTER_DESCRIPTION_CONCURRENTLY_IMPACTED_KHR
      = String -> ShowS
showString
          String
"VK_PERFORMANCE_COUNTER_DESCRIPTION_CONCURRENTLY_IMPACTED_KHR"
    showsPrec Int
p (VkPerformanceCounterDescriptionBitmaskKHR VkFlags
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkPerformanceCounterDescriptionBitmaskKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
             Int -> VkFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 VkFlags
x)

instance Read (VkPerformanceCounterDescriptionBitmaskKHR a) where
    readPrec :: ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
readPrec
      = ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a))]
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_PERFORMANCE_COUNTER_DESCRIPTION_PERFORMANCE_IMPACTING_KHR",
               VkPerformanceCounterDescriptionBitmaskKHR a
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterDescriptionBitmaskKHR a
forall (a :: FlagType). VkPerformanceCounterDescriptionBitmaskKHR a
VK_PERFORMANCE_COUNTER_DESCRIPTION_PERFORMANCE_IMPACTING_KHR),
              (String
"VK_PERFORMANCE_COUNTER_DESCRIPTION_CONCURRENTLY_IMPACTED_KHR",
               VkPerformanceCounterDescriptionBitmaskKHR a
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterDescriptionBitmaskKHR a
forall (a :: FlagType). VkPerformanceCounterDescriptionBitmaskKHR a
VK_PERFORMANCE_COUNTER_DESCRIPTION_CONCURRENTLY_IMPACTED_KHR)]
             ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkPerformanceCounterDescriptionBitmaskKHR") ReadPrec ()
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (VkFlags -> VkPerformanceCounterDescriptionBitmaskKHR a
forall (a :: FlagType).
VkFlags -> VkPerformanceCounterDescriptionBitmaskKHR a
VkPerformanceCounterDescriptionBitmaskKHR (VkFlags -> VkPerformanceCounterDescriptionBitmaskKHR a)
-> ReadPrec VkFlags
-> ReadPrec (VkPerformanceCounterDescriptionBitmaskKHR a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec VkFlags -> ReadPrec VkFlags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec VkFlags
forall a. Read a => ReadPrec a
readPrec)))

-- | bitpos = @0@
pattern VK_PERFORMANCE_COUNTER_DESCRIPTION_PERFORMANCE_IMPACTING_KHR
        :: VkPerformanceCounterDescriptionBitmaskKHR a

pattern $bVK_PERFORMANCE_COUNTER_DESCRIPTION_PERFORMANCE_IMPACTING_KHR :: forall (a :: FlagType). VkPerformanceCounterDescriptionBitmaskKHR a
$mVK_PERFORMANCE_COUNTER_DESCRIPTION_PERFORMANCE_IMPACTING_KHR :: forall {r} {a :: FlagType}.
VkPerformanceCounterDescriptionBitmaskKHR a
-> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_DESCRIPTION_PERFORMANCE_IMPACTING_KHR
        = VkPerformanceCounterDescriptionBitmaskKHR 1

-- | bitpos = @1@
pattern VK_PERFORMANCE_COUNTER_DESCRIPTION_CONCURRENTLY_IMPACTED_KHR
        :: VkPerformanceCounterDescriptionBitmaskKHR a

pattern $bVK_PERFORMANCE_COUNTER_DESCRIPTION_CONCURRENTLY_IMPACTED_KHR :: forall (a :: FlagType). VkPerformanceCounterDescriptionBitmaskKHR a
$mVK_PERFORMANCE_COUNTER_DESCRIPTION_CONCURRENTLY_IMPACTED_KHR :: forall {r} {a :: FlagType}.
VkPerformanceCounterDescriptionBitmaskKHR a
-> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_DESCRIPTION_CONCURRENTLY_IMPACTED_KHR
        = VkPerformanceCounterDescriptionBitmaskKHR 2

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkPerformanceCounterScopeKHR VkPerformanceCounterScopeKHR registry at www.khronos.org>
newtype VkPerformanceCounterScopeKHR = VkPerformanceCounterScopeKHR Int32
                                       deriving (VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
(VkPerformanceCounterScopeKHR
 -> VkPerformanceCounterScopeKHR -> Bool)
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> Bool)
-> Eq VkPerformanceCounterScopeKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
$c/= :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
== :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
$c== :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
Eq, Eq VkPerformanceCounterScopeKHR
Eq VkPerformanceCounterScopeKHR
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> Ordering)
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> Bool)
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> Bool)
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> Bool)
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> Bool)
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR)
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR)
-> Ord VkPerformanceCounterScopeKHR
VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Ordering
VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR
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 :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR
$cmin :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR
max :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR
$cmax :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR
>= :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
$c>= :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
> :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
$c> :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
<= :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
$c<= :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
< :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
$c< :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Bool
compare :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Ordering
$ccompare :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> Ordering
Ord, Int -> VkPerformanceCounterScopeKHR
VkPerformanceCounterScopeKHR -> Int
VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR]
VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR
VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR]
VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR
-> [VkPerformanceCounterScopeKHR]
(VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR)
-> (VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR)
-> (Int -> VkPerformanceCounterScopeKHR)
-> (VkPerformanceCounterScopeKHR -> Int)
-> (VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR])
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR])
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR])
-> (VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR
    -> [VkPerformanceCounterScopeKHR])
-> Enum VkPerformanceCounterScopeKHR
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR
-> [VkPerformanceCounterScopeKHR]
$cenumFromThenTo :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR
-> [VkPerformanceCounterScopeKHR]
enumFromTo :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR]
$cenumFromTo :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR]
enumFromThen :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR]
$cenumFromThen :: VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR]
enumFrom :: VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR]
$cenumFrom :: VkPerformanceCounterScopeKHR -> [VkPerformanceCounterScopeKHR]
fromEnum :: VkPerformanceCounterScopeKHR -> Int
$cfromEnum :: VkPerformanceCounterScopeKHR -> Int
toEnum :: Int -> VkPerformanceCounterScopeKHR
$ctoEnum :: Int -> VkPerformanceCounterScopeKHR
pred :: VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR
$cpred :: VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR
succ :: VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR
$csucc :: VkPerformanceCounterScopeKHR -> VkPerformanceCounterScopeKHR
Enum, Ptr VkPerformanceCounterScopeKHR -> IO VkPerformanceCounterScopeKHR
Ptr VkPerformanceCounterScopeKHR
-> Int -> IO VkPerformanceCounterScopeKHR
Ptr VkPerformanceCounterScopeKHR
-> Int -> VkPerformanceCounterScopeKHR -> IO ()
Ptr VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> IO ()
VkPerformanceCounterScopeKHR -> Int
(VkPerformanceCounterScopeKHR -> Int)
-> (VkPerformanceCounterScopeKHR -> Int)
-> (Ptr VkPerformanceCounterScopeKHR
    -> Int -> IO VkPerformanceCounterScopeKHR)
-> (Ptr VkPerformanceCounterScopeKHR
    -> Int -> VkPerformanceCounterScopeKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO VkPerformanceCounterScopeKHR)
-> (forall b.
    Ptr b -> Int -> VkPerformanceCounterScopeKHR -> IO ())
-> (Ptr VkPerformanceCounterScopeKHR
    -> IO VkPerformanceCounterScopeKHR)
-> (Ptr VkPerformanceCounterScopeKHR
    -> VkPerformanceCounterScopeKHR -> IO ())
-> Storable VkPerformanceCounterScopeKHR
forall b. Ptr b -> Int -> IO VkPerformanceCounterScopeKHR
forall b. Ptr b -> Int -> VkPerformanceCounterScopeKHR -> 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 VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> IO ()
$cpoke :: Ptr VkPerformanceCounterScopeKHR
-> VkPerformanceCounterScopeKHR -> IO ()
peek :: Ptr VkPerformanceCounterScopeKHR -> IO VkPerformanceCounterScopeKHR
$cpeek :: Ptr VkPerformanceCounterScopeKHR -> IO VkPerformanceCounterScopeKHR
pokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceCounterScopeKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceCounterScopeKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceCounterScopeKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceCounterScopeKHR
pokeElemOff :: Ptr VkPerformanceCounterScopeKHR
-> Int -> VkPerformanceCounterScopeKHR -> IO ()
$cpokeElemOff :: Ptr VkPerformanceCounterScopeKHR
-> Int -> VkPerformanceCounterScopeKHR -> IO ()
peekElemOff :: Ptr VkPerformanceCounterScopeKHR
-> Int -> IO VkPerformanceCounterScopeKHR
$cpeekElemOff :: Ptr VkPerformanceCounterScopeKHR
-> Int -> IO VkPerformanceCounterScopeKHR
alignment :: VkPerformanceCounterScopeKHR -> Int
$calignment :: VkPerformanceCounterScopeKHR -> Int
sizeOf :: VkPerformanceCounterScopeKHR -> Int
$csizeOf :: VkPerformanceCounterScopeKHR -> Int
Storable)

instance Show VkPerformanceCounterScopeKHR where
    showsPrec :: Int -> VkPerformanceCounterScopeKHR -> ShowS
showsPrec Int
_ VkPerformanceCounterScopeKHR
VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR"
    showsPrec Int
_ VkPerformanceCounterScopeKHR
VK_PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR"
    showsPrec Int
_ VkPerformanceCounterScopeKHR
VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR"
    showsPrec Int
_ VkPerformanceCounterScopeKHR
VK_QUERY_SCOPE_COMMAND_BUFFER_KHR
      = String -> ShowS
showString String
"VK_QUERY_SCOPE_COMMAND_BUFFER_KHR"
    showsPrec Int
_ VkPerformanceCounterScopeKHR
VK_QUERY_SCOPE_RENDER_PASS_KHR
      = String -> ShowS
showString String
"VK_QUERY_SCOPE_RENDER_PASS_KHR"
    showsPrec Int
_ VkPerformanceCounterScopeKHR
VK_QUERY_SCOPE_COMMAND_KHR
      = String -> ShowS
showString String
"VK_QUERY_SCOPE_COMMAND_KHR"
    showsPrec Int
p (VkPerformanceCounterScopeKHR Int32
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkPerformanceCounterScopeKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkPerformanceCounterScopeKHR where
    readPrec :: ReadPrec VkPerformanceCounterScopeKHR
readPrec
      = ReadPrec VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec VkPerformanceCounterScopeKHR)]
-> ReadPrec VkPerformanceCounterScopeKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR",
               VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterScopeKHR
VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR),
              (String
"VK_PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR",
               VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterScopeKHR
VK_PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR),
              (String
"VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR",
               VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterScopeKHR
VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR),
              (String
"VK_QUERY_SCOPE_COMMAND_BUFFER_KHR",
               VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterScopeKHR
VK_QUERY_SCOPE_COMMAND_BUFFER_KHR),
              (String
"VK_QUERY_SCOPE_RENDER_PASS_KHR",
               VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterScopeKHR
VK_QUERY_SCOPE_RENDER_PASS_KHR),
              (String
"VK_QUERY_SCOPE_COMMAND_KHR", VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterScopeKHR
VK_QUERY_SCOPE_COMMAND_KHR)]
             ReadPrec VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkPerformanceCounterScopeKHR") ReadPrec ()
-> ReadPrec VkPerformanceCounterScopeKHR
-> ReadPrec VkPerformanceCounterScopeKHR
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (Int32 -> VkPerformanceCounterScopeKHR
VkPerformanceCounterScopeKHR (Int32 -> VkPerformanceCounterScopeKHR)
-> ReadPrec Int32 -> ReadPrec VkPerformanceCounterScopeKHR
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR ::
        VkPerformanceCounterScopeKHR

pattern $bVK_PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR :: VkPerformanceCounterScopeKHR
$mVK_PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR :: forall {r}.
VkPerformanceCounterScopeKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR =
        VkPerformanceCounterScopeKHR 0

pattern VK_PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR ::
        VkPerformanceCounterScopeKHR

pattern $bVK_PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR :: VkPerformanceCounterScopeKHR
$mVK_PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR :: forall {r}.
VkPerformanceCounterScopeKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR =
        VkPerformanceCounterScopeKHR 1

pattern VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR ::
        VkPerformanceCounterScopeKHR

pattern $bVK_PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR :: VkPerformanceCounterScopeKHR
$mVK_PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR :: forall {r}.
VkPerformanceCounterScopeKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR =
        VkPerformanceCounterScopeKHR 2

pattern $bVK_QUERY_SCOPE_COMMAND_BUFFER_KHR :: VkPerformanceCounterScopeKHR
$mVK_QUERY_SCOPE_COMMAND_BUFFER_KHR :: forall {r}.
VkPerformanceCounterScopeKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_SCOPE_COMMAND_BUFFER_KHR =
        VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_BUFFER_KHR

pattern $bVK_QUERY_SCOPE_RENDER_PASS_KHR :: VkPerformanceCounterScopeKHR
$mVK_QUERY_SCOPE_RENDER_PASS_KHR :: forall {r}.
VkPerformanceCounterScopeKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_SCOPE_RENDER_PASS_KHR =
        VK_PERFORMANCE_COUNTER_SCOPE_RENDER_PASS_KHR

pattern $bVK_QUERY_SCOPE_COMMAND_KHR :: VkPerformanceCounterScopeKHR
$mVK_QUERY_SCOPE_COMMAND_KHR :: forall {r}.
VkPerformanceCounterScopeKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_SCOPE_COMMAND_KHR =
        VK_PERFORMANCE_COUNTER_SCOPE_COMMAND_KHR

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkPerformanceCounterStorageKHR VkPerformanceCounterStorageKHR registry at www.khronos.org>
newtype VkPerformanceCounterStorageKHR = VkPerformanceCounterStorageKHR Int32
                                         deriving (VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
(VkPerformanceCounterStorageKHR
 -> VkPerformanceCounterStorageKHR -> Bool)
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR -> Bool)
-> Eq VkPerformanceCounterStorageKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
$c/= :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
== :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
$c== :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
Eq, Eq VkPerformanceCounterStorageKHR
Eq VkPerformanceCounterStorageKHR
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR -> Ordering)
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR -> Bool)
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR -> Bool)
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR -> Bool)
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR -> Bool)
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR)
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR)
-> Ord VkPerformanceCounterStorageKHR
VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Ordering
VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR
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 :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR
$cmin :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR
max :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR
$cmax :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR
>= :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
$c>= :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
> :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
$c> :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
<= :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
$c<= :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
< :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
$c< :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Bool
compare :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Ordering
$ccompare :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> Ordering
Ord, Int -> VkPerformanceCounterStorageKHR
VkPerformanceCounterStorageKHR -> Int
VkPerformanceCounterStorageKHR -> [VkPerformanceCounterStorageKHR]
VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR
VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> [VkPerformanceCounterStorageKHR]
VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> [VkPerformanceCounterStorageKHR]
(VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR)
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR)
-> (Int -> VkPerformanceCounterStorageKHR)
-> (VkPerformanceCounterStorageKHR -> Int)
-> (VkPerformanceCounterStorageKHR
    -> [VkPerformanceCounterStorageKHR])
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR
    -> [VkPerformanceCounterStorageKHR])
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR
    -> [VkPerformanceCounterStorageKHR])
-> (VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR
    -> [VkPerformanceCounterStorageKHR])
-> Enum VkPerformanceCounterStorageKHR
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> [VkPerformanceCounterStorageKHR]
$cenumFromThenTo :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> [VkPerformanceCounterStorageKHR]
enumFromTo :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> [VkPerformanceCounterStorageKHR]
$cenumFromTo :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> [VkPerformanceCounterStorageKHR]
enumFromThen :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> [VkPerformanceCounterStorageKHR]
$cenumFromThen :: VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR
-> [VkPerformanceCounterStorageKHR]
enumFrom :: VkPerformanceCounterStorageKHR -> [VkPerformanceCounterStorageKHR]
$cenumFrom :: VkPerformanceCounterStorageKHR -> [VkPerformanceCounterStorageKHR]
fromEnum :: VkPerformanceCounterStorageKHR -> Int
$cfromEnum :: VkPerformanceCounterStorageKHR -> Int
toEnum :: Int -> VkPerformanceCounterStorageKHR
$ctoEnum :: Int -> VkPerformanceCounterStorageKHR
pred :: VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR
$cpred :: VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR
succ :: VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR
$csucc :: VkPerformanceCounterStorageKHR -> VkPerformanceCounterStorageKHR
Enum, Ptr VkPerformanceCounterStorageKHR
-> IO VkPerformanceCounterStorageKHR
Ptr VkPerformanceCounterStorageKHR
-> Int -> IO VkPerformanceCounterStorageKHR
Ptr VkPerformanceCounterStorageKHR
-> Int -> VkPerformanceCounterStorageKHR -> IO ()
Ptr VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> IO ()
VkPerformanceCounterStorageKHR -> Int
(VkPerformanceCounterStorageKHR -> Int)
-> (VkPerformanceCounterStorageKHR -> Int)
-> (Ptr VkPerformanceCounterStorageKHR
    -> Int -> IO VkPerformanceCounterStorageKHR)
-> (Ptr VkPerformanceCounterStorageKHR
    -> Int -> VkPerformanceCounterStorageKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO VkPerformanceCounterStorageKHR)
-> (forall b.
    Ptr b -> Int -> VkPerformanceCounterStorageKHR -> IO ())
-> (Ptr VkPerformanceCounterStorageKHR
    -> IO VkPerformanceCounterStorageKHR)
-> (Ptr VkPerformanceCounterStorageKHR
    -> VkPerformanceCounterStorageKHR -> IO ())
-> Storable VkPerformanceCounterStorageKHR
forall b. Ptr b -> Int -> IO VkPerformanceCounterStorageKHR
forall b. Ptr b -> Int -> VkPerformanceCounterStorageKHR -> 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 VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> IO ()
$cpoke :: Ptr VkPerformanceCounterStorageKHR
-> VkPerformanceCounterStorageKHR -> IO ()
peek :: Ptr VkPerformanceCounterStorageKHR
-> IO VkPerformanceCounterStorageKHR
$cpeek :: Ptr VkPerformanceCounterStorageKHR
-> IO VkPerformanceCounterStorageKHR
pokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceCounterStorageKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceCounterStorageKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceCounterStorageKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceCounterStorageKHR
pokeElemOff :: Ptr VkPerformanceCounterStorageKHR
-> Int -> VkPerformanceCounterStorageKHR -> IO ()
$cpokeElemOff :: Ptr VkPerformanceCounterStorageKHR
-> Int -> VkPerformanceCounterStorageKHR -> IO ()
peekElemOff :: Ptr VkPerformanceCounterStorageKHR
-> Int -> IO VkPerformanceCounterStorageKHR
$cpeekElemOff :: Ptr VkPerformanceCounterStorageKHR
-> Int -> IO VkPerformanceCounterStorageKHR
alignment :: VkPerformanceCounterStorageKHR -> Int
$calignment :: VkPerformanceCounterStorageKHR -> Int
sizeOf :: VkPerformanceCounterStorageKHR -> Int
$csizeOf :: VkPerformanceCounterStorageKHR -> Int
Storable)

instance Show VkPerformanceCounterStorageKHR where
    showsPrec :: Int -> VkPerformanceCounterStorageKHR -> ShowS
showsPrec Int
_ VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_INT32_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_STORAGE_INT32_KHR"
    showsPrec Int
_ VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_INT64_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_STORAGE_INT64_KHR"
    showsPrec Int
_ VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_UINT32_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_STORAGE_UINT32_KHR"
    showsPrec Int
_ VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_UINT64_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_STORAGE_UINT64_KHR"
    showsPrec Int
_ VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_FLOAT32_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_STORAGE_FLOAT32_KHR"
    showsPrec Int
_ VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_FLOAT64_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_STORAGE_FLOAT64_KHR"
    showsPrec Int
p (VkPerformanceCounterStorageKHR Int32
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkPerformanceCounterStorageKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkPerformanceCounterStorageKHR where
    readPrec :: ReadPrec VkPerformanceCounterStorageKHR
readPrec
      = ReadPrec VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec VkPerformanceCounterStorageKHR)]
-> ReadPrec VkPerformanceCounterStorageKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_PERFORMANCE_COUNTER_STORAGE_INT32_KHR",
               VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_INT32_KHR),
              (String
"VK_PERFORMANCE_COUNTER_STORAGE_INT64_KHR",
               VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_INT64_KHR),
              (String
"VK_PERFORMANCE_COUNTER_STORAGE_UINT32_KHR",
               VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_UINT32_KHR),
              (String
"VK_PERFORMANCE_COUNTER_STORAGE_UINT64_KHR",
               VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_UINT64_KHR),
              (String
"VK_PERFORMANCE_COUNTER_STORAGE_FLOAT32_KHR",
               VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_FLOAT32_KHR),
              (String
"VK_PERFORMANCE_COUNTER_STORAGE_FLOAT64_KHR",
               VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterStorageKHR
VK_PERFORMANCE_COUNTER_STORAGE_FLOAT64_KHR)]
             ReadPrec VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkPerformanceCounterStorageKHR") ReadPrec ()
-> ReadPrec VkPerformanceCounterStorageKHR
-> ReadPrec VkPerformanceCounterStorageKHR
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (Int32 -> VkPerformanceCounterStorageKHR
VkPerformanceCounterStorageKHR (Int32 -> VkPerformanceCounterStorageKHR)
-> ReadPrec Int32 -> ReadPrec VkPerformanceCounterStorageKHR
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_PERFORMANCE_COUNTER_STORAGE_INT32_KHR ::
        VkPerformanceCounterStorageKHR

pattern $bVK_PERFORMANCE_COUNTER_STORAGE_INT32_KHR :: VkPerformanceCounterStorageKHR
$mVK_PERFORMANCE_COUNTER_STORAGE_INT32_KHR :: forall {r}.
VkPerformanceCounterStorageKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_STORAGE_INT32_KHR =
        VkPerformanceCounterStorageKHR 0

pattern VK_PERFORMANCE_COUNTER_STORAGE_INT64_KHR ::
        VkPerformanceCounterStorageKHR

pattern $bVK_PERFORMANCE_COUNTER_STORAGE_INT64_KHR :: VkPerformanceCounterStorageKHR
$mVK_PERFORMANCE_COUNTER_STORAGE_INT64_KHR :: forall {r}.
VkPerformanceCounterStorageKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_STORAGE_INT64_KHR =
        VkPerformanceCounterStorageKHR 1

pattern VK_PERFORMANCE_COUNTER_STORAGE_UINT32_KHR ::
        VkPerformanceCounterStorageKHR

pattern $bVK_PERFORMANCE_COUNTER_STORAGE_UINT32_KHR :: VkPerformanceCounterStorageKHR
$mVK_PERFORMANCE_COUNTER_STORAGE_UINT32_KHR :: forall {r}.
VkPerformanceCounterStorageKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_STORAGE_UINT32_KHR =
        VkPerformanceCounterStorageKHR 2

pattern VK_PERFORMANCE_COUNTER_STORAGE_UINT64_KHR ::
        VkPerformanceCounterStorageKHR

pattern $bVK_PERFORMANCE_COUNTER_STORAGE_UINT64_KHR :: VkPerformanceCounterStorageKHR
$mVK_PERFORMANCE_COUNTER_STORAGE_UINT64_KHR :: forall {r}.
VkPerformanceCounterStorageKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_STORAGE_UINT64_KHR =
        VkPerformanceCounterStorageKHR 3

pattern VK_PERFORMANCE_COUNTER_STORAGE_FLOAT32_KHR ::
        VkPerformanceCounterStorageKHR

pattern $bVK_PERFORMANCE_COUNTER_STORAGE_FLOAT32_KHR :: VkPerformanceCounterStorageKHR
$mVK_PERFORMANCE_COUNTER_STORAGE_FLOAT32_KHR :: forall {r}.
VkPerformanceCounterStorageKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_STORAGE_FLOAT32_KHR =
        VkPerformanceCounterStorageKHR 4

pattern VK_PERFORMANCE_COUNTER_STORAGE_FLOAT64_KHR ::
        VkPerformanceCounterStorageKHR

pattern $bVK_PERFORMANCE_COUNTER_STORAGE_FLOAT64_KHR :: VkPerformanceCounterStorageKHR
$mVK_PERFORMANCE_COUNTER_STORAGE_FLOAT64_KHR :: forall {r}.
VkPerformanceCounterStorageKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_STORAGE_FLOAT64_KHR =
        VkPerformanceCounterStorageKHR 5

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkPerformanceCounterUnitKHR VkPerformanceCounterUnitKHR registry at www.khronos.org>
newtype VkPerformanceCounterUnitKHR = VkPerformanceCounterUnitKHR Int32
                                      deriving (VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
(VkPerformanceCounterUnitKHR
 -> VkPerformanceCounterUnitKHR -> Bool)
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> Bool)
-> Eq VkPerformanceCounterUnitKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
$c/= :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
== :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
$c== :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
Eq, Eq VkPerformanceCounterUnitKHR
Eq VkPerformanceCounterUnitKHR
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> Ordering)
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> Bool)
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> Bool)
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> Bool)
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> Bool)
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR)
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR)
-> Ord VkPerformanceCounterUnitKHR
VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> Ordering
VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR
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 :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR
$cmin :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR
max :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR
$cmax :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR
>= :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
$c>= :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
> :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
$c> :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
<= :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
$c<= :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
< :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
$c< :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR -> Bool
compare :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> Ordering
$ccompare :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> Ordering
Ord, Int -> VkPerformanceCounterUnitKHR
VkPerformanceCounterUnitKHR -> Int
VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR]
VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR
VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR]
VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR
-> [VkPerformanceCounterUnitKHR]
(VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR)
-> (VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR)
-> (Int -> VkPerformanceCounterUnitKHR)
-> (VkPerformanceCounterUnitKHR -> Int)
-> (VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR])
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR])
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR])
-> (VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR
    -> [VkPerformanceCounterUnitKHR])
-> Enum VkPerformanceCounterUnitKHR
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR
-> [VkPerformanceCounterUnitKHR]
$cenumFromThenTo :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR
-> [VkPerformanceCounterUnitKHR]
enumFromTo :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR]
$cenumFromTo :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR]
enumFromThen :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR]
$cenumFromThen :: VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR]
enumFrom :: VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR]
$cenumFrom :: VkPerformanceCounterUnitKHR -> [VkPerformanceCounterUnitKHR]
fromEnum :: VkPerformanceCounterUnitKHR -> Int
$cfromEnum :: VkPerformanceCounterUnitKHR -> Int
toEnum :: Int -> VkPerformanceCounterUnitKHR
$ctoEnum :: Int -> VkPerformanceCounterUnitKHR
pred :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR
$cpred :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR
succ :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR
$csucc :: VkPerformanceCounterUnitKHR -> VkPerformanceCounterUnitKHR
Enum, Ptr VkPerformanceCounterUnitKHR -> IO VkPerformanceCounterUnitKHR
Ptr VkPerformanceCounterUnitKHR
-> Int -> IO VkPerformanceCounterUnitKHR
Ptr VkPerformanceCounterUnitKHR
-> Int -> VkPerformanceCounterUnitKHR -> IO ()
Ptr VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> IO ()
VkPerformanceCounterUnitKHR -> Int
(VkPerformanceCounterUnitKHR -> Int)
-> (VkPerformanceCounterUnitKHR -> Int)
-> (Ptr VkPerformanceCounterUnitKHR
    -> Int -> IO VkPerformanceCounterUnitKHR)
-> (Ptr VkPerformanceCounterUnitKHR
    -> Int -> VkPerformanceCounterUnitKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO VkPerformanceCounterUnitKHR)
-> (forall b. Ptr b -> Int -> VkPerformanceCounterUnitKHR -> IO ())
-> (Ptr VkPerformanceCounterUnitKHR
    -> IO VkPerformanceCounterUnitKHR)
-> (Ptr VkPerformanceCounterUnitKHR
    -> VkPerformanceCounterUnitKHR -> IO ())
-> Storable VkPerformanceCounterUnitKHR
forall b. Ptr b -> Int -> IO VkPerformanceCounterUnitKHR
forall b. Ptr b -> Int -> VkPerformanceCounterUnitKHR -> 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 VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> IO ()
$cpoke :: Ptr VkPerformanceCounterUnitKHR
-> VkPerformanceCounterUnitKHR -> IO ()
peek :: Ptr VkPerformanceCounterUnitKHR -> IO VkPerformanceCounterUnitKHR
$cpeek :: Ptr VkPerformanceCounterUnitKHR -> IO VkPerformanceCounterUnitKHR
pokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceCounterUnitKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceCounterUnitKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceCounterUnitKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceCounterUnitKHR
pokeElemOff :: Ptr VkPerformanceCounterUnitKHR
-> Int -> VkPerformanceCounterUnitKHR -> IO ()
$cpokeElemOff :: Ptr VkPerformanceCounterUnitKHR
-> Int -> VkPerformanceCounterUnitKHR -> IO ()
peekElemOff :: Ptr VkPerformanceCounterUnitKHR
-> Int -> IO VkPerformanceCounterUnitKHR
$cpeekElemOff :: Ptr VkPerformanceCounterUnitKHR
-> Int -> IO VkPerformanceCounterUnitKHR
alignment :: VkPerformanceCounterUnitKHR -> Int
$calignment :: VkPerformanceCounterUnitKHR -> Int
sizeOf :: VkPerformanceCounterUnitKHR -> Int
$csizeOf :: VkPerformanceCounterUnitKHR -> Int
Storable)

instance Show VkPerformanceCounterUnitKHR where
    showsPrec :: Int -> VkPerformanceCounterUnitKHR -> ShowS
showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_GENERIC_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_GENERIC_KHR"
    showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_PERCENTAGE_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_PERCENTAGE_KHR"
    showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_NANOSECONDS_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_NANOSECONDS_KHR"
    showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_BYTES_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_BYTES_KHR"
    showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_BYTES_PER_SECOND_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_BYTES_PER_SECOND_KHR"
    showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_KELVIN_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_KELVIN_KHR"
    showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_WATTS_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_WATTS_KHR"
    showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_VOLTS_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_VOLTS_KHR"
    showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_AMPS_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_AMPS_KHR"
    showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_HERTZ_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_HERTZ_KHR"
    showsPrec Int
_ VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_CYCLES_KHR
      = String -> ShowS
showString String
"VK_PERFORMANCE_COUNTER_UNIT_CYCLES_KHR"
    showsPrec Int
p (VkPerformanceCounterUnitKHR Int32
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkPerformanceCounterUnitKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkPerformanceCounterUnitKHR where
    readPrec :: ReadPrec VkPerformanceCounterUnitKHR
readPrec
      = ReadPrec VkPerformanceCounterUnitKHR
-> ReadPrec VkPerformanceCounterUnitKHR
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec VkPerformanceCounterUnitKHR)]
-> ReadPrec VkPerformanceCounterUnitKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_PERFORMANCE_COUNTER_UNIT_GENERIC_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_GENERIC_KHR),
              (String
"VK_PERFORMANCE_COUNTER_UNIT_PERCENTAGE_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_PERCENTAGE_KHR),
              (String
"VK_PERFORMANCE_COUNTER_UNIT_NANOSECONDS_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_NANOSECONDS_KHR),
              (String
"VK_PERFORMANCE_COUNTER_UNIT_BYTES_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_BYTES_KHR),
              (String
"VK_PERFORMANCE_COUNTER_UNIT_BYTES_PER_SECOND_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_BYTES_PER_SECOND_KHR),
              (String
"VK_PERFORMANCE_COUNTER_UNIT_KELVIN_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_KELVIN_KHR),
              (String
"VK_PERFORMANCE_COUNTER_UNIT_WATTS_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_WATTS_KHR),
              (String
"VK_PERFORMANCE_COUNTER_UNIT_VOLTS_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_VOLTS_KHR),
              (String
"VK_PERFORMANCE_COUNTER_UNIT_AMPS_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_AMPS_KHR),
              (String
"VK_PERFORMANCE_COUNTER_UNIT_HERTZ_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_HERTZ_KHR),
              (String
"VK_PERFORMANCE_COUNTER_UNIT_CYCLES_KHR",
               VkPerformanceCounterUnitKHR -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceCounterUnitKHR
VK_PERFORMANCE_COUNTER_UNIT_CYCLES_KHR)]
             ReadPrec VkPerformanceCounterUnitKHR
-> ReadPrec VkPerformanceCounterUnitKHR
-> ReadPrec VkPerformanceCounterUnitKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec VkPerformanceCounterUnitKHR
-> ReadPrec VkPerformanceCounterUnitKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkPerformanceCounterUnitKHR") ReadPrec ()
-> ReadPrec VkPerformanceCounterUnitKHR
-> ReadPrec VkPerformanceCounterUnitKHR
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (Int32 -> VkPerformanceCounterUnitKHR
VkPerformanceCounterUnitKHR (Int32 -> VkPerformanceCounterUnitKHR)
-> ReadPrec Int32 -> ReadPrec VkPerformanceCounterUnitKHR
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_PERFORMANCE_COUNTER_UNIT_GENERIC_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_GENERIC_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_GENERIC_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_GENERIC_KHR =
        VkPerformanceCounterUnitKHR 0

pattern VK_PERFORMANCE_COUNTER_UNIT_PERCENTAGE_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_PERCENTAGE_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_PERCENTAGE_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_PERCENTAGE_KHR =
        VkPerformanceCounterUnitKHR 1

pattern VK_PERFORMANCE_COUNTER_UNIT_NANOSECONDS_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_NANOSECONDS_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_NANOSECONDS_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_NANOSECONDS_KHR =
        VkPerformanceCounterUnitKHR 2

pattern VK_PERFORMANCE_COUNTER_UNIT_BYTES_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_BYTES_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_BYTES_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_BYTES_KHR =
        VkPerformanceCounterUnitKHR 3

pattern VK_PERFORMANCE_COUNTER_UNIT_BYTES_PER_SECOND_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_BYTES_PER_SECOND_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_BYTES_PER_SECOND_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_BYTES_PER_SECOND_KHR =
        VkPerformanceCounterUnitKHR 4

pattern VK_PERFORMANCE_COUNTER_UNIT_KELVIN_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_KELVIN_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_KELVIN_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_KELVIN_KHR =
        VkPerformanceCounterUnitKHR 5

pattern VK_PERFORMANCE_COUNTER_UNIT_WATTS_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_WATTS_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_WATTS_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_WATTS_KHR =
        VkPerformanceCounterUnitKHR 6

pattern VK_PERFORMANCE_COUNTER_UNIT_VOLTS_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_VOLTS_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_VOLTS_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_VOLTS_KHR =
        VkPerformanceCounterUnitKHR 7

pattern VK_PERFORMANCE_COUNTER_UNIT_AMPS_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_AMPS_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_AMPS_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_AMPS_KHR =
        VkPerformanceCounterUnitKHR 8

pattern VK_PERFORMANCE_COUNTER_UNIT_HERTZ_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_HERTZ_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_HERTZ_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_HERTZ_KHR =
        VkPerformanceCounterUnitKHR 9

pattern VK_PERFORMANCE_COUNTER_UNIT_CYCLES_KHR ::
        VkPerformanceCounterUnitKHR

pattern $bVK_PERFORMANCE_COUNTER_UNIT_CYCLES_KHR :: VkPerformanceCounterUnitKHR
$mVK_PERFORMANCE_COUNTER_UNIT_CYCLES_KHR :: forall {r}.
VkPerformanceCounterUnitKHR -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_COUNTER_UNIT_CYCLES_KHR =
        VkPerformanceCounterUnitKHR 10

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkPerformanceOverrideTypeINTEL VkPerformanceOverrideTypeINTEL registry at www.khronos.org>
newtype VkPerformanceOverrideTypeINTEL = VkPerformanceOverrideTypeINTEL Int32
                                         deriving (VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
(VkPerformanceOverrideTypeINTEL
 -> VkPerformanceOverrideTypeINTEL -> Bool)
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL -> Bool)
-> Eq VkPerformanceOverrideTypeINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
$c/= :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
== :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
$c== :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
Eq, Eq VkPerformanceOverrideTypeINTEL
Eq VkPerformanceOverrideTypeINTEL
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL -> Ordering)
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL -> Bool)
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL -> Bool)
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL -> Bool)
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL -> Bool)
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL)
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL)
-> Ord VkPerformanceOverrideTypeINTEL
VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Ordering
VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL
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 :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL
$cmin :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL
max :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL
$cmax :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL
>= :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
$c>= :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
> :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
$c> :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
<= :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
$c<= :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
< :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
$c< :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Bool
compare :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Ordering
$ccompare :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> Ordering
Ord, Int -> VkPerformanceOverrideTypeINTEL
VkPerformanceOverrideTypeINTEL -> Int
VkPerformanceOverrideTypeINTEL -> [VkPerformanceOverrideTypeINTEL]
VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL
VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> [VkPerformanceOverrideTypeINTEL]
VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> [VkPerformanceOverrideTypeINTEL]
(VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL)
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL)
-> (Int -> VkPerformanceOverrideTypeINTEL)
-> (VkPerformanceOverrideTypeINTEL -> Int)
-> (VkPerformanceOverrideTypeINTEL
    -> [VkPerformanceOverrideTypeINTEL])
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL
    -> [VkPerformanceOverrideTypeINTEL])
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL
    -> [VkPerformanceOverrideTypeINTEL])
-> (VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL
    -> [VkPerformanceOverrideTypeINTEL])
-> Enum VkPerformanceOverrideTypeINTEL
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> [VkPerformanceOverrideTypeINTEL]
$cenumFromThenTo :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> [VkPerformanceOverrideTypeINTEL]
enumFromTo :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> [VkPerformanceOverrideTypeINTEL]
$cenumFromTo :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> [VkPerformanceOverrideTypeINTEL]
enumFromThen :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> [VkPerformanceOverrideTypeINTEL]
$cenumFromThen :: VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL
-> [VkPerformanceOverrideTypeINTEL]
enumFrom :: VkPerformanceOverrideTypeINTEL -> [VkPerformanceOverrideTypeINTEL]
$cenumFrom :: VkPerformanceOverrideTypeINTEL -> [VkPerformanceOverrideTypeINTEL]
fromEnum :: VkPerformanceOverrideTypeINTEL -> Int
$cfromEnum :: VkPerformanceOverrideTypeINTEL -> Int
toEnum :: Int -> VkPerformanceOverrideTypeINTEL
$ctoEnum :: Int -> VkPerformanceOverrideTypeINTEL
pred :: VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL
$cpred :: VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL
succ :: VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL
$csucc :: VkPerformanceOverrideTypeINTEL -> VkPerformanceOverrideTypeINTEL
Enum, Ptr VkPerformanceOverrideTypeINTEL
-> IO VkPerformanceOverrideTypeINTEL
Ptr VkPerformanceOverrideTypeINTEL
-> Int -> IO VkPerformanceOverrideTypeINTEL
Ptr VkPerformanceOverrideTypeINTEL
-> Int -> VkPerformanceOverrideTypeINTEL -> IO ()
Ptr VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> IO ()
VkPerformanceOverrideTypeINTEL -> Int
(VkPerformanceOverrideTypeINTEL -> Int)
-> (VkPerformanceOverrideTypeINTEL -> Int)
-> (Ptr VkPerformanceOverrideTypeINTEL
    -> Int -> IO VkPerformanceOverrideTypeINTEL)
-> (Ptr VkPerformanceOverrideTypeINTEL
    -> Int -> VkPerformanceOverrideTypeINTEL -> IO ())
-> (forall b. Ptr b -> Int -> IO VkPerformanceOverrideTypeINTEL)
-> (forall b.
    Ptr b -> Int -> VkPerformanceOverrideTypeINTEL -> IO ())
-> (Ptr VkPerformanceOverrideTypeINTEL
    -> IO VkPerformanceOverrideTypeINTEL)
-> (Ptr VkPerformanceOverrideTypeINTEL
    -> VkPerformanceOverrideTypeINTEL -> IO ())
-> Storable VkPerformanceOverrideTypeINTEL
forall b. Ptr b -> Int -> IO VkPerformanceOverrideTypeINTEL
forall b. Ptr b -> Int -> VkPerformanceOverrideTypeINTEL -> 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 VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> IO ()
$cpoke :: Ptr VkPerformanceOverrideTypeINTEL
-> VkPerformanceOverrideTypeINTEL -> IO ()
peek :: Ptr VkPerformanceOverrideTypeINTEL
-> IO VkPerformanceOverrideTypeINTEL
$cpeek :: Ptr VkPerformanceOverrideTypeINTEL
-> IO VkPerformanceOverrideTypeINTEL
pokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceOverrideTypeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceOverrideTypeINTEL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceOverrideTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceOverrideTypeINTEL
pokeElemOff :: Ptr VkPerformanceOverrideTypeINTEL
-> Int -> VkPerformanceOverrideTypeINTEL -> IO ()
$cpokeElemOff :: Ptr VkPerformanceOverrideTypeINTEL
-> Int -> VkPerformanceOverrideTypeINTEL -> IO ()
peekElemOff :: Ptr VkPerformanceOverrideTypeINTEL
-> Int -> IO VkPerformanceOverrideTypeINTEL
$cpeekElemOff :: Ptr VkPerformanceOverrideTypeINTEL
-> Int -> IO VkPerformanceOverrideTypeINTEL
alignment :: VkPerformanceOverrideTypeINTEL -> Int
$calignment :: VkPerformanceOverrideTypeINTEL -> Int
sizeOf :: VkPerformanceOverrideTypeINTEL -> Int
$csizeOf :: VkPerformanceOverrideTypeINTEL -> Int
Storable)

instance Show VkPerformanceOverrideTypeINTEL where
    showsPrec :: Int -> VkPerformanceOverrideTypeINTEL -> ShowS
showsPrec Int
_ VkPerformanceOverrideTypeINTEL
VK_PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL
      = String -> ShowS
showString String
"VK_PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL"
    showsPrec Int
_ VkPerformanceOverrideTypeINTEL
VK_PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL
      = String -> ShowS
showString String
"VK_PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL"
    showsPrec Int
p (VkPerformanceOverrideTypeINTEL Int32
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkPerformanceOverrideTypeINTEL " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkPerformanceOverrideTypeINTEL where
    readPrec :: ReadPrec VkPerformanceOverrideTypeINTEL
readPrec
      = ReadPrec VkPerformanceOverrideTypeINTEL
-> ReadPrec VkPerformanceOverrideTypeINTEL
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec VkPerformanceOverrideTypeINTEL)]
-> ReadPrec VkPerformanceOverrideTypeINTEL
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL",
               VkPerformanceOverrideTypeINTEL
-> ReadPrec VkPerformanceOverrideTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceOverrideTypeINTEL
VK_PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL),
              (String
"VK_PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL",
               VkPerformanceOverrideTypeINTEL
-> ReadPrec VkPerformanceOverrideTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceOverrideTypeINTEL
VK_PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL)]
             ReadPrec VkPerformanceOverrideTypeINTEL
-> ReadPrec VkPerformanceOverrideTypeINTEL
-> ReadPrec VkPerformanceOverrideTypeINTEL
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec VkPerformanceOverrideTypeINTEL
-> ReadPrec VkPerformanceOverrideTypeINTEL
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkPerformanceOverrideTypeINTEL") ReadPrec ()
-> ReadPrec VkPerformanceOverrideTypeINTEL
-> ReadPrec VkPerformanceOverrideTypeINTEL
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (Int32 -> VkPerformanceOverrideTypeINTEL
VkPerformanceOverrideTypeINTEL (Int32 -> VkPerformanceOverrideTypeINTEL)
-> ReadPrec Int32 -> ReadPrec VkPerformanceOverrideTypeINTEL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL ::
        VkPerformanceOverrideTypeINTEL

pattern $bVK_PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL :: VkPerformanceOverrideTypeINTEL
$mVK_PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL :: forall {r}.
VkPerformanceOverrideTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL =
        VkPerformanceOverrideTypeINTEL 0

pattern VK_PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL ::
        VkPerformanceOverrideTypeINTEL

pattern $bVK_PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL :: VkPerformanceOverrideTypeINTEL
$mVK_PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL :: forall {r}.
VkPerformanceOverrideTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL =
        VkPerformanceOverrideTypeINTEL 1

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkPerformanceParameterTypeINTEL VkPerformanceParameterTypeINTEL registry at www.khronos.org>
newtype VkPerformanceParameterTypeINTEL = VkPerformanceParameterTypeINTEL Int32
                                          deriving (VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
(VkPerformanceParameterTypeINTEL
 -> VkPerformanceParameterTypeINTEL -> Bool)
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL -> Bool)
-> Eq VkPerformanceParameterTypeINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
$c/= :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
== :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
$c== :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
Eq, Eq VkPerformanceParameterTypeINTEL
Eq VkPerformanceParameterTypeINTEL
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL -> Ordering)
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL -> Bool)
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL -> Bool)
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL -> Bool)
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL -> Bool)
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL)
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL)
-> Ord VkPerformanceParameterTypeINTEL
VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Ordering
VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
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 :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
$cmin :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
max :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
$cmax :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
>= :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
$c>= :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
> :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
$c> :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
<= :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
$c<= :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
< :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
$c< :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Bool
compare :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Ordering
$ccompare :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> Ordering
Ord, Int -> VkPerformanceParameterTypeINTEL
VkPerformanceParameterTypeINTEL -> Int
VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
VkPerformanceParameterTypeINTEL -> VkPerformanceParameterTypeINTEL
VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
(VkPerformanceParameterTypeINTEL
 -> VkPerformanceParameterTypeINTEL)
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL)
-> (Int -> VkPerformanceParameterTypeINTEL)
-> (VkPerformanceParameterTypeINTEL -> Int)
-> (VkPerformanceParameterTypeINTEL
    -> [VkPerformanceParameterTypeINTEL])
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL
    -> [VkPerformanceParameterTypeINTEL])
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL
    -> [VkPerformanceParameterTypeINTEL])
-> (VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL
    -> [VkPerformanceParameterTypeINTEL])
-> Enum VkPerformanceParameterTypeINTEL
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
$cenumFromThenTo :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
enumFromTo :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
$cenumFromTo :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
enumFromThen :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
$cenumFromThen :: VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
enumFrom :: VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
$cenumFrom :: VkPerformanceParameterTypeINTEL
-> [VkPerformanceParameterTypeINTEL]
fromEnum :: VkPerformanceParameterTypeINTEL -> Int
$cfromEnum :: VkPerformanceParameterTypeINTEL -> Int
toEnum :: Int -> VkPerformanceParameterTypeINTEL
$ctoEnum :: Int -> VkPerformanceParameterTypeINTEL
pred :: VkPerformanceParameterTypeINTEL -> VkPerformanceParameterTypeINTEL
$cpred :: VkPerformanceParameterTypeINTEL -> VkPerformanceParameterTypeINTEL
succ :: VkPerformanceParameterTypeINTEL -> VkPerformanceParameterTypeINTEL
$csucc :: VkPerformanceParameterTypeINTEL -> VkPerformanceParameterTypeINTEL
Enum, Ptr VkPerformanceParameterTypeINTEL
-> IO VkPerformanceParameterTypeINTEL
Ptr VkPerformanceParameterTypeINTEL
-> Int -> IO VkPerformanceParameterTypeINTEL
Ptr VkPerformanceParameterTypeINTEL
-> Int -> VkPerformanceParameterTypeINTEL -> IO ()
Ptr VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> IO ()
VkPerformanceParameterTypeINTEL -> Int
(VkPerformanceParameterTypeINTEL -> Int)
-> (VkPerformanceParameterTypeINTEL -> Int)
-> (Ptr VkPerformanceParameterTypeINTEL
    -> Int -> IO VkPerformanceParameterTypeINTEL)
-> (Ptr VkPerformanceParameterTypeINTEL
    -> Int -> VkPerformanceParameterTypeINTEL -> IO ())
-> (forall b. Ptr b -> Int -> IO VkPerformanceParameterTypeINTEL)
-> (forall b.
    Ptr b -> Int -> VkPerformanceParameterTypeINTEL -> IO ())
-> (Ptr VkPerformanceParameterTypeINTEL
    -> IO VkPerformanceParameterTypeINTEL)
-> (Ptr VkPerformanceParameterTypeINTEL
    -> VkPerformanceParameterTypeINTEL -> IO ())
-> Storable VkPerformanceParameterTypeINTEL
forall b. Ptr b -> Int -> IO VkPerformanceParameterTypeINTEL
forall b. Ptr b -> Int -> VkPerformanceParameterTypeINTEL -> 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 VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> IO ()
$cpoke :: Ptr VkPerformanceParameterTypeINTEL
-> VkPerformanceParameterTypeINTEL -> IO ()
peek :: Ptr VkPerformanceParameterTypeINTEL
-> IO VkPerformanceParameterTypeINTEL
$cpeek :: Ptr VkPerformanceParameterTypeINTEL
-> IO VkPerformanceParameterTypeINTEL
pokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceParameterTypeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceParameterTypeINTEL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceParameterTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceParameterTypeINTEL
pokeElemOff :: Ptr VkPerformanceParameterTypeINTEL
-> Int -> VkPerformanceParameterTypeINTEL -> IO ()
$cpokeElemOff :: Ptr VkPerformanceParameterTypeINTEL
-> Int -> VkPerformanceParameterTypeINTEL -> IO ()
peekElemOff :: Ptr VkPerformanceParameterTypeINTEL
-> Int -> IO VkPerformanceParameterTypeINTEL
$cpeekElemOff :: Ptr VkPerformanceParameterTypeINTEL
-> Int -> IO VkPerformanceParameterTypeINTEL
alignment :: VkPerformanceParameterTypeINTEL -> Int
$calignment :: VkPerformanceParameterTypeINTEL -> Int
sizeOf :: VkPerformanceParameterTypeINTEL -> Int
$csizeOf :: VkPerformanceParameterTypeINTEL -> Int
Storable)

instance Show VkPerformanceParameterTypeINTEL where
    showsPrec :: Int -> VkPerformanceParameterTypeINTEL -> ShowS
showsPrec Int
_
      VkPerformanceParameterTypeINTEL
VK_PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL
      = String -> ShowS
showString
          String
"VK_PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL"
    showsPrec Int
_
      VkPerformanceParameterTypeINTEL
VK_PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL
      = String -> ShowS
showString
          String
"VK_PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL"
    showsPrec Int
p (VkPerformanceParameterTypeINTEL Int32
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkPerformanceParameterTypeINTEL " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkPerformanceParameterTypeINTEL where
    readPrec :: ReadPrec VkPerformanceParameterTypeINTEL
readPrec
      = ReadPrec VkPerformanceParameterTypeINTEL
-> ReadPrec VkPerformanceParameterTypeINTEL
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec VkPerformanceParameterTypeINTEL)]
-> ReadPrec VkPerformanceParameterTypeINTEL
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL",
               VkPerformanceParameterTypeINTEL
-> ReadPrec VkPerformanceParameterTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceParameterTypeINTEL
VK_PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL),
              (String
"VK_PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL",
               VkPerformanceParameterTypeINTEL
-> ReadPrec VkPerformanceParameterTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceParameterTypeINTEL
VK_PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL)]
             ReadPrec VkPerformanceParameterTypeINTEL
-> ReadPrec VkPerformanceParameterTypeINTEL
-> ReadPrec VkPerformanceParameterTypeINTEL
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec VkPerformanceParameterTypeINTEL
-> ReadPrec VkPerformanceParameterTypeINTEL
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkPerformanceParameterTypeINTEL") ReadPrec ()
-> ReadPrec VkPerformanceParameterTypeINTEL
-> ReadPrec VkPerformanceParameterTypeINTEL
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (Int32 -> VkPerformanceParameterTypeINTEL
VkPerformanceParameterTypeINTEL (Int32 -> VkPerformanceParameterTypeINTEL)
-> ReadPrec Int32 -> ReadPrec VkPerformanceParameterTypeINTEL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL
        :: VkPerformanceParameterTypeINTEL

pattern $bVK_PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL :: VkPerformanceParameterTypeINTEL
$mVK_PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL :: forall {r}.
VkPerformanceParameterTypeINTEL
-> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL =
        VkPerformanceParameterTypeINTEL 0

pattern VK_PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL
        :: VkPerformanceParameterTypeINTEL

pattern $bVK_PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL :: VkPerformanceParameterTypeINTEL
$mVK_PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL :: forall {r}.
VkPerformanceParameterTypeINTEL
-> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL
        = VkPerformanceParameterTypeINTEL 1

-- | type = @enum@
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkPerformanceValueTypeINTEL VkPerformanceValueTypeINTEL registry at www.khronos.org>
newtype VkPerformanceValueTypeINTEL = VkPerformanceValueTypeINTEL Int32
                                      deriving (VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
(VkPerformanceValueTypeINTEL
 -> VkPerformanceValueTypeINTEL -> Bool)
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> Bool)
-> Eq VkPerformanceValueTypeINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
$c/= :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
== :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
$c== :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
Eq, Eq VkPerformanceValueTypeINTEL
Eq VkPerformanceValueTypeINTEL
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> Ordering)
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> Bool)
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> Bool)
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> Bool)
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> Bool)
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL)
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL)
-> Ord VkPerformanceValueTypeINTEL
VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> Ordering
VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL
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 :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL
$cmin :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL
max :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL
$cmax :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL
>= :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
$c>= :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
> :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
$c> :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
<= :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
$c<= :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
< :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
$c< :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL -> Bool
compare :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> Ordering
$ccompare :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> Ordering
Ord, Int -> VkPerformanceValueTypeINTEL
VkPerformanceValueTypeINTEL -> Int
VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL]
VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL
VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL]
VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL
-> [VkPerformanceValueTypeINTEL]
(VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL)
-> (VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL)
-> (Int -> VkPerformanceValueTypeINTEL)
-> (VkPerformanceValueTypeINTEL -> Int)
-> (VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL])
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL])
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL])
-> (VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL
    -> [VkPerformanceValueTypeINTEL])
-> Enum VkPerformanceValueTypeINTEL
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL
-> [VkPerformanceValueTypeINTEL]
$cenumFromThenTo :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL
-> [VkPerformanceValueTypeINTEL]
enumFromTo :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL]
$cenumFromTo :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL]
enumFromThen :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL]
$cenumFromThen :: VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL]
enumFrom :: VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL]
$cenumFrom :: VkPerformanceValueTypeINTEL -> [VkPerformanceValueTypeINTEL]
fromEnum :: VkPerformanceValueTypeINTEL -> Int
$cfromEnum :: VkPerformanceValueTypeINTEL -> Int
toEnum :: Int -> VkPerformanceValueTypeINTEL
$ctoEnum :: Int -> VkPerformanceValueTypeINTEL
pred :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL
$cpred :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL
succ :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL
$csucc :: VkPerformanceValueTypeINTEL -> VkPerformanceValueTypeINTEL
Enum, Ptr VkPerformanceValueTypeINTEL -> IO VkPerformanceValueTypeINTEL
Ptr VkPerformanceValueTypeINTEL
-> Int -> IO VkPerformanceValueTypeINTEL
Ptr VkPerformanceValueTypeINTEL
-> Int -> VkPerformanceValueTypeINTEL -> IO ()
Ptr VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> IO ()
VkPerformanceValueTypeINTEL -> Int
(VkPerformanceValueTypeINTEL -> Int)
-> (VkPerformanceValueTypeINTEL -> Int)
-> (Ptr VkPerformanceValueTypeINTEL
    -> Int -> IO VkPerformanceValueTypeINTEL)
-> (Ptr VkPerformanceValueTypeINTEL
    -> Int -> VkPerformanceValueTypeINTEL -> IO ())
-> (forall b. Ptr b -> Int -> IO VkPerformanceValueTypeINTEL)
-> (forall b. Ptr b -> Int -> VkPerformanceValueTypeINTEL -> IO ())
-> (Ptr VkPerformanceValueTypeINTEL
    -> IO VkPerformanceValueTypeINTEL)
-> (Ptr VkPerformanceValueTypeINTEL
    -> VkPerformanceValueTypeINTEL -> IO ())
-> Storable VkPerformanceValueTypeINTEL
forall b. Ptr b -> Int -> IO VkPerformanceValueTypeINTEL
forall b. Ptr b -> Int -> VkPerformanceValueTypeINTEL -> 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 VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> IO ()
$cpoke :: Ptr VkPerformanceValueTypeINTEL
-> VkPerformanceValueTypeINTEL -> IO ()
peek :: Ptr VkPerformanceValueTypeINTEL -> IO VkPerformanceValueTypeINTEL
$cpeek :: Ptr VkPerformanceValueTypeINTEL -> IO VkPerformanceValueTypeINTEL
pokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceValueTypeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> VkPerformanceValueTypeINTEL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceValueTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO VkPerformanceValueTypeINTEL
pokeElemOff :: Ptr VkPerformanceValueTypeINTEL
-> Int -> VkPerformanceValueTypeINTEL -> IO ()
$cpokeElemOff :: Ptr VkPerformanceValueTypeINTEL
-> Int -> VkPerformanceValueTypeINTEL -> IO ()
peekElemOff :: Ptr VkPerformanceValueTypeINTEL
-> Int -> IO VkPerformanceValueTypeINTEL
$cpeekElemOff :: Ptr VkPerformanceValueTypeINTEL
-> Int -> IO VkPerformanceValueTypeINTEL
alignment :: VkPerformanceValueTypeINTEL -> Int
$calignment :: VkPerformanceValueTypeINTEL -> Int
sizeOf :: VkPerformanceValueTypeINTEL -> Int
$csizeOf :: VkPerformanceValueTypeINTEL -> Int
Storable)

instance Show VkPerformanceValueTypeINTEL where
    showsPrec :: Int -> VkPerformanceValueTypeINTEL -> ShowS
showsPrec Int
_ VkPerformanceValueTypeINTEL
VK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL
      = String -> ShowS
showString String
"VK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL"
    showsPrec Int
_ VkPerformanceValueTypeINTEL
VK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL
      = String -> ShowS
showString String
"VK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL"
    showsPrec Int
_ VkPerformanceValueTypeINTEL
VK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL
      = String -> ShowS
showString String
"VK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL"
    showsPrec Int
_ VkPerformanceValueTypeINTEL
VK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL
      = String -> ShowS
showString String
"VK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL"
    showsPrec Int
_ VkPerformanceValueTypeINTEL
VK_PERFORMANCE_VALUE_TYPE_STRING_INTEL
      = String -> ShowS
showString String
"VK_PERFORMANCE_VALUE_TYPE_STRING_INTEL"
    showsPrec Int
p (VkPerformanceValueTypeINTEL Int32
x)
      = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11)
          (String -> ShowS
showString String
"VkPerformanceValueTypeINTEL " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Int32
x)

instance Read VkPerformanceValueTypeINTEL where
    readPrec :: ReadPrec VkPerformanceValueTypeINTEL
readPrec
      = ReadPrec VkPerformanceValueTypeINTEL
-> ReadPrec VkPerformanceValueTypeINTEL
forall a. ReadPrec a -> ReadPrec a
parens
          ([(String, ReadPrec VkPerformanceValueTypeINTEL)]
-> ReadPrec VkPerformanceValueTypeINTEL
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose
             [(String
"VK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL",
               VkPerformanceValueTypeINTEL -> ReadPrec VkPerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceValueTypeINTEL
VK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL),
              (String
"VK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL",
               VkPerformanceValueTypeINTEL -> ReadPrec VkPerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceValueTypeINTEL
VK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL),
              (String
"VK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL",
               VkPerformanceValueTypeINTEL -> ReadPrec VkPerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceValueTypeINTEL
VK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL),
              (String
"VK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL",
               VkPerformanceValueTypeINTEL -> ReadPrec VkPerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceValueTypeINTEL
VK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL),
              (String
"VK_PERFORMANCE_VALUE_TYPE_STRING_INTEL",
               VkPerformanceValueTypeINTEL -> ReadPrec VkPerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure VkPerformanceValueTypeINTEL
VK_PERFORMANCE_VALUE_TYPE_STRING_INTEL)]
             ReadPrec VkPerformanceValueTypeINTEL
-> ReadPrec VkPerformanceValueTypeINTEL
-> ReadPrec VkPerformanceValueTypeINTEL
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
             Int
-> ReadPrec VkPerformanceValueTypeINTEL
-> ReadPrec VkPerformanceValueTypeINTEL
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10
               (Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident String
"VkPerformanceValueTypeINTEL") ReadPrec ()
-> ReadPrec VkPerformanceValueTypeINTEL
-> ReadPrec VkPerformanceValueTypeINTEL
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                  (Int32 -> VkPerformanceValueTypeINTEL
VkPerformanceValueTypeINTEL (Int32 -> VkPerformanceValueTypeINTEL)
-> ReadPrec Int32 -> ReadPrec VkPerformanceValueTypeINTEL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec)))

pattern VK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL ::
        VkPerformanceValueTypeINTEL

pattern $bVK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL :: VkPerformanceValueTypeINTEL
$mVK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL :: forall {r}.
VkPerformanceValueTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL =
        VkPerformanceValueTypeINTEL 0

pattern VK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL ::
        VkPerformanceValueTypeINTEL

pattern $bVK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL :: VkPerformanceValueTypeINTEL
$mVK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL :: forall {r}.
VkPerformanceValueTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL =
        VkPerformanceValueTypeINTEL 1

pattern VK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL ::
        VkPerformanceValueTypeINTEL

pattern $bVK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL :: VkPerformanceValueTypeINTEL
$mVK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL :: forall {r}.
VkPerformanceValueTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL =
        VkPerformanceValueTypeINTEL 2

pattern VK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL ::
        VkPerformanceValueTypeINTEL

pattern $bVK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL :: VkPerformanceValueTypeINTEL
$mVK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL :: forall {r}.
VkPerformanceValueTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL =
        VkPerformanceValueTypeINTEL 3

pattern VK_PERFORMANCE_VALUE_TYPE_STRING_INTEL ::
        VkPerformanceValueTypeINTEL

pattern $bVK_PERFORMANCE_VALUE_TYPE_STRING_INTEL :: VkPerformanceValueTypeINTEL
$mVK_PERFORMANCE_VALUE_TYPE_STRING_INTEL :: forall {r}.
VkPerformanceValueTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
VK_PERFORMANCE_VALUE_TYPE_STRING_INTEL =
        VkPerformanceValueTypeINTEL 4