module Data.SpirV.Enum.Decoration where

import Data.String (IsString(..))
import Data.Word (Word32)
import Foreign (Storable(..))
import GHC.Read (Read(..))
import Text.ParserCombinators.ReadPrec (pfail)
import qualified GHC.Read as Read
import qualified Text.Read.Lex as Lex

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

pattern RelaxedPrecision :: Decoration
pattern $bRelaxedPrecision :: Decoration
$mRelaxedPrecision :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
RelaxedPrecision = Decoration 0

pattern SpecId :: Decoration
pattern $bSpecId :: Decoration
$mSpecId :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
SpecId = Decoration 1

pattern Block :: Decoration
pattern $bBlock :: Decoration
$mBlock :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Block = Decoration 2

pattern BufferBlock :: Decoration
pattern $bBufferBlock :: Decoration
$mBufferBlock :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
BufferBlock = Decoration 3

pattern RowMajor :: Decoration
pattern $bRowMajor :: Decoration
$mRowMajor :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
RowMajor = Decoration 4

pattern ColMajor :: Decoration
pattern $bColMajor :: Decoration
$mColMajor :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
ColMajor = Decoration 5

pattern ArrayStride :: Decoration
pattern $bArrayStride :: Decoration
$mArrayStride :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
ArrayStride = Decoration 6

pattern MatrixStride :: Decoration
pattern $bMatrixStride :: Decoration
$mMatrixStride :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
MatrixStride = Decoration 7

pattern GLSLShared :: Decoration
pattern $bGLSLShared :: Decoration
$mGLSLShared :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
GLSLShared = Decoration 8

pattern GLSLPacked :: Decoration
pattern $bGLSLPacked :: Decoration
$mGLSLPacked :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
GLSLPacked = Decoration 9

pattern CPacked :: Decoration
pattern $bCPacked :: Decoration
$mCPacked :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
CPacked = Decoration 10

pattern BuiltIn :: Decoration
pattern $bBuiltIn :: Decoration
$mBuiltIn :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
BuiltIn = Decoration 11

pattern NoPerspective :: Decoration
pattern $bNoPerspective :: Decoration
$mNoPerspective :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
NoPerspective = Decoration 13

pattern Flat :: Decoration
pattern $bFlat :: Decoration
$mFlat :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Flat = Decoration 14

pattern Patch :: Decoration
pattern $bPatch :: Decoration
$mPatch :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Patch = Decoration 15

pattern Centroid :: Decoration
pattern $bCentroid :: Decoration
$mCentroid :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Centroid = Decoration 16

pattern Sample :: Decoration
pattern $bSample :: Decoration
$mSample :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Sample = Decoration 17

pattern Invariant :: Decoration
pattern $bInvariant :: Decoration
$mInvariant :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Invariant = Decoration 18

pattern Restrict :: Decoration
pattern $bRestrict :: Decoration
$mRestrict :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Restrict = Decoration 19

pattern Aliased :: Decoration
pattern $bAliased :: Decoration
$mAliased :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Aliased = Decoration 20

pattern Volatile :: Decoration
pattern $bVolatile :: Decoration
$mVolatile :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Volatile = Decoration 21

pattern Constant :: Decoration
pattern $bConstant :: Decoration
$mConstant :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Constant = Decoration 22

pattern Coherent :: Decoration
pattern $bCoherent :: Decoration
$mCoherent :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Coherent = Decoration 23

pattern NonWritable :: Decoration
pattern $bNonWritable :: Decoration
$mNonWritable :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
NonWritable = Decoration 24

pattern NonReadable :: Decoration
pattern $bNonReadable :: Decoration
$mNonReadable :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
NonReadable = Decoration 25

pattern Uniform :: Decoration
pattern $bUniform :: Decoration
$mUniform :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Uniform = Decoration 26

pattern UniformId :: Decoration
pattern $bUniformId :: Decoration
$mUniformId :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
UniformId = Decoration 27

pattern SaturatedConversion :: Decoration
pattern $bSaturatedConversion :: Decoration
$mSaturatedConversion :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
SaturatedConversion = Decoration 28

pattern Stream :: Decoration
pattern $bStream :: Decoration
$mStream :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Stream = Decoration 29

pattern Location :: Decoration
pattern $bLocation :: Decoration
$mLocation :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Location = Decoration 30

pattern Component :: Decoration
pattern $bComponent :: Decoration
$mComponent :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Component = Decoration 31

pattern Index :: Decoration
pattern $bIndex :: Decoration
$mIndex :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Index = Decoration 32

pattern Binding :: Decoration
pattern $bBinding :: Decoration
$mBinding :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Binding = Decoration 33

pattern DescriptorSet :: Decoration
pattern $bDescriptorSet :: Decoration
$mDescriptorSet :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
DescriptorSet = Decoration 34

pattern Offset :: Decoration
pattern $bOffset :: Decoration
$mOffset :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Offset = Decoration 35

pattern XfbBuffer :: Decoration
pattern $bXfbBuffer :: Decoration
$mXfbBuffer :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
XfbBuffer = Decoration 36

pattern XfbStride :: Decoration
pattern $bXfbStride :: Decoration
$mXfbStride :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
XfbStride = Decoration 37

pattern FuncParamAttr :: Decoration
pattern $bFuncParamAttr :: Decoration
$mFuncParamAttr :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
FuncParamAttr = Decoration 38

pattern FPRoundingMode :: Decoration
pattern $bFPRoundingMode :: Decoration
$mFPRoundingMode :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
FPRoundingMode = Decoration 39

pattern FPFastMathMode :: Decoration
pattern $bFPFastMathMode :: Decoration
$mFPFastMathMode :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
FPFastMathMode = Decoration 40

pattern LinkageAttributes :: Decoration
pattern $bLinkageAttributes :: Decoration
$mLinkageAttributes :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
LinkageAttributes = Decoration 41

pattern NoContraction :: Decoration
pattern $bNoContraction :: Decoration
$mNoContraction :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
NoContraction = Decoration 42

pattern InputAttachmentIndex :: Decoration
pattern $bInputAttachmentIndex :: Decoration
$mInputAttachmentIndex :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
InputAttachmentIndex = Decoration 43

pattern Alignment :: Decoration
pattern $bAlignment :: Decoration
$mAlignment :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
Alignment = Decoration 44

pattern MaxByteOffset :: Decoration
pattern $bMaxByteOffset :: Decoration
$mMaxByteOffset :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
MaxByteOffset = Decoration 45

pattern AlignmentId :: Decoration
pattern $bAlignmentId :: Decoration
$mAlignmentId :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
AlignmentId = Decoration 46

pattern MaxByteOffsetId :: Decoration
pattern $bMaxByteOffsetId :: Decoration
$mMaxByteOffsetId :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
MaxByteOffsetId = Decoration 47

pattern NoSignedWrap :: Decoration
pattern $bNoSignedWrap :: Decoration
$mNoSignedWrap :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
NoSignedWrap = Decoration 4469

pattern NoUnsignedWrap :: Decoration
pattern $bNoUnsignedWrap :: Decoration
$mNoUnsignedWrap :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
NoUnsignedWrap = Decoration 4470

pattern ExplicitInterpAMD :: Decoration
pattern $bExplicitInterpAMD :: Decoration
$mExplicitInterpAMD :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
ExplicitInterpAMD = Decoration 4999

pattern OverrideCoverageNV :: Decoration
pattern $bOverrideCoverageNV :: Decoration
$mOverrideCoverageNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
OverrideCoverageNV = Decoration 5248

pattern PassthroughNV :: Decoration
pattern $bPassthroughNV :: Decoration
$mPassthroughNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
PassthroughNV = Decoration 5250

pattern ViewportRelativeNV :: Decoration
pattern $bViewportRelativeNV :: Decoration
$mViewportRelativeNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
ViewportRelativeNV = Decoration 5252

pattern SecondaryViewportRelativeNV :: Decoration
pattern $bSecondaryViewportRelativeNV :: Decoration
$mSecondaryViewportRelativeNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
SecondaryViewportRelativeNV = Decoration 5256

pattern PerPrimitiveEXT :: Decoration
pattern $bPerPrimitiveEXT :: Decoration
$mPerPrimitiveEXT :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
PerPrimitiveEXT = Decoration 5271

pattern PerPrimitiveNV :: Decoration
pattern $bPerPrimitiveNV :: Decoration
$mPerPrimitiveNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
PerPrimitiveNV = Decoration 5271

pattern PerViewNV :: Decoration
pattern $bPerViewNV :: Decoration
$mPerViewNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
PerViewNV = Decoration 5272

pattern PerTaskNV :: Decoration
pattern $bPerTaskNV :: Decoration
$mPerTaskNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
PerTaskNV = Decoration 5273

pattern PerVertexKHR :: Decoration
pattern $bPerVertexKHR :: Decoration
$mPerVertexKHR :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
PerVertexKHR = Decoration 5285

pattern PerVertexNV :: Decoration
pattern $bPerVertexNV :: Decoration
$mPerVertexNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
PerVertexNV = Decoration 5285

pattern NonUniform :: Decoration
pattern $bNonUniform :: Decoration
$mNonUniform :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
NonUniform = Decoration 5300

pattern NonUniformEXT :: Decoration
pattern $bNonUniformEXT :: Decoration
$mNonUniformEXT :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
NonUniformEXT = Decoration 5300

pattern RestrictPointer :: Decoration
pattern $bRestrictPointer :: Decoration
$mRestrictPointer :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
RestrictPointer = Decoration 5355

pattern RestrictPointerEXT :: Decoration
pattern $bRestrictPointerEXT :: Decoration
$mRestrictPointerEXT :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
RestrictPointerEXT = Decoration 5355

pattern AliasedPointer :: Decoration
pattern $bAliasedPointer :: Decoration
$mAliasedPointer :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
AliasedPointer = Decoration 5356

pattern AliasedPointerEXT :: Decoration
pattern $bAliasedPointerEXT :: Decoration
$mAliasedPointerEXT :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
AliasedPointerEXT = Decoration 5356

pattern HitObjectShaderRecordBufferNV :: Decoration
pattern $bHitObjectShaderRecordBufferNV :: Decoration
$mHitObjectShaderRecordBufferNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
HitObjectShaderRecordBufferNV = Decoration 5386

pattern BindlessSamplerNV :: Decoration
pattern $bBindlessSamplerNV :: Decoration
$mBindlessSamplerNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
BindlessSamplerNV = Decoration 5398

pattern BindlessImageNV :: Decoration
pattern $bBindlessImageNV :: Decoration
$mBindlessImageNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
BindlessImageNV = Decoration 5399

pattern BoundSamplerNV :: Decoration
pattern $bBoundSamplerNV :: Decoration
$mBoundSamplerNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
BoundSamplerNV = Decoration 5400

pattern BoundImageNV :: Decoration
pattern $bBoundImageNV :: Decoration
$mBoundImageNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
BoundImageNV = Decoration 5401

pattern SIMTCallINTEL :: Decoration
pattern $bSIMTCallINTEL :: Decoration
$mSIMTCallINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
SIMTCallINTEL = Decoration 5599

pattern ReferencedIndirectlyINTEL :: Decoration
pattern $bReferencedIndirectlyINTEL :: Decoration
$mReferencedIndirectlyINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
ReferencedIndirectlyINTEL = Decoration 5602

pattern ClobberINTEL :: Decoration
pattern $bClobberINTEL :: Decoration
$mClobberINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
ClobberINTEL = Decoration 5607

pattern SideEffectsINTEL :: Decoration
pattern $bSideEffectsINTEL :: Decoration
$mSideEffectsINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
SideEffectsINTEL = Decoration 5608

pattern VectorComputeVariableINTEL :: Decoration
pattern $bVectorComputeVariableINTEL :: Decoration
$mVectorComputeVariableINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
VectorComputeVariableINTEL = Decoration 5624

pattern FuncParamIOKindINTEL :: Decoration
pattern $bFuncParamIOKindINTEL :: Decoration
$mFuncParamIOKindINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
FuncParamIOKindINTEL = Decoration 5625

pattern VectorComputeFunctionINTEL :: Decoration
pattern $bVectorComputeFunctionINTEL :: Decoration
$mVectorComputeFunctionINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
VectorComputeFunctionINTEL = Decoration 5626

pattern StackCallINTEL :: Decoration
pattern $bStackCallINTEL :: Decoration
$mStackCallINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
StackCallINTEL = Decoration 5627

pattern GlobalVariableOffsetINTEL :: Decoration
pattern $bGlobalVariableOffsetINTEL :: Decoration
$mGlobalVariableOffsetINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
GlobalVariableOffsetINTEL = Decoration 5628

pattern CounterBuffer :: Decoration
pattern $bCounterBuffer :: Decoration
$mCounterBuffer :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
CounterBuffer = Decoration 5634

pattern HlslCounterBufferGOOGLE :: Decoration
pattern $bHlslCounterBufferGOOGLE :: Decoration
$mHlslCounterBufferGOOGLE :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
HlslCounterBufferGOOGLE = Decoration 5634

pattern HlslSemanticGOOGLE :: Decoration
pattern $bHlslSemanticGOOGLE :: Decoration
$mHlslSemanticGOOGLE :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
HlslSemanticGOOGLE = Decoration 5635

pattern UserSemantic :: Decoration
pattern $bUserSemantic :: Decoration
$mUserSemantic :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
UserSemantic = Decoration 5635

pattern UserTypeGOOGLE :: Decoration
pattern $bUserTypeGOOGLE :: Decoration
$mUserTypeGOOGLE :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
UserTypeGOOGLE = Decoration 5636

pattern FunctionRoundingModeINTEL :: Decoration
pattern $bFunctionRoundingModeINTEL :: Decoration
$mFunctionRoundingModeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
FunctionRoundingModeINTEL = Decoration 5822

pattern FunctionDenormModeINTEL :: Decoration
pattern $bFunctionDenormModeINTEL :: Decoration
$mFunctionDenormModeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
FunctionDenormModeINTEL = Decoration 5823

pattern RegisterINTEL :: Decoration
pattern $bRegisterINTEL :: Decoration
$mRegisterINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
RegisterINTEL = Decoration 5825

pattern MemoryINTEL :: Decoration
pattern $bMemoryINTEL :: Decoration
$mMemoryINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
MemoryINTEL = Decoration 5826

pattern NumbanksINTEL :: Decoration
pattern $bNumbanksINTEL :: Decoration
$mNumbanksINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
NumbanksINTEL = Decoration 5827

pattern BankwidthINTEL :: Decoration
pattern $bBankwidthINTEL :: Decoration
$mBankwidthINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
BankwidthINTEL = Decoration 5828

pattern MaxPrivateCopiesINTEL :: Decoration
pattern $bMaxPrivateCopiesINTEL :: Decoration
$mMaxPrivateCopiesINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
MaxPrivateCopiesINTEL = Decoration 5829

pattern SinglepumpINTEL :: Decoration
pattern $bSinglepumpINTEL :: Decoration
$mSinglepumpINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
SinglepumpINTEL = Decoration 5830

pattern DoublepumpINTEL :: Decoration
pattern $bDoublepumpINTEL :: Decoration
$mDoublepumpINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
DoublepumpINTEL = Decoration 5831

pattern MaxReplicatesINTEL :: Decoration
pattern $bMaxReplicatesINTEL :: Decoration
$mMaxReplicatesINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
MaxReplicatesINTEL = Decoration 5832

pattern SimpleDualPortINTEL :: Decoration
pattern $bSimpleDualPortINTEL :: Decoration
$mSimpleDualPortINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
SimpleDualPortINTEL = Decoration 5833

pattern MergeINTEL :: Decoration
pattern $bMergeINTEL :: Decoration
$mMergeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
MergeINTEL = Decoration 5834

pattern BankBitsINTEL :: Decoration
pattern $bBankBitsINTEL :: Decoration
$mBankBitsINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
BankBitsINTEL = Decoration 5835

pattern ForcePow2DepthINTEL :: Decoration
pattern $bForcePow2DepthINTEL :: Decoration
$mForcePow2DepthINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
ForcePow2DepthINTEL = Decoration 5836

pattern BurstCoalesceINTEL :: Decoration
pattern $bBurstCoalesceINTEL :: Decoration
$mBurstCoalesceINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
BurstCoalesceINTEL = Decoration 5899

pattern CacheSizeINTEL :: Decoration
pattern $bCacheSizeINTEL :: Decoration
$mCacheSizeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
CacheSizeINTEL = Decoration 5900

pattern DontStaticallyCoalesceINTEL :: Decoration
pattern $bDontStaticallyCoalesceINTEL :: Decoration
$mDontStaticallyCoalesceINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
DontStaticallyCoalesceINTEL = Decoration 5901

pattern PrefetchINTEL :: Decoration
pattern $bPrefetchINTEL :: Decoration
$mPrefetchINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
PrefetchINTEL = Decoration 5902

pattern StallEnableINTEL :: Decoration
pattern $bStallEnableINTEL :: Decoration
$mStallEnableINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
StallEnableINTEL = Decoration 5905

pattern FuseLoopsInFunctionINTEL :: Decoration
pattern $bFuseLoopsInFunctionINTEL :: Decoration
$mFuseLoopsInFunctionINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
FuseLoopsInFunctionINTEL = Decoration 5907

pattern MathOpDSPModeINTEL :: Decoration
pattern $bMathOpDSPModeINTEL :: Decoration
$mMathOpDSPModeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
MathOpDSPModeINTEL = Decoration 5909

pattern AliasScopeINTEL :: Decoration
pattern $bAliasScopeINTEL :: Decoration
$mAliasScopeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
AliasScopeINTEL = Decoration 5914

pattern NoAliasINTEL :: Decoration
pattern $bNoAliasINTEL :: Decoration
$mNoAliasINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
NoAliasINTEL = Decoration 5915

pattern InitiationIntervalINTEL :: Decoration
pattern $bInitiationIntervalINTEL :: Decoration
$mInitiationIntervalINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
InitiationIntervalINTEL = Decoration 5917

pattern MaxConcurrencyINTEL :: Decoration
pattern $bMaxConcurrencyINTEL :: Decoration
$mMaxConcurrencyINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
MaxConcurrencyINTEL = Decoration 5918

pattern PipelineEnableINTEL :: Decoration
pattern $bPipelineEnableINTEL :: Decoration
$mPipelineEnableINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
PipelineEnableINTEL = Decoration 5919

pattern BufferLocationINTEL :: Decoration
pattern $bBufferLocationINTEL :: Decoration
$mBufferLocationINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
BufferLocationINTEL = Decoration 5921

pattern IOPipeStorageINTEL :: Decoration
pattern $bIOPipeStorageINTEL :: Decoration
$mIOPipeStorageINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
IOPipeStorageINTEL = Decoration 5944

pattern FunctionFloatingPointModeINTEL :: Decoration
pattern $bFunctionFloatingPointModeINTEL :: Decoration
$mFunctionFloatingPointModeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
FunctionFloatingPointModeINTEL = Decoration 6080

pattern SingleElementVectorINTEL :: Decoration
pattern $bSingleElementVectorINTEL :: Decoration
$mSingleElementVectorINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
SingleElementVectorINTEL = Decoration 6085

pattern VectorComputeCallableFunctionINTEL :: Decoration
pattern $bVectorComputeCallableFunctionINTEL :: Decoration
$mVectorComputeCallableFunctionINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
VectorComputeCallableFunctionINTEL = Decoration 6087

pattern MediaBlockIOINTEL :: Decoration
pattern $bMediaBlockIOINTEL :: Decoration
$mMediaBlockIOINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
MediaBlockIOINTEL = Decoration 6140

toName :: IsString a => Decoration -> a
toName :: forall a. IsString a => Decoration -> a
toName Decoration
x = case Decoration
x of
  Decoration
RelaxedPrecision -> a
"RelaxedPrecision"
  Decoration
SpecId -> a
"SpecId"
  Decoration
Block -> a
"Block"
  Decoration
BufferBlock -> a
"BufferBlock"
  Decoration
RowMajor -> a
"RowMajor"
  Decoration
ColMajor -> a
"ColMajor"
  Decoration
ArrayStride -> a
"ArrayStride"
  Decoration
MatrixStride -> a
"MatrixStride"
  Decoration
GLSLShared -> a
"GLSLShared"
  Decoration
GLSLPacked -> a
"GLSLPacked"
  Decoration
CPacked -> a
"CPacked"
  Decoration
BuiltIn -> a
"BuiltIn"
  Decoration
NoPerspective -> a
"NoPerspective"
  Decoration
Flat -> a
"Flat"
  Decoration
Patch -> a
"Patch"
  Decoration
Centroid -> a
"Centroid"
  Decoration
Sample -> a
"Sample"
  Decoration
Invariant -> a
"Invariant"
  Decoration
Restrict -> a
"Restrict"
  Decoration
Aliased -> a
"Aliased"
  Decoration
Volatile -> a
"Volatile"
  Decoration
Constant -> a
"Constant"
  Decoration
Coherent -> a
"Coherent"
  Decoration
NonWritable -> a
"NonWritable"
  Decoration
NonReadable -> a
"NonReadable"
  Decoration
Uniform -> a
"Uniform"
  Decoration
UniformId -> a
"UniformId"
  Decoration
SaturatedConversion -> a
"SaturatedConversion"
  Decoration
Stream -> a
"Stream"
  Decoration
Location -> a
"Location"
  Decoration
Component -> a
"Component"
  Decoration
Index -> a
"Index"
  Decoration
Binding -> a
"Binding"
  Decoration
DescriptorSet -> a
"DescriptorSet"
  Decoration
Offset -> a
"Offset"
  Decoration
XfbBuffer -> a
"XfbBuffer"
  Decoration
XfbStride -> a
"XfbStride"
  Decoration
FuncParamAttr -> a
"FuncParamAttr"
  Decoration
FPRoundingMode -> a
"FPRoundingMode"
  Decoration
FPFastMathMode -> a
"FPFastMathMode"
  Decoration
LinkageAttributes -> a
"LinkageAttributes"
  Decoration
NoContraction -> a
"NoContraction"
  Decoration
InputAttachmentIndex -> a
"InputAttachmentIndex"
  Decoration
Alignment -> a
"Alignment"
  Decoration
MaxByteOffset -> a
"MaxByteOffset"
  Decoration
AlignmentId -> a
"AlignmentId"
  Decoration
MaxByteOffsetId -> a
"MaxByteOffsetId"
  Decoration
NoSignedWrap -> a
"NoSignedWrap"
  Decoration
NoUnsignedWrap -> a
"NoUnsignedWrap"
  Decoration
ExplicitInterpAMD -> a
"ExplicitInterpAMD"
  Decoration
OverrideCoverageNV -> a
"OverrideCoverageNV"
  Decoration
PassthroughNV -> a
"PassthroughNV"
  Decoration
ViewportRelativeNV -> a
"ViewportRelativeNV"
  Decoration
SecondaryViewportRelativeNV -> a
"SecondaryViewportRelativeNV"
  Decoration
PerPrimitiveEXT -> a
"PerPrimitiveEXT"
  Decoration
PerPrimitiveNV -> a
"PerPrimitiveNV"
  Decoration
PerViewNV -> a
"PerViewNV"
  Decoration
PerTaskNV -> a
"PerTaskNV"
  Decoration
PerVertexKHR -> a
"PerVertexKHR"
  Decoration
PerVertexNV -> a
"PerVertexNV"
  Decoration
NonUniform -> a
"NonUniform"
  Decoration
NonUniformEXT -> a
"NonUniformEXT"
  Decoration
RestrictPointer -> a
"RestrictPointer"
  Decoration
RestrictPointerEXT -> a
"RestrictPointerEXT"
  Decoration
AliasedPointer -> a
"AliasedPointer"
  Decoration
AliasedPointerEXT -> a
"AliasedPointerEXT"
  Decoration
HitObjectShaderRecordBufferNV -> a
"HitObjectShaderRecordBufferNV"
  Decoration
BindlessSamplerNV -> a
"BindlessSamplerNV"
  Decoration
BindlessImageNV -> a
"BindlessImageNV"
  Decoration
BoundSamplerNV -> a
"BoundSamplerNV"
  Decoration
BoundImageNV -> a
"BoundImageNV"
  Decoration
SIMTCallINTEL -> a
"SIMTCallINTEL"
  Decoration
ReferencedIndirectlyINTEL -> a
"ReferencedIndirectlyINTEL"
  Decoration
ClobberINTEL -> a
"ClobberINTEL"
  Decoration
SideEffectsINTEL -> a
"SideEffectsINTEL"
  Decoration
VectorComputeVariableINTEL -> a
"VectorComputeVariableINTEL"
  Decoration
FuncParamIOKindINTEL -> a
"FuncParamIOKindINTEL"
  Decoration
VectorComputeFunctionINTEL -> a
"VectorComputeFunctionINTEL"
  Decoration
StackCallINTEL -> a
"StackCallINTEL"
  Decoration
GlobalVariableOffsetINTEL -> a
"GlobalVariableOffsetINTEL"
  Decoration
CounterBuffer -> a
"CounterBuffer"
  Decoration
HlslCounterBufferGOOGLE -> a
"HlslCounterBufferGOOGLE"
  Decoration
HlslSemanticGOOGLE -> a
"HlslSemanticGOOGLE"
  Decoration
UserSemantic -> a
"UserSemantic"
  Decoration
UserTypeGOOGLE -> a
"UserTypeGOOGLE"
  Decoration
FunctionRoundingModeINTEL -> a
"FunctionRoundingModeINTEL"
  Decoration
FunctionDenormModeINTEL -> a
"FunctionDenormModeINTEL"
  Decoration
RegisterINTEL -> a
"RegisterINTEL"
  Decoration
MemoryINTEL -> a
"MemoryINTEL"
  Decoration
NumbanksINTEL -> a
"NumbanksINTEL"
  Decoration
BankwidthINTEL -> a
"BankwidthINTEL"
  Decoration
MaxPrivateCopiesINTEL -> a
"MaxPrivateCopiesINTEL"
  Decoration
SinglepumpINTEL -> a
"SinglepumpINTEL"
  Decoration
DoublepumpINTEL -> a
"DoublepumpINTEL"
  Decoration
MaxReplicatesINTEL -> a
"MaxReplicatesINTEL"
  Decoration
SimpleDualPortINTEL -> a
"SimpleDualPortINTEL"
  Decoration
MergeINTEL -> a
"MergeINTEL"
  Decoration
BankBitsINTEL -> a
"BankBitsINTEL"
  Decoration
ForcePow2DepthINTEL -> a
"ForcePow2DepthINTEL"
  Decoration
BurstCoalesceINTEL -> a
"BurstCoalesceINTEL"
  Decoration
CacheSizeINTEL -> a
"CacheSizeINTEL"
  Decoration
DontStaticallyCoalesceINTEL -> a
"DontStaticallyCoalesceINTEL"
  Decoration
PrefetchINTEL -> a
"PrefetchINTEL"
  Decoration
StallEnableINTEL -> a
"StallEnableINTEL"
  Decoration
FuseLoopsInFunctionINTEL -> a
"FuseLoopsInFunctionINTEL"
  Decoration
MathOpDSPModeINTEL -> a
"MathOpDSPModeINTEL"
  Decoration
AliasScopeINTEL -> a
"AliasScopeINTEL"
  Decoration
NoAliasINTEL -> a
"NoAliasINTEL"
  Decoration
InitiationIntervalINTEL -> a
"InitiationIntervalINTEL"
  Decoration
MaxConcurrencyINTEL -> a
"MaxConcurrencyINTEL"
  Decoration
PipelineEnableINTEL -> a
"PipelineEnableINTEL"
  Decoration
BufferLocationINTEL -> a
"BufferLocationINTEL"
  Decoration
IOPipeStorageINTEL -> a
"IOPipeStorageINTEL"
  Decoration
FunctionFloatingPointModeINTEL -> a
"FunctionFloatingPointModeINTEL"
  Decoration
SingleElementVectorINTEL -> a
"SingleElementVectorINTEL"
  Decoration
VectorComputeCallableFunctionINTEL -> a
"VectorComputeCallableFunctionINTEL"
  Decoration
MediaBlockIOINTEL -> a
"MediaBlockIOINTEL"
  Decoration
unknown -> forall a. IsString a => [Char] -> a
fromString forall a b. (a -> b) -> a -> b
$ [Char]
"Decoration " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Decoration
unknown

instance Show Decoration where
  show :: Decoration -> [Char]
show = forall a. IsString a => Decoration -> a
toName

fromName :: (IsString a, Eq a) => a -> Maybe Decoration
fromName :: forall a. (IsString a, Eq a) => a -> Maybe Decoration
fromName a
x = case a
x of
  a
"RelaxedPrecision" -> forall a. a -> Maybe a
Just Decoration
RelaxedPrecision
  a
"SpecId" -> forall a. a -> Maybe a
Just Decoration
SpecId
  a
"Block" -> forall a. a -> Maybe a
Just Decoration
Block
  a
"BufferBlock" -> forall a. a -> Maybe a
Just Decoration
BufferBlock
  a
"RowMajor" -> forall a. a -> Maybe a
Just Decoration
RowMajor
  a
"ColMajor" -> forall a. a -> Maybe a
Just Decoration
ColMajor
  a
"ArrayStride" -> forall a. a -> Maybe a
Just Decoration
ArrayStride
  a
"MatrixStride" -> forall a. a -> Maybe a
Just Decoration
MatrixStride
  a
"GLSLShared" -> forall a. a -> Maybe a
Just Decoration
GLSLShared
  a
"GLSLPacked" -> forall a. a -> Maybe a
Just Decoration
GLSLPacked
  a
"CPacked" -> forall a. a -> Maybe a
Just Decoration
CPacked
  a
"BuiltIn" -> forall a. a -> Maybe a
Just Decoration
BuiltIn
  a
"NoPerspective" -> forall a. a -> Maybe a
Just Decoration
NoPerspective
  a
"Flat" -> forall a. a -> Maybe a
Just Decoration
Flat
  a
"Patch" -> forall a. a -> Maybe a
Just Decoration
Patch
  a
"Centroid" -> forall a. a -> Maybe a
Just Decoration
Centroid
  a
"Sample" -> forall a. a -> Maybe a
Just Decoration
Sample
  a
"Invariant" -> forall a. a -> Maybe a
Just Decoration
Invariant
  a
"Restrict" -> forall a. a -> Maybe a
Just Decoration
Restrict
  a
"Aliased" -> forall a. a -> Maybe a
Just Decoration
Aliased
  a
"Volatile" -> forall a. a -> Maybe a
Just Decoration
Volatile
  a
"Constant" -> forall a. a -> Maybe a
Just Decoration
Constant
  a
"Coherent" -> forall a. a -> Maybe a
Just Decoration
Coherent
  a
"NonWritable" -> forall a. a -> Maybe a
Just Decoration
NonWritable
  a
"NonReadable" -> forall a. a -> Maybe a
Just Decoration
NonReadable
  a
"Uniform" -> forall a. a -> Maybe a
Just Decoration
Uniform
  a
"UniformId" -> forall a. a -> Maybe a
Just Decoration
UniformId
  a
"SaturatedConversion" -> forall a. a -> Maybe a
Just Decoration
SaturatedConversion
  a
"Stream" -> forall a. a -> Maybe a
Just Decoration
Stream
  a
"Location" -> forall a. a -> Maybe a
Just Decoration
Location
  a
"Component" -> forall a. a -> Maybe a
Just Decoration
Component
  a
"Index" -> forall a. a -> Maybe a
Just Decoration
Index
  a
"Binding" -> forall a. a -> Maybe a
Just Decoration
Binding
  a
"DescriptorSet" -> forall a. a -> Maybe a
Just Decoration
DescriptorSet
  a
"Offset" -> forall a. a -> Maybe a
Just Decoration
Offset
  a
"XfbBuffer" -> forall a. a -> Maybe a
Just Decoration
XfbBuffer
  a
"XfbStride" -> forall a. a -> Maybe a
Just Decoration
XfbStride
  a
"FuncParamAttr" -> forall a. a -> Maybe a
Just Decoration
FuncParamAttr
  a
"FPRoundingMode" -> forall a. a -> Maybe a
Just Decoration
FPRoundingMode
  a
"FPFastMathMode" -> forall a. a -> Maybe a
Just Decoration
FPFastMathMode
  a
"LinkageAttributes" -> forall a. a -> Maybe a
Just Decoration
LinkageAttributes
  a
"NoContraction" -> forall a. a -> Maybe a
Just Decoration
NoContraction
  a
"InputAttachmentIndex" -> forall a. a -> Maybe a
Just Decoration
InputAttachmentIndex
  a
"Alignment" -> forall a. a -> Maybe a
Just Decoration
Alignment
  a
"MaxByteOffset" -> forall a. a -> Maybe a
Just Decoration
MaxByteOffset
  a
"AlignmentId" -> forall a. a -> Maybe a
Just Decoration
AlignmentId
  a
"MaxByteOffsetId" -> forall a. a -> Maybe a
Just Decoration
MaxByteOffsetId
  a
"NoSignedWrap" -> forall a. a -> Maybe a
Just Decoration
NoSignedWrap
  a
"NoUnsignedWrap" -> forall a. a -> Maybe a
Just Decoration
NoUnsignedWrap
  a
"ExplicitInterpAMD" -> forall a. a -> Maybe a
Just Decoration
ExplicitInterpAMD
  a
"OverrideCoverageNV" -> forall a. a -> Maybe a
Just Decoration
OverrideCoverageNV
  a
"PassthroughNV" -> forall a. a -> Maybe a
Just Decoration
PassthroughNV
  a
"ViewportRelativeNV" -> forall a. a -> Maybe a
Just Decoration
ViewportRelativeNV
  a
"SecondaryViewportRelativeNV" -> forall a. a -> Maybe a
Just Decoration
SecondaryViewportRelativeNV
  a
"PerPrimitiveEXT" -> forall a. a -> Maybe a
Just Decoration
PerPrimitiveEXT
  a
"PerPrimitiveNV" -> forall a. a -> Maybe a
Just Decoration
PerPrimitiveNV
  a
"PerViewNV" -> forall a. a -> Maybe a
Just Decoration
PerViewNV
  a
"PerTaskNV" -> forall a. a -> Maybe a
Just Decoration
PerTaskNV
  a
"PerVertexKHR" -> forall a. a -> Maybe a
Just Decoration
PerVertexKHR
  a
"PerVertexNV" -> forall a. a -> Maybe a
Just Decoration
PerVertexNV
  a
"NonUniform" -> forall a. a -> Maybe a
Just Decoration
NonUniform
  a
"NonUniformEXT" -> forall a. a -> Maybe a
Just Decoration
NonUniformEXT
  a
"RestrictPointer" -> forall a. a -> Maybe a
Just Decoration
RestrictPointer
  a
"RestrictPointerEXT" -> forall a. a -> Maybe a
Just Decoration
RestrictPointerEXT
  a
"AliasedPointer" -> forall a. a -> Maybe a
Just Decoration
AliasedPointer
  a
"AliasedPointerEXT" -> forall a. a -> Maybe a
Just Decoration
AliasedPointerEXT
  a
"HitObjectShaderRecordBufferNV" -> forall a. a -> Maybe a
Just Decoration
HitObjectShaderRecordBufferNV
  a
"BindlessSamplerNV" -> forall a. a -> Maybe a
Just Decoration
BindlessSamplerNV
  a
"BindlessImageNV" -> forall a. a -> Maybe a
Just Decoration
BindlessImageNV
  a
"BoundSamplerNV" -> forall a. a -> Maybe a
Just Decoration
BoundSamplerNV
  a
"BoundImageNV" -> forall a. a -> Maybe a
Just Decoration
BoundImageNV
  a
"SIMTCallINTEL" -> forall a. a -> Maybe a
Just Decoration
SIMTCallINTEL
  a
"ReferencedIndirectlyINTEL" -> forall a. a -> Maybe a
Just Decoration
ReferencedIndirectlyINTEL
  a
"ClobberINTEL" -> forall a. a -> Maybe a
Just Decoration
ClobberINTEL
  a
"SideEffectsINTEL" -> forall a. a -> Maybe a
Just Decoration
SideEffectsINTEL
  a
"VectorComputeVariableINTEL" -> forall a. a -> Maybe a
Just Decoration
VectorComputeVariableINTEL
  a
"FuncParamIOKindINTEL" -> forall a. a -> Maybe a
Just Decoration
FuncParamIOKindINTEL
  a
"VectorComputeFunctionINTEL" -> forall a. a -> Maybe a
Just Decoration
VectorComputeFunctionINTEL
  a
"StackCallINTEL" -> forall a. a -> Maybe a
Just Decoration
StackCallINTEL
  a
"GlobalVariableOffsetINTEL" -> forall a. a -> Maybe a
Just Decoration
GlobalVariableOffsetINTEL
  a
"CounterBuffer" -> forall a. a -> Maybe a
Just Decoration
CounterBuffer
  a
"HlslCounterBufferGOOGLE" -> forall a. a -> Maybe a
Just Decoration
HlslCounterBufferGOOGLE
  a
"HlslSemanticGOOGLE" -> forall a. a -> Maybe a
Just Decoration
HlslSemanticGOOGLE
  a
"UserSemantic" -> forall a. a -> Maybe a
Just Decoration
UserSemantic
  a
"UserTypeGOOGLE" -> forall a. a -> Maybe a
Just Decoration
UserTypeGOOGLE
  a
"FunctionRoundingModeINTEL" -> forall a. a -> Maybe a
Just Decoration
FunctionRoundingModeINTEL
  a
"FunctionDenormModeINTEL" -> forall a. a -> Maybe a
Just Decoration
FunctionDenormModeINTEL
  a
"RegisterINTEL" -> forall a. a -> Maybe a
Just Decoration
RegisterINTEL
  a
"MemoryINTEL" -> forall a. a -> Maybe a
Just Decoration
MemoryINTEL
  a
"NumbanksINTEL" -> forall a. a -> Maybe a
Just Decoration
NumbanksINTEL
  a
"BankwidthINTEL" -> forall a. a -> Maybe a
Just Decoration
BankwidthINTEL
  a
"MaxPrivateCopiesINTEL" -> forall a. a -> Maybe a
Just Decoration
MaxPrivateCopiesINTEL
  a
"SinglepumpINTEL" -> forall a. a -> Maybe a
Just Decoration
SinglepumpINTEL
  a
"DoublepumpINTEL" -> forall a. a -> Maybe a
Just Decoration
DoublepumpINTEL
  a
"MaxReplicatesINTEL" -> forall a. a -> Maybe a
Just Decoration
MaxReplicatesINTEL
  a
"SimpleDualPortINTEL" -> forall a. a -> Maybe a
Just Decoration
SimpleDualPortINTEL
  a
"MergeINTEL" -> forall a. a -> Maybe a
Just Decoration
MergeINTEL
  a
"BankBitsINTEL" -> forall a. a -> Maybe a
Just Decoration
BankBitsINTEL
  a
"ForcePow2DepthINTEL" -> forall a. a -> Maybe a
Just Decoration
ForcePow2DepthINTEL
  a
"BurstCoalesceINTEL" -> forall a. a -> Maybe a
Just Decoration
BurstCoalesceINTEL
  a
"CacheSizeINTEL" -> forall a. a -> Maybe a
Just Decoration
CacheSizeINTEL
  a
"DontStaticallyCoalesceINTEL" -> forall a. a -> Maybe a
Just Decoration
DontStaticallyCoalesceINTEL
  a
"PrefetchINTEL" -> forall a. a -> Maybe a
Just Decoration
PrefetchINTEL
  a
"StallEnableINTEL" -> forall a. a -> Maybe a
Just Decoration
StallEnableINTEL
  a
"FuseLoopsInFunctionINTEL" -> forall a. a -> Maybe a
Just Decoration
FuseLoopsInFunctionINTEL
  a
"MathOpDSPModeINTEL" -> forall a. a -> Maybe a
Just Decoration
MathOpDSPModeINTEL
  a
"AliasScopeINTEL" -> forall a. a -> Maybe a
Just Decoration
AliasScopeINTEL
  a
"NoAliasINTEL" -> forall a. a -> Maybe a
Just Decoration
NoAliasINTEL
  a
"InitiationIntervalINTEL" -> forall a. a -> Maybe a
Just Decoration
InitiationIntervalINTEL
  a
"MaxConcurrencyINTEL" -> forall a. a -> Maybe a
Just Decoration
MaxConcurrencyINTEL
  a
"PipelineEnableINTEL" -> forall a. a -> Maybe a
Just Decoration
PipelineEnableINTEL
  a
"BufferLocationINTEL" -> forall a. a -> Maybe a
Just Decoration
BufferLocationINTEL
  a
"IOPipeStorageINTEL" -> forall a. a -> Maybe a
Just Decoration
IOPipeStorageINTEL
  a
"FunctionFloatingPointModeINTEL" -> forall a. a -> Maybe a
Just Decoration
FunctionFloatingPointModeINTEL
  a
"SingleElementVectorINTEL" -> forall a. a -> Maybe a
Just Decoration
SingleElementVectorINTEL
  a
"VectorComputeCallableFunctionINTEL" -> forall a. a -> Maybe a
Just Decoration
VectorComputeCallableFunctionINTEL
  a
"MediaBlockIOINTEL" -> forall a. a -> Maybe a
Just Decoration
MediaBlockIOINTEL
  a
_unknown -> forall a. Maybe a
Nothing

instance Read Decoration where
  readPrec :: ReadPrec Decoration
readPrec = forall a. ReadPrec a -> ReadPrec a
Read.parens do
    Lex.Ident [Char]
s <- ReadPrec Lexeme
Read.lexP
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. ReadPrec a
pfail forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. (IsString a, Eq a) => a -> Maybe Decoration
fromName [Char]
s