{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TypeSynonymInstances #-}

module Data.SpirV.Enum.ExecutionMode where

import Data.Word (Word32)
import Foreign.Storable (Storable)

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

instance Show ExecutionMode where
  showsPrec :: Int -> ExecutionMode -> ShowS
showsPrec Int
p (ExecutionMode Word32
v) = case Word32
v of
    Word32
0 -> String -> ShowS
showString String
"Invocations"
    Word32
1 -> String -> ShowS
showString String
"SpacingEqual"
    Word32
2 -> String -> ShowS
showString String
"SpacingFractionalEven"
    Word32
3 -> String -> ShowS
showString String
"SpacingFractionalOdd"
    Word32
4 -> String -> ShowS
showString String
"VertexOrderCw"
    Word32
5 -> String -> ShowS
showString String
"VertexOrderCcw"
    Word32
6 -> String -> ShowS
showString String
"PixelCenterInteger"
    Word32
7 -> String -> ShowS
showString String
"OriginUpperLeft"
    Word32
8 -> String -> ShowS
showString String
"OriginLowerLeft"
    Word32
9 -> String -> ShowS
showString String
"EarlyFragmentTests"
    Word32
10 -> String -> ShowS
showString String
"PointMode"
    Word32
11 -> String -> ShowS
showString String
"Xfb"
    Word32
12 -> String -> ShowS
showString String
"DepthReplacing"
    Word32
14 -> String -> ShowS
showString String
"DepthGreater"
    Word32
15 -> String -> ShowS
showString String
"DepthLess"
    Word32
16 -> String -> ShowS
showString String
"DepthUnchanged"
    Word32
17 -> String -> ShowS
showString String
"LocalSize"
    Word32
18 -> String -> ShowS
showString String
"LocalSizeHint"
    Word32
19 -> String -> ShowS
showString String
"InputPoints"
    Word32
20 -> String -> ShowS
showString String
"InputLines"
    Word32
21 -> String -> ShowS
showString String
"InputLinesAdjacency"
    Word32
22 -> String -> ShowS
showString String
"Triangles"
    Word32
23 -> String -> ShowS
showString String
"InputTrianglesAdjacency"
    Word32
24 -> String -> ShowS
showString String
"Quads"
    Word32
25 -> String -> ShowS
showString String
"Isolines"
    Word32
26 -> String -> ShowS
showString String
"OutputVertices"
    Word32
27 -> String -> ShowS
showString String
"OutputPoints"
    Word32
28 -> String -> ShowS
showString String
"OutputLineStrip"
    Word32
29 -> String -> ShowS
showString String
"OutputTriangleStrip"
    Word32
30 -> String -> ShowS
showString String
"VecTypeHint"
    Word32
31 -> String -> ShowS
showString String
"ContractionOff"
    Word32
33 -> String -> ShowS
showString String
"Initializer"
    Word32
34 -> String -> ShowS
showString String
"Finalizer"
    Word32
35 -> String -> ShowS
showString String
"SubgroupSize"
    Word32
36 -> String -> ShowS
showString String
"SubgroupsPerWorkgroup"
    Word32
37 -> String -> ShowS
showString String
"SubgroupsPerWorkgroupId"
    Word32
38 -> String -> ShowS
showString String
"LocalSizeId"
    Word32
39 -> String -> ShowS
showString String
"LocalSizeHintId"
    Word32
4169 -> String -> ShowS
showString String
"NonCoherentColorAttachmentReadEXT"
    Word32
4170 -> String -> ShowS
showString String
"NonCoherentDepthAttachmentReadEXT"
    Word32
4171 -> String -> ShowS
showString String
"NonCoherentStencilAttachmentReadEXT"
    Word32
4421 -> String -> ShowS
showString String
"SubgroupUniformControlFlowKHR"
    Word32
4446 -> String -> ShowS
showString String
"PostDepthCoverage"
    Word32
4459 -> String -> ShowS
showString String
"DenormPreserve"
    Word32
4460 -> String -> ShowS
showString String
"DenormFlushToZero"
    Word32
4461 -> String -> ShowS
showString String
"SignedZeroInfNanPreserve"
    Word32
4462 -> String -> ShowS
showString String
"RoundingModeRTE"
    Word32
4463 -> String -> ShowS
showString String
"RoundingModeRTZ"
    Word32
5017 -> String -> ShowS
showString String
"EarlyAndLateFragmentTestsAMD"
    Word32
5027 -> String -> ShowS
showString String
"StencilRefReplacingEXT"
    Word32
5069 -> String -> ShowS
showString String
"CoalescingAMDX"
    Word32
5071 -> String -> ShowS
showString String
"MaxNodeRecursionAMDX"
    Word32
5072 -> String -> ShowS
showString String
"StaticNumWorkgroupsAMDX"
    Word32
5073 -> String -> ShowS
showString String
"ShaderIndexAMDX"
    Word32
5077 -> String -> ShowS
showString String
"MaxNumWorkgroupsAMDX"
    Word32
5079 -> String -> ShowS
showString String
"StencilRefUnchangedFrontAMD"
    Word32
5080 -> String -> ShowS
showString String
"StencilRefGreaterFrontAMD"
    Word32
5081 -> String -> ShowS
showString String
"StencilRefLessFrontAMD"
    Word32
5082 -> String -> ShowS
showString String
"StencilRefUnchangedBackAMD"
    Word32
5083 -> String -> ShowS
showString String
"StencilRefGreaterBackAMD"
    Word32
5084 -> String -> ShowS
showString String
"StencilRefLessBackAMD"
    Word32
5088 -> String -> ShowS
showString String
"QuadDerivativesKHR"
    Word32
5089 -> String -> ShowS
showString String
"RequireFullQuadsKHR"
    Word32
5269 -> String -> ShowS
showString String
"OutputLinesEXT"
    Word32
5270 -> String -> ShowS
showString String
"OutputPrimitivesEXT"
    Word32
5289 -> String -> ShowS
showString String
"DerivativeGroupQuadsNV"
    Word32
5290 -> String -> ShowS
showString String
"DerivativeGroupLinearNV"
    Word32
5298 -> String -> ShowS
showString String
"OutputTrianglesEXT"
    Word32
5366 -> String -> ShowS
showString String
"PixelInterlockOrderedEXT"
    Word32
5367 -> String -> ShowS
showString String
"PixelInterlockUnorderedEXT"
    Word32
5368 -> String -> ShowS
showString String
"SampleInterlockOrderedEXT"
    Word32
5369 -> String -> ShowS
showString String
"SampleInterlockUnorderedEXT"
    Word32
5370 -> String -> ShowS
showString String
"ShadingRateInterlockOrderedEXT"
    Word32
5371 -> String -> ShowS
showString String
"ShadingRateInterlockUnorderedEXT"
    Word32
5618 -> String -> ShowS
showString String
"SharedLocalMemorySizeINTEL"
    Word32
5620 -> String -> ShowS
showString String
"RoundingModeRTPINTEL"
    Word32
5621 -> String -> ShowS
showString String
"RoundingModeRTNINTEL"
    Word32
5622 -> String -> ShowS
showString String
"FloatingPointModeALTINTEL"
    Word32
5623 -> String -> ShowS
showString String
"FloatingPointModeIEEEINTEL"
    Word32
5893 -> String -> ShowS
showString String
"MaxWorkgroupSizeINTEL"
    Word32
5894 -> String -> ShowS
showString String
"MaxWorkDimINTEL"
    Word32
5895 -> String -> ShowS
showString String
"NoGlobalOffsetINTEL"
    Word32
5896 -> String -> ShowS
showString String
"NumSIMDWorkitemsINTEL"
    Word32
5903 -> String -> ShowS
showString String
"SchedulerTargetFmaxMhzINTEL"
    Word32
6023 -> String -> ShowS
showString String
"MaximallyReconvergesKHR"
    Word32
6028 -> String -> ShowS
showString String
"FPFastMathDefault"
    Word32
6154 -> String -> ShowS
showString String
"StreamingInterfaceINTEL"
    Word32
6160 -> String -> ShowS
showString String
"RegisterMapInterfaceINTEL"
    Word32
6417 -> String -> ShowS
showString String
"NamedBarrierCountINTEL"
    Word32
6461 -> String -> ShowS
showString String
"MaximumRegistersINTEL"
    Word32
6462 -> String -> ShowS
showString String
"MaximumRegistersIdINTEL"
    Word32
6463 -> String -> ShowS
showString String
"NamedMaximumRegistersINTEL"
    Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"ExecutionMode " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word32
x

pattern Invocations :: ExecutionMode
pattern $mInvocations :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bInvocations :: ExecutionMode
Invocations = ExecutionMode 0

pattern SpacingEqual :: ExecutionMode
pattern $mSpacingEqual :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSpacingEqual :: ExecutionMode
SpacingEqual = ExecutionMode 1

pattern SpacingFractionalEven :: ExecutionMode
pattern $mSpacingFractionalEven :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSpacingFractionalEven :: ExecutionMode
SpacingFractionalEven = ExecutionMode 2

pattern SpacingFractionalOdd :: ExecutionMode
pattern $mSpacingFractionalOdd :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSpacingFractionalOdd :: ExecutionMode
SpacingFractionalOdd = ExecutionMode 3

pattern VertexOrderCw :: ExecutionMode
pattern $mVertexOrderCw :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bVertexOrderCw :: ExecutionMode
VertexOrderCw = ExecutionMode 4

pattern VertexOrderCcw :: ExecutionMode
pattern $mVertexOrderCcw :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bVertexOrderCcw :: ExecutionMode
VertexOrderCcw = ExecutionMode 5

pattern PixelCenterInteger :: ExecutionMode
pattern $mPixelCenterInteger :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bPixelCenterInteger :: ExecutionMode
PixelCenterInteger = ExecutionMode 6

pattern OriginUpperLeft :: ExecutionMode
pattern $mOriginUpperLeft :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOriginUpperLeft :: ExecutionMode
OriginUpperLeft = ExecutionMode 7

pattern OriginLowerLeft :: ExecutionMode
pattern $mOriginLowerLeft :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOriginLowerLeft :: ExecutionMode
OriginLowerLeft = ExecutionMode 8

pattern EarlyFragmentTests :: ExecutionMode
pattern $mEarlyFragmentTests :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bEarlyFragmentTests :: ExecutionMode
EarlyFragmentTests = ExecutionMode 9

pattern PointMode :: ExecutionMode
pattern $mPointMode :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bPointMode :: ExecutionMode
PointMode = ExecutionMode 10

pattern Xfb :: ExecutionMode
pattern $mXfb :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bXfb :: ExecutionMode
Xfb = ExecutionMode 11

pattern DepthReplacing :: ExecutionMode
pattern $mDepthReplacing :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bDepthReplacing :: ExecutionMode
DepthReplacing = ExecutionMode 12

pattern DepthGreater :: ExecutionMode
pattern $mDepthGreater :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bDepthGreater :: ExecutionMode
DepthGreater = ExecutionMode 14

pattern DepthLess :: ExecutionMode
pattern $mDepthLess :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bDepthLess :: ExecutionMode
DepthLess = ExecutionMode 15

pattern DepthUnchanged :: ExecutionMode
pattern $mDepthUnchanged :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bDepthUnchanged :: ExecutionMode
DepthUnchanged = ExecutionMode 16

pattern LocalSize :: ExecutionMode
pattern $mLocalSize :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bLocalSize :: ExecutionMode
LocalSize = ExecutionMode 17

pattern LocalSizeHint :: ExecutionMode
pattern $mLocalSizeHint :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bLocalSizeHint :: ExecutionMode
LocalSizeHint = ExecutionMode 18

pattern InputPoints :: ExecutionMode
pattern $mInputPoints :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bInputPoints :: ExecutionMode
InputPoints = ExecutionMode 19

pattern InputLines :: ExecutionMode
pattern $mInputLines :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bInputLines :: ExecutionMode
InputLines = ExecutionMode 20

pattern InputLinesAdjacency :: ExecutionMode
pattern $mInputLinesAdjacency :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bInputLinesAdjacency :: ExecutionMode
InputLinesAdjacency = ExecutionMode 21

pattern Triangles :: ExecutionMode
pattern $mTriangles :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bTriangles :: ExecutionMode
Triangles = ExecutionMode 22

pattern InputTrianglesAdjacency :: ExecutionMode
pattern $mInputTrianglesAdjacency :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bInputTrianglesAdjacency :: ExecutionMode
InputTrianglesAdjacency = ExecutionMode 23

pattern Quads :: ExecutionMode
pattern $mQuads :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bQuads :: ExecutionMode
Quads = ExecutionMode 24

pattern Isolines :: ExecutionMode
pattern $mIsolines :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bIsolines :: ExecutionMode
Isolines = ExecutionMode 25

pattern OutputVertices :: ExecutionMode
pattern $mOutputVertices :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOutputVertices :: ExecutionMode
OutputVertices = ExecutionMode 26

pattern OutputPoints :: ExecutionMode
pattern $mOutputPoints :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOutputPoints :: ExecutionMode
OutputPoints = ExecutionMode 27

pattern OutputLineStrip :: ExecutionMode
pattern $mOutputLineStrip :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOutputLineStrip :: ExecutionMode
OutputLineStrip = ExecutionMode 28

pattern OutputTriangleStrip :: ExecutionMode
pattern $mOutputTriangleStrip :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOutputTriangleStrip :: ExecutionMode
OutputTriangleStrip = ExecutionMode 29

pattern VecTypeHint :: ExecutionMode
pattern $mVecTypeHint :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bVecTypeHint :: ExecutionMode
VecTypeHint = ExecutionMode 30

pattern ContractionOff :: ExecutionMode
pattern $mContractionOff :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bContractionOff :: ExecutionMode
ContractionOff = ExecutionMode 31

pattern Initializer :: ExecutionMode
pattern $mInitializer :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bInitializer :: ExecutionMode
Initializer = ExecutionMode 33

pattern Finalizer :: ExecutionMode
pattern $mFinalizer :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bFinalizer :: ExecutionMode
Finalizer = ExecutionMode 34

pattern SubgroupSize :: ExecutionMode
pattern $mSubgroupSize :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSubgroupSize :: ExecutionMode
SubgroupSize = ExecutionMode 35

pattern SubgroupsPerWorkgroup :: ExecutionMode
pattern $mSubgroupsPerWorkgroup :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSubgroupsPerWorkgroup :: ExecutionMode
SubgroupsPerWorkgroup = ExecutionMode 36

pattern SubgroupsPerWorkgroupId :: ExecutionMode
pattern $mSubgroupsPerWorkgroupId :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSubgroupsPerWorkgroupId :: ExecutionMode
SubgroupsPerWorkgroupId = ExecutionMode 37

pattern LocalSizeId :: ExecutionMode
pattern $mLocalSizeId :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bLocalSizeId :: ExecutionMode
LocalSizeId = ExecutionMode 38

pattern LocalSizeHintId :: ExecutionMode
pattern $mLocalSizeHintId :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bLocalSizeHintId :: ExecutionMode
LocalSizeHintId = ExecutionMode 39

pattern NonCoherentColorAttachmentReadEXT :: ExecutionMode
pattern $mNonCoherentColorAttachmentReadEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bNonCoherentColorAttachmentReadEXT :: ExecutionMode
NonCoherentColorAttachmentReadEXT = ExecutionMode 4169

pattern NonCoherentDepthAttachmentReadEXT :: ExecutionMode
pattern $mNonCoherentDepthAttachmentReadEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bNonCoherentDepthAttachmentReadEXT :: ExecutionMode
NonCoherentDepthAttachmentReadEXT = ExecutionMode 4170

pattern NonCoherentStencilAttachmentReadEXT :: ExecutionMode
pattern $mNonCoherentStencilAttachmentReadEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bNonCoherentStencilAttachmentReadEXT :: ExecutionMode
NonCoherentStencilAttachmentReadEXT = ExecutionMode 4171

pattern SubgroupUniformControlFlowKHR :: ExecutionMode
pattern $mSubgroupUniformControlFlowKHR :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSubgroupUniformControlFlowKHR :: ExecutionMode
SubgroupUniformControlFlowKHR = ExecutionMode 4421

pattern PostDepthCoverage :: ExecutionMode
pattern $mPostDepthCoverage :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bPostDepthCoverage :: ExecutionMode
PostDepthCoverage = ExecutionMode 4446

pattern DenormPreserve :: ExecutionMode
pattern $mDenormPreserve :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bDenormPreserve :: ExecutionMode
DenormPreserve = ExecutionMode 4459

pattern DenormFlushToZero :: ExecutionMode
pattern $mDenormFlushToZero :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bDenormFlushToZero :: ExecutionMode
DenormFlushToZero = ExecutionMode 4460

pattern SignedZeroInfNanPreserve :: ExecutionMode
pattern $mSignedZeroInfNanPreserve :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSignedZeroInfNanPreserve :: ExecutionMode
SignedZeroInfNanPreserve = ExecutionMode 4461

pattern RoundingModeRTE :: ExecutionMode
pattern $mRoundingModeRTE :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bRoundingModeRTE :: ExecutionMode
RoundingModeRTE = ExecutionMode 4462

pattern RoundingModeRTZ :: ExecutionMode
pattern $mRoundingModeRTZ :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bRoundingModeRTZ :: ExecutionMode
RoundingModeRTZ = ExecutionMode 4463

pattern EarlyAndLateFragmentTestsAMD :: ExecutionMode
pattern $mEarlyAndLateFragmentTestsAMD :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bEarlyAndLateFragmentTestsAMD :: ExecutionMode
EarlyAndLateFragmentTestsAMD = ExecutionMode 5017

pattern StencilRefReplacingEXT :: ExecutionMode
pattern $mStencilRefReplacingEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bStencilRefReplacingEXT :: ExecutionMode
StencilRefReplacingEXT = ExecutionMode 5027

pattern CoalescingAMDX :: ExecutionMode
pattern $mCoalescingAMDX :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bCoalescingAMDX :: ExecutionMode
CoalescingAMDX = ExecutionMode 5069

pattern MaxNodeRecursionAMDX :: ExecutionMode
pattern $mMaxNodeRecursionAMDX :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaxNodeRecursionAMDX :: ExecutionMode
MaxNodeRecursionAMDX = ExecutionMode 5071

pattern StaticNumWorkgroupsAMDX :: ExecutionMode
pattern $mStaticNumWorkgroupsAMDX :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bStaticNumWorkgroupsAMDX :: ExecutionMode
StaticNumWorkgroupsAMDX = ExecutionMode 5072

pattern ShaderIndexAMDX :: ExecutionMode
pattern $mShaderIndexAMDX :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bShaderIndexAMDX :: ExecutionMode
ShaderIndexAMDX = ExecutionMode 5073

pattern MaxNumWorkgroupsAMDX :: ExecutionMode
pattern $mMaxNumWorkgroupsAMDX :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaxNumWorkgroupsAMDX :: ExecutionMode
MaxNumWorkgroupsAMDX = ExecutionMode 5077

pattern StencilRefUnchangedFrontAMD :: ExecutionMode
pattern $mStencilRefUnchangedFrontAMD :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bStencilRefUnchangedFrontAMD :: ExecutionMode
StencilRefUnchangedFrontAMD = ExecutionMode 5079

pattern StencilRefGreaterFrontAMD :: ExecutionMode
pattern $mStencilRefGreaterFrontAMD :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bStencilRefGreaterFrontAMD :: ExecutionMode
StencilRefGreaterFrontAMD = ExecutionMode 5080

pattern StencilRefLessFrontAMD :: ExecutionMode
pattern $mStencilRefLessFrontAMD :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bStencilRefLessFrontAMD :: ExecutionMode
StencilRefLessFrontAMD = ExecutionMode 5081

pattern StencilRefUnchangedBackAMD :: ExecutionMode
pattern $mStencilRefUnchangedBackAMD :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bStencilRefUnchangedBackAMD :: ExecutionMode
StencilRefUnchangedBackAMD = ExecutionMode 5082

pattern StencilRefGreaterBackAMD :: ExecutionMode
pattern $mStencilRefGreaterBackAMD :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bStencilRefGreaterBackAMD :: ExecutionMode
StencilRefGreaterBackAMD = ExecutionMode 5083

pattern StencilRefLessBackAMD :: ExecutionMode
pattern $mStencilRefLessBackAMD :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bStencilRefLessBackAMD :: ExecutionMode
StencilRefLessBackAMD = ExecutionMode 5084

pattern QuadDerivativesKHR :: ExecutionMode
pattern $mQuadDerivativesKHR :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bQuadDerivativesKHR :: ExecutionMode
QuadDerivativesKHR = ExecutionMode 5088

pattern RequireFullQuadsKHR :: ExecutionMode
pattern $mRequireFullQuadsKHR :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bRequireFullQuadsKHR :: ExecutionMode
RequireFullQuadsKHR = ExecutionMode 5089

pattern OutputLinesEXT :: ExecutionMode
pattern $mOutputLinesEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOutputLinesEXT :: ExecutionMode
OutputLinesEXT = ExecutionMode 5269

pattern OutputLinesNV :: ExecutionMode
pattern $mOutputLinesNV :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOutputLinesNV :: ExecutionMode
OutputLinesNV = ExecutionMode 5269

pattern OutputPrimitivesEXT :: ExecutionMode
pattern $mOutputPrimitivesEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOutputPrimitivesEXT :: ExecutionMode
OutputPrimitivesEXT = ExecutionMode 5270

pattern OutputPrimitivesNV :: ExecutionMode
pattern $mOutputPrimitivesNV :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOutputPrimitivesNV :: ExecutionMode
OutputPrimitivesNV = ExecutionMode 5270

pattern DerivativeGroupQuadsNV :: ExecutionMode
pattern $mDerivativeGroupQuadsNV :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bDerivativeGroupQuadsNV :: ExecutionMode
DerivativeGroupQuadsNV = ExecutionMode 5289

pattern DerivativeGroupLinearNV :: ExecutionMode
pattern $mDerivativeGroupLinearNV :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bDerivativeGroupLinearNV :: ExecutionMode
DerivativeGroupLinearNV = ExecutionMode 5290

pattern OutputTrianglesEXT :: ExecutionMode
pattern $mOutputTrianglesEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOutputTrianglesEXT :: ExecutionMode
OutputTrianglesEXT = ExecutionMode 5298

pattern OutputTrianglesNV :: ExecutionMode
pattern $mOutputTrianglesNV :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bOutputTrianglesNV :: ExecutionMode
OutputTrianglesNV = ExecutionMode 5298

pattern PixelInterlockOrderedEXT :: ExecutionMode
pattern $mPixelInterlockOrderedEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bPixelInterlockOrderedEXT :: ExecutionMode
PixelInterlockOrderedEXT = ExecutionMode 5366

pattern PixelInterlockUnorderedEXT :: ExecutionMode
pattern $mPixelInterlockUnorderedEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bPixelInterlockUnorderedEXT :: ExecutionMode
PixelInterlockUnorderedEXT = ExecutionMode 5367

pattern SampleInterlockOrderedEXT :: ExecutionMode
pattern $mSampleInterlockOrderedEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSampleInterlockOrderedEXT :: ExecutionMode
SampleInterlockOrderedEXT = ExecutionMode 5368

pattern SampleInterlockUnorderedEXT :: ExecutionMode
pattern $mSampleInterlockUnorderedEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSampleInterlockUnorderedEXT :: ExecutionMode
SampleInterlockUnorderedEXT = ExecutionMode 5369

pattern ShadingRateInterlockOrderedEXT :: ExecutionMode
pattern $mShadingRateInterlockOrderedEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bShadingRateInterlockOrderedEXT :: ExecutionMode
ShadingRateInterlockOrderedEXT = ExecutionMode 5370

pattern ShadingRateInterlockUnorderedEXT :: ExecutionMode
pattern $mShadingRateInterlockUnorderedEXT :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bShadingRateInterlockUnorderedEXT :: ExecutionMode
ShadingRateInterlockUnorderedEXT = ExecutionMode 5371

pattern SharedLocalMemorySizeINTEL :: ExecutionMode
pattern $mSharedLocalMemorySizeINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSharedLocalMemorySizeINTEL :: ExecutionMode
SharedLocalMemorySizeINTEL = ExecutionMode 5618

pattern RoundingModeRTPINTEL :: ExecutionMode
pattern $mRoundingModeRTPINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bRoundingModeRTPINTEL :: ExecutionMode
RoundingModeRTPINTEL = ExecutionMode 5620

pattern RoundingModeRTNINTEL :: ExecutionMode
pattern $mRoundingModeRTNINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bRoundingModeRTNINTEL :: ExecutionMode
RoundingModeRTNINTEL = ExecutionMode 5621

pattern FloatingPointModeALTINTEL :: ExecutionMode
pattern $mFloatingPointModeALTINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bFloatingPointModeALTINTEL :: ExecutionMode
FloatingPointModeALTINTEL = ExecutionMode 5622

pattern FloatingPointModeIEEEINTEL :: ExecutionMode
pattern $mFloatingPointModeIEEEINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bFloatingPointModeIEEEINTEL :: ExecutionMode
FloatingPointModeIEEEINTEL = ExecutionMode 5623

pattern MaxWorkgroupSizeINTEL :: ExecutionMode
pattern $mMaxWorkgroupSizeINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaxWorkgroupSizeINTEL :: ExecutionMode
MaxWorkgroupSizeINTEL = ExecutionMode 5893

pattern MaxWorkDimINTEL :: ExecutionMode
pattern $mMaxWorkDimINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaxWorkDimINTEL :: ExecutionMode
MaxWorkDimINTEL = ExecutionMode 5894

pattern NoGlobalOffsetINTEL :: ExecutionMode
pattern $mNoGlobalOffsetINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bNoGlobalOffsetINTEL :: ExecutionMode
NoGlobalOffsetINTEL = ExecutionMode 5895

pattern NumSIMDWorkitemsINTEL :: ExecutionMode
pattern $mNumSIMDWorkitemsINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bNumSIMDWorkitemsINTEL :: ExecutionMode
NumSIMDWorkitemsINTEL = ExecutionMode 5896

pattern SchedulerTargetFmaxMhzINTEL :: ExecutionMode
pattern $mSchedulerTargetFmaxMhzINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bSchedulerTargetFmaxMhzINTEL :: ExecutionMode
SchedulerTargetFmaxMhzINTEL = ExecutionMode 5903

pattern MaximallyReconvergesKHR :: ExecutionMode
pattern $mMaximallyReconvergesKHR :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaximallyReconvergesKHR :: ExecutionMode
MaximallyReconvergesKHR = ExecutionMode 6023

pattern FPFastMathDefault :: ExecutionMode
pattern $mFPFastMathDefault :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bFPFastMathDefault :: ExecutionMode
FPFastMathDefault = ExecutionMode 6028

pattern StreamingInterfaceINTEL :: ExecutionMode
pattern $mStreamingInterfaceINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bStreamingInterfaceINTEL :: ExecutionMode
StreamingInterfaceINTEL = ExecutionMode 6154

pattern RegisterMapInterfaceINTEL :: ExecutionMode
pattern $mRegisterMapInterfaceINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bRegisterMapInterfaceINTEL :: ExecutionMode
RegisterMapInterfaceINTEL = ExecutionMode 6160

pattern NamedBarrierCountINTEL :: ExecutionMode
pattern $mNamedBarrierCountINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bNamedBarrierCountINTEL :: ExecutionMode
NamedBarrierCountINTEL = ExecutionMode 6417

pattern MaximumRegistersINTEL :: ExecutionMode
pattern $mMaximumRegistersINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaximumRegistersINTEL :: ExecutionMode
MaximumRegistersINTEL = ExecutionMode 6461

pattern MaximumRegistersIdINTEL :: ExecutionMode
pattern $mMaximumRegistersIdINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaximumRegistersIdINTEL :: ExecutionMode
MaximumRegistersIdINTEL = ExecutionMode 6462

pattern NamedMaximumRegistersINTEL :: ExecutionMode
pattern $mNamedMaximumRegistersINTEL :: forall {r}. ExecutionMode -> ((# #) -> r) -> ((# #) -> r) -> r
$bNamedMaximumRegistersINTEL :: ExecutionMode
NamedMaximumRegistersINTEL = ExecutionMode 6463