{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Data.SpirV.Enum.Decoration where
import Data.Word (Word32)
import Foreign.Storable (Storable)
newtype Decoration = Decoration Word32
deriving newtype (Decoration -> Decoration -> Bool
(Decoration -> Decoration -> Bool)
-> (Decoration -> Decoration -> Bool) -> Eq Decoration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Decoration -> Decoration -> Bool
== :: Decoration -> Decoration -> Bool
$c/= :: Decoration -> Decoration -> Bool
/= :: Decoration -> Decoration -> Bool
Eq, Eq Decoration
Eq Decoration =>
(Decoration -> Decoration -> Ordering)
-> (Decoration -> Decoration -> Bool)
-> (Decoration -> Decoration -> Bool)
-> (Decoration -> Decoration -> Bool)
-> (Decoration -> Decoration -> Bool)
-> (Decoration -> Decoration -> Decoration)
-> (Decoration -> Decoration -> Decoration)
-> Ord 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
$ccompare :: Decoration -> Decoration -> Ordering
compare :: Decoration -> Decoration -> Ordering
$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
>= :: Decoration -> Decoration -> Bool
$cmax :: Decoration -> Decoration -> Decoration
max :: Decoration -> Decoration -> Decoration
$cmin :: Decoration -> Decoration -> Decoration
min :: Decoration -> Decoration -> Decoration
Ord, Ptr Decoration -> IO Decoration
Ptr Decoration -> Int -> IO Decoration
Ptr Decoration -> Int -> Decoration -> IO ()
Ptr Decoration -> Decoration -> IO ()
Decoration -> Int
(Decoration -> Int)
-> (Decoration -> Int)
-> (Ptr Decoration -> Int -> IO Decoration)
-> (Ptr Decoration -> Int -> Decoration -> IO ())
-> (forall b. Ptr b -> Int -> IO Decoration)
-> (forall b. Ptr b -> Int -> Decoration -> IO ())
-> (Ptr Decoration -> IO Decoration)
-> (Ptr Decoration -> Decoration -> IO ())
-> Storable Decoration
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
$csizeOf :: Decoration -> Int
sizeOf :: Decoration -> Int
$calignment :: Decoration -> Int
alignment :: Decoration -> Int
$cpeekElemOff :: Ptr Decoration -> Int -> IO Decoration
peekElemOff :: Ptr Decoration -> Int -> IO Decoration
$cpokeElemOff :: Ptr Decoration -> Int -> Decoration -> IO ()
pokeElemOff :: Ptr Decoration -> Int -> Decoration -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Decoration
peekByteOff :: forall b. Ptr b -> Int -> IO Decoration
$cpokeByteOff :: forall b. Ptr b -> Int -> Decoration -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> Decoration -> IO ()
$cpeek :: Ptr Decoration -> IO Decoration
peek :: Ptr Decoration -> IO Decoration
$cpoke :: Ptr Decoration -> Decoration -> IO ()
poke :: Ptr Decoration -> Decoration -> IO ()
Storable)
instance Show Decoration where
showsPrec :: Int -> Decoration -> ShowS
showsPrec Int
p (Decoration Word32
v) = case Word32
v of
Word32
0 -> String -> ShowS
showString String
"RelaxedPrecision"
Word32
1 -> String -> ShowS
showString String
"SpecId"
Word32
2 -> String -> ShowS
showString String
"Block"
Word32
3 -> String -> ShowS
showString String
"BufferBlock"
Word32
4 -> String -> ShowS
showString String
"RowMajor"
Word32
5 -> String -> ShowS
showString String
"ColMajor"
Word32
6 -> String -> ShowS
showString String
"ArrayStride"
Word32
7 -> String -> ShowS
showString String
"MatrixStride"
Word32
8 -> String -> ShowS
showString String
"GLSLShared"
Word32
9 -> String -> ShowS
showString String
"GLSLPacked"
Word32
10 -> String -> ShowS
showString String
"CPacked"
Word32
11 -> String -> ShowS
showString String
"BuiltIn"
Word32
13 -> String -> ShowS
showString String
"NoPerspective"
Word32
14 -> String -> ShowS
showString String
"Flat"
Word32
15 -> String -> ShowS
showString String
"Patch"
Word32
16 -> String -> ShowS
showString String
"Centroid"
Word32
17 -> String -> ShowS
showString String
"Sample"
Word32
18 -> String -> ShowS
showString String
"Invariant"
Word32
19 -> String -> ShowS
showString String
"Restrict"
Word32
20 -> String -> ShowS
showString String
"Aliased"
Word32
21 -> String -> ShowS
showString String
"Volatile"
Word32
22 -> String -> ShowS
showString String
"Constant"
Word32
23 -> String -> ShowS
showString String
"Coherent"
Word32
24 -> String -> ShowS
showString String
"NonWritable"
Word32
25 -> String -> ShowS
showString String
"NonReadable"
Word32
26 -> String -> ShowS
showString String
"Uniform"
Word32
27 -> String -> ShowS
showString String
"UniformId"
Word32
28 -> String -> ShowS
showString String
"SaturatedConversion"
Word32
29 -> String -> ShowS
showString String
"Stream"
Word32
30 -> String -> ShowS
showString String
"Location"
Word32
31 -> String -> ShowS
showString String
"Component"
Word32
32 -> String -> ShowS
showString String
"Index"
Word32
33 -> String -> ShowS
showString String
"Binding"
Word32
34 -> String -> ShowS
showString String
"DescriptorSet"
Word32
35 -> String -> ShowS
showString String
"Offset"
Word32
36 -> String -> ShowS
showString String
"XfbBuffer"
Word32
37 -> String -> ShowS
showString String
"XfbStride"
Word32
38 -> String -> ShowS
showString String
"FuncParamAttr"
Word32
39 -> String -> ShowS
showString String
"FPRoundingMode"
Word32
40 -> String -> ShowS
showString String
"FPFastMathMode"
Word32
41 -> String -> ShowS
showString String
"LinkageAttributes"
Word32
42 -> String -> ShowS
showString String
"NoContraction"
Word32
43 -> String -> ShowS
showString String
"InputAttachmentIndex"
Word32
44 -> String -> ShowS
showString String
"Alignment"
Word32
45 -> String -> ShowS
showString String
"MaxByteOffset"
Word32
46 -> String -> ShowS
showString String
"AlignmentId"
Word32
47 -> String -> ShowS
showString String
"MaxByteOffsetId"
Word32
4469 -> String -> ShowS
showString String
"NoSignedWrap"
Word32
4470 -> String -> ShowS
showString String
"NoUnsignedWrap"
Word32
4487 -> String -> ShowS
showString String
"WeightTextureQCOM"
Word32
4488 -> String -> ShowS
showString String
"BlockMatchTextureQCOM"
Word32
4499 -> String -> ShowS
showString String
"BlockMatchSamplerQCOM"
Word32
4999 -> String -> ShowS
showString String
"ExplicitInterpAMD"
Word32
5019 -> String -> ShowS
showString String
"NodeSharesPayloadLimitsWithAMDX"
Word32
5020 -> String -> ShowS
showString String
"NodeMaxPayloadsAMDX"
Word32
5078 -> String -> ShowS
showString String
"TrackFinishWritingAMDX"
Word32
5091 -> String -> ShowS
showString String
"PayloadNodeNameAMDX"
Word32
5248 -> String -> ShowS
showString String
"OverrideCoverageNV"
Word32
5250 -> String -> ShowS
showString String
"PassthroughNV"
Word32
5252 -> String -> ShowS
showString String
"ViewportRelativeNV"
Word32
5256 -> String -> ShowS
showString String
"SecondaryViewportRelativeNV"
Word32
5271 -> String -> ShowS
showString String
"PerPrimitiveEXT"
Word32
5272 -> String -> ShowS
showString String
"PerViewNV"
Word32
5273 -> String -> ShowS
showString String
"PerTaskNV"
Word32
5285 -> String -> ShowS
showString String
"PerVertexKHR"
Word32
5300 -> String -> ShowS
showString String
"NonUniform"
Word32
5355 -> String -> ShowS
showString String
"RestrictPointer"
Word32
5356 -> String -> ShowS
showString String
"AliasedPointer"
Word32
5386 -> String -> ShowS
showString String
"HitObjectShaderRecordBufferNV"
Word32
5398 -> String -> ShowS
showString String
"BindlessSamplerNV"
Word32
5399 -> String -> ShowS
showString String
"BindlessImageNV"
Word32
5400 -> String -> ShowS
showString String
"BoundSamplerNV"
Word32
5401 -> String -> ShowS
showString String
"BoundImageNV"
Word32
5599 -> String -> ShowS
showString String
"SIMTCallINTEL"
Word32
5602 -> String -> ShowS
showString String
"ReferencedIndirectlyINTEL"
Word32
5607 -> String -> ShowS
showString String
"ClobberINTEL"
Word32
5608 -> String -> ShowS
showString String
"SideEffectsINTEL"
Word32
5624 -> String -> ShowS
showString String
"VectorComputeVariableINTEL"
Word32
5625 -> String -> ShowS
showString String
"FuncParamIOKindINTEL"
Word32
5626 -> String -> ShowS
showString String
"VectorComputeFunctionINTEL"
Word32
5627 -> String -> ShowS
showString String
"StackCallINTEL"
Word32
5628 -> String -> ShowS
showString String
"GlobalVariableOffsetINTEL"
Word32
5634 -> String -> ShowS
showString String
"CounterBuffer"
Word32
5635 -> String -> ShowS
showString String
"HlslSemanticGOOGLE"
Word32
5636 -> String -> ShowS
showString String
"UserTypeGOOGLE"
Word32
5822 -> String -> ShowS
showString String
"FunctionRoundingModeINTEL"
Word32
5823 -> String -> ShowS
showString String
"FunctionDenormModeINTEL"
Word32
5825 -> String -> ShowS
showString String
"RegisterINTEL"
Word32
5826 -> String -> ShowS
showString String
"MemoryINTEL"
Word32
5827 -> String -> ShowS
showString String
"NumbanksINTEL"
Word32
5828 -> String -> ShowS
showString String
"BankwidthINTEL"
Word32
5829 -> String -> ShowS
showString String
"MaxPrivateCopiesINTEL"
Word32
5830 -> String -> ShowS
showString String
"SinglepumpINTEL"
Word32
5831 -> String -> ShowS
showString String
"DoublepumpINTEL"
Word32
5832 -> String -> ShowS
showString String
"MaxReplicatesINTEL"
Word32
5833 -> String -> ShowS
showString String
"SimpleDualPortINTEL"
Word32
5834 -> String -> ShowS
showString String
"MergeINTEL"
Word32
5835 -> String -> ShowS
showString String
"BankBitsINTEL"
Word32
5836 -> String -> ShowS
showString String
"ForcePow2DepthINTEL"
Word32
5883 -> String -> ShowS
showString String
"StridesizeINTEL"
Word32
5884 -> String -> ShowS
showString String
"WordsizeINTEL"
Word32
5885 -> String -> ShowS
showString String
"TrueDualPortINTEL"
Word32
5899 -> String -> ShowS
showString String
"BurstCoalesceINTEL"
Word32
5900 -> String -> ShowS
showString String
"CacheSizeINTEL"
Word32
5901 -> String -> ShowS
showString String
"DontStaticallyCoalesceINTEL"
Word32
5902 -> String -> ShowS
showString String
"PrefetchINTEL"
Word32
5905 -> String -> ShowS
showString String
"StallEnableINTEL"
Word32
5907 -> String -> ShowS
showString String
"FuseLoopsInFunctionINTEL"
Word32
5909 -> String -> ShowS
showString String
"MathOpDSPModeINTEL"
Word32
5914 -> String -> ShowS
showString String
"AliasScopeINTEL"
Word32
5915 -> String -> ShowS
showString String
"NoAliasINTEL"
Word32
5917 -> String -> ShowS
showString String
"InitiationIntervalINTEL"
Word32
5918 -> String -> ShowS
showString String
"MaxConcurrencyINTEL"
Word32
5919 -> String -> ShowS
showString String
"PipelineEnableINTEL"
Word32
5921 -> String -> ShowS
showString String
"BufferLocationINTEL"
Word32
5944 -> String -> ShowS
showString String
"IOPipeStorageINTEL"
Word32
6080 -> String -> ShowS
showString String
"FunctionFloatingPointModeINTEL"
Word32
6085 -> String -> ShowS
showString String
"SingleElementVectorINTEL"
Word32
6087 -> String -> ShowS
showString String
"VectorComputeCallableFunctionINTEL"
Word32
6140 -> String -> ShowS
showString String
"MediaBlockIOINTEL"
Word32
6151 -> String -> ShowS
showString String
"StallFreeINTEL"
Word32
6170 -> String -> ShowS
showString String
"FPMaxErrorDecorationINTEL"
Word32
6172 -> String -> ShowS
showString String
"LatencyControlLabelINTEL"
Word32
6173 -> String -> ShowS
showString String
"LatencyControlConstraintINTEL"
Word32
6175 -> String -> ShowS
showString String
"ConduitKernelArgumentINTEL"
Word32
6176 -> String -> ShowS
showString String
"RegisterMapKernelArgumentINTEL"
Word32
6177 -> String -> ShowS
showString String
"MMHostInterfaceAddressWidthINTEL"
Word32
6178 -> String -> ShowS
showString String
"MMHostInterfaceDataWidthINTEL"
Word32
6179 -> String -> ShowS
showString String
"MMHostInterfaceLatencyINTEL"
Word32
6180 -> String -> ShowS
showString String
"MMHostInterfaceReadWriteModeINTEL"
Word32
6181 -> String -> ShowS
showString String
"MMHostInterfaceMaxBurstINTEL"
Word32
6182 -> String -> ShowS
showString String
"MMHostInterfaceWaitRequestINTEL"
Word32
6183 -> String -> ShowS
showString String
"StableKernelArgumentINTEL"
Word32
6188 -> String -> ShowS
showString String
"HostAccessINTEL"
Word32
6190 -> String -> ShowS
showString String
"InitModeINTEL"
Word32
6191 -> String -> ShowS
showString String
"ImplementInRegisterMapINTEL"
Word32
6442 -> String -> ShowS
showString String
"CacheControlLoadINTEL"
Word32
6443 -> String -> ShowS
showString String
"CacheControlStoreINTEL"
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
"Decoration " 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 RelaxedPrecision :: Decoration
pattern $mRelaxedPrecision :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bRelaxedPrecision :: Decoration
RelaxedPrecision = Decoration 0
pattern SpecId :: Decoration
pattern $mSpecId :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bSpecId :: Decoration
SpecId = Decoration 1
pattern Block :: Decoration
pattern $mBlock :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBlock :: Decoration
Block = Decoration 2
pattern BufferBlock :: Decoration
pattern $mBufferBlock :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBufferBlock :: Decoration
BufferBlock = Decoration 3
pattern RowMajor :: Decoration
pattern $mRowMajor :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bRowMajor :: Decoration
RowMajor = Decoration 4
pattern ColMajor :: Decoration
pattern $mColMajor :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bColMajor :: Decoration
ColMajor = Decoration 5
pattern ArrayStride :: Decoration
pattern $mArrayStride :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bArrayStride :: Decoration
ArrayStride = Decoration 6
pattern MatrixStride :: Decoration
pattern $mMatrixStride :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMatrixStride :: Decoration
MatrixStride = Decoration 7
pattern GLSLShared :: Decoration
pattern $mGLSLShared :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bGLSLShared :: Decoration
GLSLShared = Decoration 8
pattern GLSLPacked :: Decoration
pattern $mGLSLPacked :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bGLSLPacked :: Decoration
GLSLPacked = Decoration 9
pattern CPacked :: Decoration
pattern $mCPacked :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bCPacked :: Decoration
CPacked = Decoration 10
pattern BuiltIn :: Decoration
pattern $mBuiltIn :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBuiltIn :: Decoration
BuiltIn = Decoration 11
pattern NoPerspective :: Decoration
pattern $mNoPerspective :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNoPerspective :: Decoration
NoPerspective = Decoration 13
pattern Flat :: Decoration
pattern $mFlat :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bFlat :: Decoration
Flat = Decoration 14
pattern Patch :: Decoration
pattern $mPatch :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPatch :: Decoration
Patch = Decoration 15
pattern Centroid :: Decoration
pattern $mCentroid :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bCentroid :: Decoration
Centroid = Decoration 16
pattern Sample :: Decoration
pattern $mSample :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bSample :: Decoration
Sample = Decoration 17
pattern Invariant :: Decoration
pattern $mInvariant :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bInvariant :: Decoration
Invariant = Decoration 18
pattern Restrict :: Decoration
pattern $mRestrict :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bRestrict :: Decoration
Restrict = Decoration 19
pattern Aliased :: Decoration
pattern $mAliased :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bAliased :: Decoration
Aliased = Decoration 20
pattern Volatile :: Decoration
pattern $mVolatile :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bVolatile :: Decoration
Volatile = Decoration 21
pattern Constant :: Decoration
pattern $mConstant :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bConstant :: Decoration
Constant = Decoration 22
pattern Coherent :: Decoration
pattern $mCoherent :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bCoherent :: Decoration
Coherent = Decoration 23
pattern NonWritable :: Decoration
pattern $mNonWritable :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNonWritable :: Decoration
NonWritable = Decoration 24
pattern NonReadable :: Decoration
pattern $mNonReadable :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNonReadable :: Decoration
NonReadable = Decoration 25
pattern Uniform :: Decoration
pattern $mUniform :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bUniform :: Decoration
Uniform = Decoration 26
pattern UniformId :: Decoration
pattern $mUniformId :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bUniformId :: Decoration
UniformId = Decoration 27
pattern SaturatedConversion :: Decoration
pattern $mSaturatedConversion :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bSaturatedConversion :: Decoration
SaturatedConversion = Decoration 28
pattern Stream :: Decoration
pattern $mStream :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bStream :: Decoration
Stream = Decoration 29
pattern Location :: Decoration
pattern $mLocation :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bLocation :: Decoration
Location = Decoration 30
pattern Component :: Decoration
pattern $mComponent :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bComponent :: Decoration
Component = Decoration 31
pattern Index :: Decoration
pattern $mIndex :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bIndex :: Decoration
Index = Decoration 32
pattern Binding :: Decoration
pattern $mBinding :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBinding :: Decoration
Binding = Decoration 33
pattern DescriptorSet :: Decoration
pattern $mDescriptorSet :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bDescriptorSet :: Decoration
DescriptorSet = Decoration 34
pattern Offset :: Decoration
pattern $mOffset :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bOffset :: Decoration
Offset = Decoration 35
pattern XfbBuffer :: Decoration
pattern $mXfbBuffer :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bXfbBuffer :: Decoration
XfbBuffer = Decoration 36
pattern XfbStride :: Decoration
pattern $mXfbStride :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bXfbStride :: Decoration
XfbStride = Decoration 37
pattern FuncParamAttr :: Decoration
pattern $mFuncParamAttr :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bFuncParamAttr :: Decoration
FuncParamAttr = Decoration 38
pattern FPRoundingMode :: Decoration
pattern $mFPRoundingMode :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bFPRoundingMode :: Decoration
FPRoundingMode = Decoration 39
pattern FPFastMathMode :: Decoration
pattern $mFPFastMathMode :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bFPFastMathMode :: Decoration
FPFastMathMode = Decoration 40
pattern LinkageAttributes :: Decoration
pattern $mLinkageAttributes :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bLinkageAttributes :: Decoration
LinkageAttributes = Decoration 41
pattern NoContraction :: Decoration
pattern $mNoContraction :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNoContraction :: Decoration
NoContraction = Decoration 42
pattern InputAttachmentIndex :: Decoration
pattern $mInputAttachmentIndex :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bInputAttachmentIndex :: Decoration
InputAttachmentIndex = Decoration 43
pattern Alignment :: Decoration
pattern $mAlignment :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bAlignment :: Decoration
Alignment = Decoration 44
pattern MaxByteOffset :: Decoration
pattern $mMaxByteOffset :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaxByteOffset :: Decoration
MaxByteOffset = Decoration 45
pattern AlignmentId :: Decoration
pattern $mAlignmentId :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bAlignmentId :: Decoration
AlignmentId = Decoration 46
pattern MaxByteOffsetId :: Decoration
pattern $mMaxByteOffsetId :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaxByteOffsetId :: Decoration
MaxByteOffsetId = Decoration 47
pattern NoSignedWrap :: Decoration
pattern $mNoSignedWrap :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNoSignedWrap :: Decoration
NoSignedWrap = Decoration 4469
pattern NoUnsignedWrap :: Decoration
pattern $mNoUnsignedWrap :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNoUnsignedWrap :: Decoration
NoUnsignedWrap = Decoration 4470
pattern WeightTextureQCOM :: Decoration
pattern $mWeightTextureQCOM :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bWeightTextureQCOM :: Decoration
WeightTextureQCOM = Decoration 4487
pattern BlockMatchTextureQCOM :: Decoration
pattern $mBlockMatchTextureQCOM :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBlockMatchTextureQCOM :: Decoration
BlockMatchTextureQCOM = Decoration 4488
pattern BlockMatchSamplerQCOM :: Decoration
pattern $mBlockMatchSamplerQCOM :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBlockMatchSamplerQCOM :: Decoration
BlockMatchSamplerQCOM = Decoration 4499
pattern ExplicitInterpAMD :: Decoration
pattern $mExplicitInterpAMD :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bExplicitInterpAMD :: Decoration
ExplicitInterpAMD = Decoration 4999
pattern NodeSharesPayloadLimitsWithAMDX :: Decoration
pattern $mNodeSharesPayloadLimitsWithAMDX :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNodeSharesPayloadLimitsWithAMDX :: Decoration
NodeSharesPayloadLimitsWithAMDX = Decoration 5019
pattern NodeMaxPayloadsAMDX :: Decoration
pattern $mNodeMaxPayloadsAMDX :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNodeMaxPayloadsAMDX :: Decoration
NodeMaxPayloadsAMDX = Decoration 5020
pattern TrackFinishWritingAMDX :: Decoration
pattern $mTrackFinishWritingAMDX :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bTrackFinishWritingAMDX :: Decoration
TrackFinishWritingAMDX = Decoration 5078
pattern PayloadNodeNameAMDX :: Decoration
pattern $mPayloadNodeNameAMDX :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPayloadNodeNameAMDX :: Decoration
PayloadNodeNameAMDX = Decoration 5091
pattern OverrideCoverageNV :: Decoration
pattern $mOverrideCoverageNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bOverrideCoverageNV :: Decoration
OverrideCoverageNV = Decoration 5248
pattern PassthroughNV :: Decoration
pattern $mPassthroughNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPassthroughNV :: Decoration
PassthroughNV = Decoration 5250
pattern ViewportRelativeNV :: Decoration
pattern $mViewportRelativeNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bViewportRelativeNV :: Decoration
ViewportRelativeNV = Decoration 5252
pattern SecondaryViewportRelativeNV :: Decoration
pattern $mSecondaryViewportRelativeNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bSecondaryViewportRelativeNV :: Decoration
SecondaryViewportRelativeNV = Decoration 5256
pattern PerPrimitiveEXT :: Decoration
pattern $mPerPrimitiveEXT :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPerPrimitiveEXT :: Decoration
PerPrimitiveEXT = Decoration 5271
pattern PerPrimitiveNV :: Decoration
pattern $mPerPrimitiveNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPerPrimitiveNV :: Decoration
PerPrimitiveNV = Decoration 5271
pattern PerViewNV :: Decoration
pattern $mPerViewNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPerViewNV :: Decoration
PerViewNV = Decoration 5272
pattern PerTaskNV :: Decoration
pattern $mPerTaskNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPerTaskNV :: Decoration
PerTaskNV = Decoration 5273
pattern PerVertexKHR :: Decoration
pattern $mPerVertexKHR :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPerVertexKHR :: Decoration
PerVertexKHR = Decoration 5285
pattern PerVertexNV :: Decoration
pattern $mPerVertexNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPerVertexNV :: Decoration
PerVertexNV = Decoration 5285
pattern NonUniform :: Decoration
pattern $mNonUniform :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNonUniform :: Decoration
NonUniform = Decoration 5300
pattern NonUniformEXT :: Decoration
pattern $mNonUniformEXT :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNonUniformEXT :: Decoration
NonUniformEXT = Decoration 5300
pattern RestrictPointer :: Decoration
pattern $mRestrictPointer :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bRestrictPointer :: Decoration
RestrictPointer = Decoration 5355
pattern RestrictPointerEXT :: Decoration
pattern $mRestrictPointerEXT :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bRestrictPointerEXT :: Decoration
RestrictPointerEXT = Decoration 5355
pattern AliasedPointer :: Decoration
pattern $mAliasedPointer :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bAliasedPointer :: Decoration
AliasedPointer = Decoration 5356
pattern AliasedPointerEXT :: Decoration
pattern $mAliasedPointerEXT :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bAliasedPointerEXT :: Decoration
AliasedPointerEXT = Decoration 5356
pattern HitObjectShaderRecordBufferNV :: Decoration
pattern $mHitObjectShaderRecordBufferNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bHitObjectShaderRecordBufferNV :: Decoration
HitObjectShaderRecordBufferNV = Decoration 5386
pattern BindlessSamplerNV :: Decoration
pattern $mBindlessSamplerNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBindlessSamplerNV :: Decoration
BindlessSamplerNV = Decoration 5398
pattern BindlessImageNV :: Decoration
pattern $mBindlessImageNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBindlessImageNV :: Decoration
BindlessImageNV = Decoration 5399
pattern BoundSamplerNV :: Decoration
pattern $mBoundSamplerNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBoundSamplerNV :: Decoration
BoundSamplerNV = Decoration 5400
pattern BoundImageNV :: Decoration
pattern $mBoundImageNV :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBoundImageNV :: Decoration
BoundImageNV = Decoration 5401
pattern SIMTCallINTEL :: Decoration
pattern $mSIMTCallINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bSIMTCallINTEL :: Decoration
SIMTCallINTEL = Decoration 5599
pattern ReferencedIndirectlyINTEL :: Decoration
pattern $mReferencedIndirectlyINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bReferencedIndirectlyINTEL :: Decoration
ReferencedIndirectlyINTEL = Decoration 5602
pattern ClobberINTEL :: Decoration
pattern $mClobberINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bClobberINTEL :: Decoration
ClobberINTEL = Decoration 5607
pattern SideEffectsINTEL :: Decoration
pattern $mSideEffectsINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bSideEffectsINTEL :: Decoration
SideEffectsINTEL = Decoration 5608
pattern VectorComputeVariableINTEL :: Decoration
pattern $mVectorComputeVariableINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bVectorComputeVariableINTEL :: Decoration
VectorComputeVariableINTEL = Decoration 5624
pattern FuncParamIOKindINTEL :: Decoration
pattern $mFuncParamIOKindINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bFuncParamIOKindINTEL :: Decoration
FuncParamIOKindINTEL = Decoration 5625
pattern VectorComputeFunctionINTEL :: Decoration
pattern $mVectorComputeFunctionINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bVectorComputeFunctionINTEL :: Decoration
VectorComputeFunctionINTEL = Decoration 5626
pattern StackCallINTEL :: Decoration
pattern $mStackCallINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bStackCallINTEL :: Decoration
StackCallINTEL = Decoration 5627
pattern GlobalVariableOffsetINTEL :: Decoration
pattern $mGlobalVariableOffsetINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bGlobalVariableOffsetINTEL :: Decoration
GlobalVariableOffsetINTEL = Decoration 5628
pattern CounterBuffer :: Decoration
pattern $mCounterBuffer :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bCounterBuffer :: Decoration
CounterBuffer = Decoration 5634
pattern HlslCounterBufferGOOGLE :: Decoration
pattern $mHlslCounterBufferGOOGLE :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bHlslCounterBufferGOOGLE :: Decoration
HlslCounterBufferGOOGLE = Decoration 5634
pattern HlslSemanticGOOGLE :: Decoration
pattern $mHlslSemanticGOOGLE :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bHlslSemanticGOOGLE :: Decoration
HlslSemanticGOOGLE = Decoration 5635
pattern UserSemantic :: Decoration
pattern $mUserSemantic :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bUserSemantic :: Decoration
UserSemantic = Decoration 5635
pattern UserTypeGOOGLE :: Decoration
pattern $mUserTypeGOOGLE :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bUserTypeGOOGLE :: Decoration
UserTypeGOOGLE = Decoration 5636
pattern FunctionRoundingModeINTEL :: Decoration
pattern $mFunctionRoundingModeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bFunctionRoundingModeINTEL :: Decoration
FunctionRoundingModeINTEL = Decoration 5822
pattern FunctionDenormModeINTEL :: Decoration
pattern $mFunctionDenormModeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bFunctionDenormModeINTEL :: Decoration
FunctionDenormModeINTEL = Decoration 5823
pattern RegisterINTEL :: Decoration
pattern $mRegisterINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bRegisterINTEL :: Decoration
RegisterINTEL = Decoration 5825
pattern MemoryINTEL :: Decoration
pattern $mMemoryINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMemoryINTEL :: Decoration
MemoryINTEL = Decoration 5826
pattern NumbanksINTEL :: Decoration
pattern $mNumbanksINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNumbanksINTEL :: Decoration
NumbanksINTEL = Decoration 5827
pattern BankwidthINTEL :: Decoration
pattern $mBankwidthINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBankwidthINTEL :: Decoration
BankwidthINTEL = Decoration 5828
pattern MaxPrivateCopiesINTEL :: Decoration
pattern $mMaxPrivateCopiesINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaxPrivateCopiesINTEL :: Decoration
MaxPrivateCopiesINTEL = Decoration 5829
pattern SinglepumpINTEL :: Decoration
pattern $mSinglepumpINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bSinglepumpINTEL :: Decoration
SinglepumpINTEL = Decoration 5830
pattern DoublepumpINTEL :: Decoration
pattern $mDoublepumpINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bDoublepumpINTEL :: Decoration
DoublepumpINTEL = Decoration 5831
pattern MaxReplicatesINTEL :: Decoration
pattern $mMaxReplicatesINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaxReplicatesINTEL :: Decoration
MaxReplicatesINTEL = Decoration 5832
pattern SimpleDualPortINTEL :: Decoration
pattern $mSimpleDualPortINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bSimpleDualPortINTEL :: Decoration
SimpleDualPortINTEL = Decoration 5833
pattern MergeINTEL :: Decoration
pattern $mMergeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMergeINTEL :: Decoration
MergeINTEL = Decoration 5834
pattern BankBitsINTEL :: Decoration
pattern $mBankBitsINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBankBitsINTEL :: Decoration
BankBitsINTEL = Decoration 5835
pattern ForcePow2DepthINTEL :: Decoration
pattern $mForcePow2DepthINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bForcePow2DepthINTEL :: Decoration
ForcePow2DepthINTEL = Decoration 5836
pattern StridesizeINTEL :: Decoration
pattern $mStridesizeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bStridesizeINTEL :: Decoration
StridesizeINTEL = Decoration 5883
pattern WordsizeINTEL :: Decoration
pattern $mWordsizeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bWordsizeINTEL :: Decoration
WordsizeINTEL = Decoration 5884
pattern TrueDualPortINTEL :: Decoration
pattern $mTrueDualPortINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bTrueDualPortINTEL :: Decoration
TrueDualPortINTEL = Decoration 5885
pattern BurstCoalesceINTEL :: Decoration
pattern $mBurstCoalesceINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBurstCoalesceINTEL :: Decoration
BurstCoalesceINTEL = Decoration 5899
pattern CacheSizeINTEL :: Decoration
pattern $mCacheSizeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bCacheSizeINTEL :: Decoration
CacheSizeINTEL = Decoration 5900
pattern DontStaticallyCoalesceINTEL :: Decoration
pattern $mDontStaticallyCoalesceINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bDontStaticallyCoalesceINTEL :: Decoration
DontStaticallyCoalesceINTEL = Decoration 5901
pattern PrefetchINTEL :: Decoration
pattern $mPrefetchINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPrefetchINTEL :: Decoration
PrefetchINTEL = Decoration 5902
pattern StallEnableINTEL :: Decoration
pattern $mStallEnableINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bStallEnableINTEL :: Decoration
StallEnableINTEL = Decoration 5905
pattern FuseLoopsInFunctionINTEL :: Decoration
pattern $mFuseLoopsInFunctionINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bFuseLoopsInFunctionINTEL :: Decoration
FuseLoopsInFunctionINTEL = Decoration 5907
pattern MathOpDSPModeINTEL :: Decoration
pattern $mMathOpDSPModeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMathOpDSPModeINTEL :: Decoration
MathOpDSPModeINTEL = Decoration 5909
pattern AliasScopeINTEL :: Decoration
pattern $mAliasScopeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bAliasScopeINTEL :: Decoration
AliasScopeINTEL = Decoration 5914
pattern NoAliasINTEL :: Decoration
pattern $mNoAliasINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bNoAliasINTEL :: Decoration
NoAliasINTEL = Decoration 5915
pattern InitiationIntervalINTEL :: Decoration
pattern $mInitiationIntervalINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bInitiationIntervalINTEL :: Decoration
InitiationIntervalINTEL = Decoration 5917
pattern MaxConcurrencyINTEL :: Decoration
pattern $mMaxConcurrencyINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMaxConcurrencyINTEL :: Decoration
MaxConcurrencyINTEL = Decoration 5918
pattern PipelineEnableINTEL :: Decoration
pattern $mPipelineEnableINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bPipelineEnableINTEL :: Decoration
PipelineEnableINTEL = Decoration 5919
pattern BufferLocationINTEL :: Decoration
pattern $mBufferLocationINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bBufferLocationINTEL :: Decoration
BufferLocationINTEL = Decoration 5921
pattern IOPipeStorageINTEL :: Decoration
pattern $mIOPipeStorageINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bIOPipeStorageINTEL :: Decoration
IOPipeStorageINTEL = Decoration 5944
pattern FunctionFloatingPointModeINTEL :: Decoration
pattern $mFunctionFloatingPointModeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bFunctionFloatingPointModeINTEL :: Decoration
FunctionFloatingPointModeINTEL = Decoration 6080
pattern SingleElementVectorINTEL :: Decoration
pattern $mSingleElementVectorINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bSingleElementVectorINTEL :: Decoration
SingleElementVectorINTEL = Decoration 6085
pattern VectorComputeCallableFunctionINTEL :: Decoration
pattern $mVectorComputeCallableFunctionINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bVectorComputeCallableFunctionINTEL :: Decoration
VectorComputeCallableFunctionINTEL = Decoration 6087
pattern MediaBlockIOINTEL :: Decoration
pattern $mMediaBlockIOINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMediaBlockIOINTEL :: Decoration
MediaBlockIOINTEL = Decoration 6140
pattern StallFreeINTEL :: Decoration
pattern $mStallFreeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bStallFreeINTEL :: Decoration
StallFreeINTEL = Decoration 6151
pattern FPMaxErrorDecorationINTEL :: Decoration
pattern $mFPMaxErrorDecorationINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bFPMaxErrorDecorationINTEL :: Decoration
FPMaxErrorDecorationINTEL = Decoration 6170
pattern LatencyControlLabelINTEL :: Decoration
pattern $mLatencyControlLabelINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bLatencyControlLabelINTEL :: Decoration
LatencyControlLabelINTEL = Decoration 6172
pattern LatencyControlConstraintINTEL :: Decoration
pattern $mLatencyControlConstraintINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bLatencyControlConstraintINTEL :: Decoration
LatencyControlConstraintINTEL = Decoration 6173
pattern ConduitKernelArgumentINTEL :: Decoration
pattern $mConduitKernelArgumentINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bConduitKernelArgumentINTEL :: Decoration
ConduitKernelArgumentINTEL = Decoration 6175
pattern RegisterMapKernelArgumentINTEL :: Decoration
pattern $mRegisterMapKernelArgumentINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bRegisterMapKernelArgumentINTEL :: Decoration
RegisterMapKernelArgumentINTEL = Decoration 6176
pattern MMHostInterfaceAddressWidthINTEL :: Decoration
pattern $mMMHostInterfaceAddressWidthINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMMHostInterfaceAddressWidthINTEL :: Decoration
MMHostInterfaceAddressWidthINTEL = Decoration 6177
pattern MMHostInterfaceDataWidthINTEL :: Decoration
pattern $mMMHostInterfaceDataWidthINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMMHostInterfaceDataWidthINTEL :: Decoration
MMHostInterfaceDataWidthINTEL = Decoration 6178
pattern MMHostInterfaceLatencyINTEL :: Decoration
pattern $mMMHostInterfaceLatencyINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMMHostInterfaceLatencyINTEL :: Decoration
MMHostInterfaceLatencyINTEL = Decoration 6179
pattern MMHostInterfaceReadWriteModeINTEL :: Decoration
pattern $mMMHostInterfaceReadWriteModeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMMHostInterfaceReadWriteModeINTEL :: Decoration
MMHostInterfaceReadWriteModeINTEL = Decoration 6180
pattern MMHostInterfaceMaxBurstINTEL :: Decoration
pattern $mMMHostInterfaceMaxBurstINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMMHostInterfaceMaxBurstINTEL :: Decoration
MMHostInterfaceMaxBurstINTEL = Decoration 6181
pattern MMHostInterfaceWaitRequestINTEL :: Decoration
pattern $mMMHostInterfaceWaitRequestINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bMMHostInterfaceWaitRequestINTEL :: Decoration
MMHostInterfaceWaitRequestINTEL = Decoration 6182
pattern StableKernelArgumentINTEL :: Decoration
pattern $mStableKernelArgumentINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bStableKernelArgumentINTEL :: Decoration
StableKernelArgumentINTEL = Decoration 6183
pattern HostAccessINTEL :: Decoration
pattern $mHostAccessINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bHostAccessINTEL :: Decoration
HostAccessINTEL = Decoration 6188
pattern InitModeINTEL :: Decoration
pattern $mInitModeINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bInitModeINTEL :: Decoration
InitModeINTEL = Decoration 6190
pattern ImplementInRegisterMapINTEL :: Decoration
pattern $mImplementInRegisterMapINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bImplementInRegisterMapINTEL :: Decoration
ImplementInRegisterMapINTEL = Decoration 6191
pattern CacheControlLoadINTEL :: Decoration
pattern $mCacheControlLoadINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bCacheControlLoadINTEL :: Decoration
CacheControlLoadINTEL = Decoration 6442
pattern CacheControlStoreINTEL :: Decoration
pattern $mCacheControlStoreINTEL :: forall {r}. Decoration -> ((# #) -> r) -> ((# #) -> r) -> r
$bCacheControlStoreINTEL :: Decoration
CacheControlStoreINTEL = Decoration 6443