comparison nobuild/d.vim @ 98:cd0c9a4a7e44

Added new d.vim
author David Bryant <bagnose@gmail.com>
date Tue, 31 Aug 2010 10:03:37 +0930
parents
children ad672ab258c5
comparison
equal deleted inserted replaced
97:dcd641209671 98:cd0c9a4a7e44
1 " Vim syntax file for the D programming language (version 1.053 and 2.047).
2 "
3 " Language: D
4 " Maintainer: Jesse Phillips <Jesse.K.Phillips+D@gmail.com>
5 " Last Change: 2010 Aug 17
6 " Version: 0.20
7 "
8 " Contributors:
9 " - Jason Mills <jasonmills@nf.sympatico.ca>: original Maintainer
10 " - Shougo Matsushita <Shougo.Matsu@gmail.com>: updates for latest 2.047 highlighting
11 " - Kirk McDonald: version 0.17 updates, with minor modifications
12 " (http://paste.dprogramming.com/dplmb7qx?view=hidelines)
13 " - Tim Keating: patch to fix a bug in highlighting the `\` literal
14 " - Frank Benoit: Fixed a bug that caused some identifiers and numbers to highlight as octal number errors.
15 "
16 " Please email me with bugs, comments, and suggestions.
17 "
18 " Options:
19 " d_comment_strings - Set to highlight strings and numbers in comments.
20 "
21 " d_hl_operator_overload - Set to highlight D's specially named functions
22 " that when overloaded implement unary and binary operators (e.g. opCmp).
23 "
24 " Todo:
25 " - Determine a better method of sync'ing than simply setting minlines
26 " to a large number.
27 "
28 " - Several keywords (e.g., in, out, inout) are both storage class and
29 " statements, depending on their context. Perhaps use pattern matching to
30 " figure out which and highlight appropriately. For now I have made such
31 " keywords storage classes so their highlighting is consistent with other
32 " keywords that are commonly used with them, but are true storage classes,
33 " such as lazy. Similarly, I made some statement keywords (e.g. body) storage
34 " classes.
35 "
36 " - Mark contents of the asm statement body as special
37 "
38 " - Maybe highlight the 'exit', 'failure', and 'success' parts of the
39 " scope() statement.
40 "
41 " - Highlighting DDoc comments.
42 "
43
44 " Quit when a syntax file was already loaded
45 if exists("b:current_syntax")
46 finish
47 endif
48
49 " Keyword definitions
50 "
51 syn keyword dExternal import package module extern
52 syn keyword dConditional if else switch
53 syn keyword dBranch goto break continue
54 syn keyword dRepeat while for do foreach foreach_reverse
55 syn keyword dBoolean true false
56 syn keyword dConstant null
57 syn keyword dConstant __FILE__ __LINE__ __EOF__ __VERSION__
58 syn keyword dConstant __DATE__ __TIME__ __TIMESTAMP__ __VENDOR__
59 syn keyword dTypedef alias typedef
60 syn keyword dStructure template interface class struct union
61 syn keyword dEnum enum
62 syn keyword dOperator new delete typeof typeid cast align is
63 syn keyword dOperator this super
64 if exists("d_hl_operator_overload")
65 syn keyword dOpOverload opNeg opCom opPostInc opPostDec opCast opAdd
66 syn keyword dOpOverload opSub opSub_r opMul opDiv opDiv_r opMod
67 syn keyword dOpOverload opMod_r opAnd opOr opXor opShl opShl_r opShr
68 syn keyword dOpOverload opShr_r opUShr opUShr_r opCat
69 syn keyword dOpOverload opCat_r opEquals opEquals opCmp
70 syn keyword dOpOverload opAssign opAddAssign opSubAssign opMulAssign
71 syn keyword dOpOverload opDivAssign opModAssign opAndAssign
72 syn keyword dOpOverload opOrAssign opXorAssign opShlAssign
73 syn keyword dOpOverload opShrAssign opUShrAssign opCatAssign
74 syn keyword dOpOverload opIndex opIndexAssign opIndexOpAssign
75 syn keyword dOpOverload opCall opSlice opSliceAssign opSliceOpAssign
76 syn keyword dOpOverload opPos opAdd_r opMul_r opAnd_r opOr_r opXor_r
77 syn keyword dOpOverload opIn opIn_r opPow opDispatch opStar opDot
78 syn keyword dOpOverload opApply opApplyReverse
79 syn keyword dOpOverload opUnary opIndexUnary opSliceUnary
80 syn keyword dOpOverload opBinary opBinaryRight
81 endif
82
83 syn keyword dType void ushort int uint long ulong float
84 syn keyword dType byte ubyte double bit char wchar ucent cent
85 syn keyword dType short bool dchar wstring dstring
86 syn keyword dType real ireal ifloat idouble
87 syn keyword dType creal cfloat cdouble
88 syn keyword dDebug deprecated unittest
89 syn keyword dExceptions throw try catch finally
90 syn keyword dScopeDecl public protected private export
91 syn keyword dStatement debug return with
92 syn keyword dStatement function delegate __traits mixin macro
93 syn keyword dStorageClass in out inout ref lazy body
94 syn keyword dStorageClass pure nothrow
95 syn keyword dStorageClass auto static override final abstract volatile
96 syn keyword dStorageClass __gshared __thread
97 syn keyword dStorageClass synchronized shared immutable const lazy
98 syn keyword dPragma pragma
99 syn keyword dIdentifier _arguments _argptr __vptr __monitor _ctor _dtor
100 syn keyword dScopeIdentifier contained exit success failure
101 syn keyword dAttribute contained safe trusted system
102 syn keyword dAttribute contained property disable
103 syn keyword dVersionIdentifier contained DigitalMars GNU LDC LLVM
104 syn keyword dVersionIdentifier contained X86 X86_64 Windows Win32 Win64
105 syn keyword dVersionIdentifier contained linux Posix OSX FreeBSD
106 syn keyword dVersionIdentifier contained LittleEndian BigEndian D_Coverage
107 syn keyword dVersionIdentifier contained D_Ddoc D_InlineAsm_X86
108 syn keyword dVersionIdentifier contained D_InlineAsm_X86_64 D_LP64 D_PIC
109 syn keyword dVersionIdentifier contained unittest D_Version2 none all
110
111 " Attributes/annotations
112 syn match dAnnotation "@[_$a-zA-Z][_$a-zA-Z0-9_]*\>" contains=dAttribute
113
114 " Version Identifiers
115 syn match dVersion "version\s*([_a-zA-Z][_a-zA-Z0-9]*\>"he=s+7 contains=dVersionIdentifier
116 syn match dVersion "[^.]\s*\<version\>"
117 syn match dVersion "^\<version\>"
118
119 " Scope Identifiers
120 syn match dScope "scope\s*([_a-zA-Z][_a-zA-Z0-9]*\>"he=s+5 contains=dScopeIdentifier
121
122 " String is a statement and a module name.
123 syn match dAssert "^string"
124 syn match dAssert "[^.]\s*\<string\>"ms=s+1
125
126 " Assert is a statement and a module name.
127 syn match dAssert "^assert"
128 syn match dAssert "[^.]\s*\<assert\>"ms=s+1
129
130 " dTokens is used by the token string highlighting
131 syn cluster dTokens contains=dExternal,dConditional,dBranch,dRepeat,dBoolean
132 syn cluster dTokens add=dConstant,dTypedef,dStructure,dOperator,dOpOverload
133 syn cluster dTokens add=dType,dDebug,dExceptions,dScopeDecl,dStatement
134 syn cluster dTokens add=dStorageClass,dPragma,dAssert,dAnnotation
135
136
137 " Labels
138 "
139 " We contain dScopeDecl so public: private: etc. are not highlighted like labels
140 syn match dUserLabel "^\s*[_$a-zA-Z][_$a-zA-Z0-9_]*\s*:"he=e-1 contains=dLabel,dScopeDecl,dEnum
141 syn keyword dLabel case default
142
143 syn cluster dTokens add=dUserLabel,dLabel
144
145 " Comments
146 "
147 syn keyword dTodo contained TODO FIXME TEMP REFACTOR REVIEW HACK BUG XXX
148 syn match dCommentStar contained "^\s*\*[^/]"me=e-1
149 syn match dCommentStar contained "^\s*\*$"
150 syn match dCommentPlus contained "^\s*+[^/]"me=e-1
151 syn match dCommentPlus contained "^\s*+$"
152 if exists("d_comment_strings")
153 syn region dBlockCommentString contained start=+"+ end=+"+ end=+\*/+me=s-1,he=s-1 contains=dCommentStar,dUnicode,dEscSequence,@Spell
154 syn region dNestedCommentString contained start=+"+ end=+"+ end="+"me=s-1,he=s-1 contains=dCommentPlus,dUnicode,dEscSequence,@Spell
155 syn region dLineCommentString contained start=+"+ end=+$\|"+ contains=dUnicode,dEscSequence,@Spell
156 syn region dBlockComment start="/\*" end="\*/" contains=dBlockCommentString,dTodo,@Spell
157 syn region dNestedComment start="/+" end="+/" contains=dNestedComment,dNestedCommentString,dTodo,@Spell
158 syn match dLineComment "//.*" contains=dLineCommentString,dTodo,@Spell
159 else
160 syn region dBlockComment start="/\*" end="\*/" contains=dBlockCommentString,dTodo,@Spell
161 syn region dNestedComment start="/+" end="+/" contains=dNestedComment,dNestedCommentString,dTodo,@Spell
162 syn match dLineComment "//.*" contains=dLineCommentString,dTodo,@Spell
163 endif
164
165 hi link dLineCommentString dBlockCommentString
166 hi link dBlockCommentString dString
167 hi link dNestedCommentString dString
168 hi link dCommentStar dBlockComment
169 hi link dCommentPlus dNestedComment
170
171 syn cluster dTokens add=dBlockComment,dNestedComment,dLineComment
172
173 " /+ +/ style comments and strings that span multiple lines can cause
174 " problems. To play it safe, set minlines to a large number.
175 syn sync minlines=200
176 " Use ccomment for /* */ style comments
177 syn sync ccomment dBlockComment
178
179 " Characters
180 "
181 syn match dSpecialCharError contained "[^']"
182
183 " Escape sequences (oct,specal char,hex,wchar, character entities \&xxx;)
184 " These are not contained because they are considered string literals.
185 syn match dEscSequence "\\\(\o\{1,3}\|[\"\\'\\?ntbrfva]\|u\x\{4}\|U\x\{8}\|x\x\x\)"
186 syn match dEscSequence "\\&[^;& \t]\+;"
187 syn match dCharacter "'[^']*'" contains=dEscSequence,dSpecialCharError
188 syn match dCharacter "'\\''" contains=dEscSequence
189 syn match dCharacter "'[^\\]'"
190
191 syn cluster dTokens add=dEscSequence,dCharacter
192
193 " Unicode characters
194 "
195 syn match dUnicode "\\u\d\{4\}"
196
197 " String.
198 "
199 syn region dString start=+"+ end=+"[cwd]\=+ skip=+\\\\\|\\"+ contains=dEscSequence,@Spell
200 syn region dRawString start=+`+ end=+`[cwd]\=+ contains=@Spell
201 syn region dRawString start=+r"+ end=+"[cwd]\=+ contains=@Spell
202 syn region dHexString start=+x"+ end=+"[cwd]\=+ contains=@Spell
203 syn region dDelimString start=+q"\z(.\)+ end=+\z1"+ contains=@Spell
204 syn region dHereString start=+q"\z(\I\i*\)\n+ end=+\n\z1"+ contains=@Spell
205
206 " Nesting delimited string contents
207 "
208 syn region dNestParenString start=+(+ end=+)+ contained transparent contains=dNestParenString,@Spell
209 syn region dNestBrackString start=+\[+ end=+\]+ contained transparent contains=dNestBrackString,@Spell
210 syn region dNestAngleString start=+<+ end=+>+ contained transparent contains=dNestAngleString,@Spell
211 syn region dNestCurlyString start=+{+ end=+}+ contained transparent contains=dNestCurlyString,@Spell
212
213 " Nesting delimited strings
214 "
215 syn region dParenString matchgroup=dParenString start=+q"(+ end=+)"+ contains=dNestParenString,@Spell
216 syn region dBrackString matchgroup=dBrackString start=+q"\[+ end=+\]"+ contains=dNestBrackString,@Spell
217 syn region dAngleString matchgroup=dAngleString start=+q"<+ end=+>"+ contains=dNestAngleString,@Spell
218 syn region dCurlyString matchgroup=dCurlyString start=+q"{+ end=+}"+ contains=dNestCurlyString,@Spell
219
220 hi link dParenString dNestString
221 hi link dBrackString dNestString
222 hi link dAngleString dNestString
223 hi link dCurlyString dNestString
224
225 syn cluster dTokens add=dString,dRawString,dHexString,dDelimString,dNestString
226
227 " Token strings
228 "
229 syn region dNestTokenString start=+{+ end=+}+ contained contains=dNestTokenString,@dTokens
230 syn region dTokenString matchgroup=dTokenStringBrack transparent start=+q{+ end=+}+ contains=dNestTokenString,@dTokens
231
232 syn cluster dTokens add=dTokenString
233
234 " Numbers
235 "
236 syn case ignore
237
238 syn match dDec display "\<\d[0-9_]*\(u\=l\=\|l\=u\=\)\>"
239
240 " Hex number
241 syn match dHex display "\<0x[0-9a-f_]\+\(u\=l\=\|l\=u\=\)\>"
242
243 syn match dOctal display "\<0[0-7_]\+\(u\=l\=\|l\=u\=\)\>"
244 " flag an octal number with wrong digits
245 syn match dOctalError display "\<0[0-7_]*[89][0-9_]*"
246
247 " binary numbers
248 syn match dBinary display "\<0b[01_]\+\(u\=l\=\|l\=u\=\)\>"
249
250 "floating point without the dot
251 syn match dFloat display "\<\d[0-9_]*\(fi\=\|l\=i\)\>"
252 "floating point number, with dot, optional exponent
253 syn match dFloat display "\<\d[0-9_]*\.[0-9_]*\(e[-+]\=[0-9_]\+\)\=[fl]\=i\="
254 "floating point number, starting with a dot, optional exponent
255 syn match dFloat display "\(\.[0-9_]\+\)\(e[-+]\=[0-9_]\+\)\=[fl]\=i\=\>"
256 "floating point number, without dot, with exponent
257 "syn match dFloat display "\<\d\+e[-+]\=\d\+[fl]\=\>"
258 syn match dFloat display "\<\d[0-9_]*e[-+]\=[0-9_]\+[fl]\=\>"
259
260 "floating point without the dot
261 syn match dHexFloat display "\<0x[0-9a-f_]\+\(fi\=\|l\=i\)\>"
262 "floating point number, with dot, optional exponent
263 syn match dHexFloat display "\<0x[0-9a-f_]\+\.[0-9a-f_]*\(p[-+]\=[0-9_]\+\)\=[fl]\=i\="
264 "floating point number, without dot, with exponent
265 syn match dHexFloat display "\<0x[0-9a-f_]\+p[-+]\=[0-9_]\+[fl]\=i\=\>"
266
267 syn cluster dTokens add=dDec,dHex,dOctal,dOctalError,dBinary,dFloat,dHexFloat
268
269 syn case match
270
271 " Pragma (preprocessor) support
272 " TODO: Highlight following Integer and optional Filespec.
273 syn region dPragma start="#\s*\(line\>\)" skip="\\$" end="$"
274
275
276 " The default highlighting.
277 "
278 hi def link dBinary Number
279 hi def link dDec Number
280 hi def link dHex Number
281 hi def link dOctal Number
282 hi def link dFloat Float
283 hi def link dHexFloat Float
284 hi def link dDebug Debug
285 hi def link dBranch Conditional
286 hi def link dConditional Conditional
287 hi def link dLabel Label
288 hi def link dUserLabel Label
289 hi def link dRepeat Repeat
290 hi def link dExceptions Exception
291 hi def link dAssert Statement
292 hi def link dStatement Statement
293 hi def link dScopeDecl dStorageClass
294 hi def link dStorageClass StorageClass
295 hi def link dBoolean Boolean
296 hi def link dUnicode Special
297 hi def link dTokenStringBrack String
298 hi def link dHereString String
299 hi def link dNestString String
300 hi def link dDelimString String
301 hi def link dRawString String
302 hi def link dString String
303 hi def link dHexString String
304 hi def link dCharacter Character
305 hi def link dEscSequence SpecialChar
306 hi def link dSpecialCharError Error
307 hi def link dOctalError Error
308 hi def link dOperator Operator
309 hi def link dOpOverload Identifier
310 hi def link dConstant Constant
311 hi def link dTypedef Typedef
312 hi def link dEnum Structure
313 hi def link dStructure Structure
314 hi def link dTodo Todo
315 hi def link dType Type
316 hi def link dLineComment Comment
317 hi def link dBlockComment Comment
318 hi def link dNestedComment Comment
319 hi def link dExternal Include
320 hi def link dPragma PreProc
321 hi def link dAnnotation PreProc
322 hi def link dAttribute StorageClass
323 hi def link dIdentifier Identifier
324 hi def link dVersionIdentifier Identifier
325 hi def link dVersion dStatement
326 hi def link dScopeIdentifier dStatement
327 hi def link dScope dStorageClass
328
329 let b:current_syntax = "d"
330
331 " Marks contents of the asm statment body as special
332
333 syn match dAsmStatement "\<asm\>"
334 syn region dAsmBody start="asm[\n]*\s*{"hs=e+1 end="}"he=e-1 contains=dAsmStatement,dAsmOpCode
335
336 hi def link dAsmBody dUnicode
337 hi def link dAsmStatement dStatement
338 hi def link dAsmOpCode Identifier
339
340 syn keyword dAsmOpCode contained aaa aad aam aas adc
341 syn keyword dAsmOpCode contained add addpd addps addsd addss
342 syn keyword dAsmOpCode contained and andnpd andnps andpd andps
343 syn keyword dAsmOpCode contained arpl bound bsf bsr bswap
344 syn keyword dAsmOpCode contained bt btc btr bts call
345 syn keyword dAsmOpCode contained cbw cdq clc cld clflush
346 syn keyword dAsmOpCode contained cli clts cmc cmova cmovae
347 syn keyword dAsmOpCode contained cmovb cmovbe cmovc cmove cmovg
348 syn keyword dAsmOpCode contained cmovge cmovl cmovle cmovna cmovnae
349 syn keyword dAsmOpCode contained cmovnb cmovnbe cmovnc cmovne cmovng
350 syn keyword dAsmOpCode contained cmovnge cmovnl cmovnle cmovno cmovnp
351 syn keyword dAsmOpCode contained cmovns cmovnz cmovo cmovp cmovpe
352 syn keyword dAsmOpCode contained cmovpo cmovs cmovz cmp cmppd
353 syn keyword dAsmOpCode contained cmpps cmps cmpsb cmpsd cmpss
354 syn keyword dAsmOpCode contained cmpsw cmpxch8b cmpxchg comisd comiss
355 syn keyword dAsmOpCode contained cpuid cvtdq2pd cvtdq2ps cvtpd2dq cvtpd2pi
356 syn keyword dAsmOpCode contained cvtpd2ps cvtpi2pd cvtpi2ps cvtps2dq cvtps2pd
357 syn keyword dAsmOpCode contained cvtps2pi cvtsd2si cvtsd2ss cvtsi2sd cvtsi2ss
358 syn keyword dAsmOpCode contained cvtss2sd cvtss2si cvttpd2dq cvttpd2pi cvttps2dq
359 syn keyword dAsmOpCode contained cvttps2pi cvttsd2si cvttss2si cwd cwde
360 syn keyword dAsmOpCode contained da daa das db dd
361 syn keyword dAsmOpCode contained de dec df di div
362 syn keyword dAsmOpCode contained divpd divps divsd divss dl
363 syn keyword dAsmOpCode contained dq ds dt dw emms
364 syn keyword dAsmOpCode contained enter f2xm1 fabs fadd faddp
365 syn keyword dAsmOpCode contained fbld fbstp fchs fclex fcmovb
366 syn keyword dAsmOpCode contained fcmovbe fcmove fcmovnb fcmovnbe fcmovne
367 syn keyword dAsmOpCode contained fcmovnu fcmovu fcom fcomi fcomip
368 syn keyword dAsmOpCode contained fcomp fcompp fcos fdecstp fdisi
369 syn keyword dAsmOpCode contained fdiv fdivp fdivr fdivrp feni
370 syn keyword dAsmOpCode contained ffree fiadd ficom ficomp fidiv
371 syn keyword dAsmOpCode contained fidivr fild fimul fincstp finit
372 syn keyword dAsmOpCode contained fist fistp fisub fisubr fld
373 syn keyword dAsmOpCode contained fld1 fldcw fldenv fldl2e fldl2t
374 syn keyword dAsmOpCode contained fldlg2 fldln2 fldpi fldz fmul
375 syn keyword dAsmOpCode contained fmulp fnclex fndisi fneni fninit
376 syn keyword dAsmOpCode contained fnop fnsave fnstcw fnstenv fnstsw
377 syn keyword dAsmOpCode contained fpatan fprem fprem1 fptan frndint
378 syn keyword dAsmOpCode contained frstor fsave fscale fsetpm fsin
379 syn keyword dAsmOpCode contained fsincos fsqrt fst fstcw fstenv
380 syn keyword dAsmOpCode contained fstp fstsw fsub fsubp fsubr
381 syn keyword dAsmOpCode contained fsubrp ftst fucom fucomi fucomip
382 syn keyword dAsmOpCode contained fucomp fucompp fwait fxam fxch
383 syn keyword dAsmOpCode contained fxrstor fxsave fxtract fyl2x fyl2xp1
384 syn keyword dAsmOpCode contained hlt idiv imul in inc
385 syn keyword dAsmOpCode contained ins insb insd insw int
386 syn keyword dAsmOpCode contained into invd invlpg iret iretd
387 syn keyword dAsmOpCode contained ja jae jb jbe jc
388 syn keyword dAsmOpCode contained jcxz je jecxz jg jge
389 syn keyword dAsmOpCode contained jl jle jmp jna jnae
390 syn keyword dAsmOpCode contained jnb jnbe jnc jne jng
391 syn keyword dAsmOpCode contained jnge jnl jnle jno jnp
392 syn keyword dAsmOpCode contained jns jnz jo jp jpe
393 syn keyword dAsmOpCode contained jpo js jz lahf lar
394 syn keyword dAsmOpCode contained ldmxcsr lds lea leave les
395 syn keyword dAsmOpCode contained lfence lfs lgdt lgs lidt
396 syn keyword dAsmOpCode contained lldt lmsw lock lods lodsb
397 syn keyword dAsmOpCode contained lodsd lodsw loop loope loopne
398 syn keyword dAsmOpCode contained loopnz loopz lsl lss ltr
399 syn keyword dAsmOpCode contained maskmovdqu maskmovq maxpd maxps maxsd
400 syn keyword dAsmOpCode contained maxss mfence minpd minps minsd
401 syn keyword dAsmOpCode contained minss mov movapd movaps movd
402 syn keyword dAsmOpCode contained movdq2q movdqa movdqu movhlps movhpd
403 syn keyword dAsmOpCode contained movhps movlhps movlpd movlps movmskpd
404 syn keyword dAsmOpCode contained movmskps movntdq movnti movntpd movntps
405 syn keyword dAsmOpCode contained movntq movq movq2dq movs movsb
406 syn keyword dAsmOpCode contained movsd movss movsw movsx movupd
407 syn keyword dAsmOpCode contained movups movzx mul mulpd mulps
408 syn keyword dAsmOpCode contained mulsd mulss neg nop not
409 syn keyword dAsmOpCode contained or orpd orps out outs
410 syn keyword dAsmOpCode contained outsb outsd outsw packssdw packsswb
411 syn keyword dAsmOpCode contained packuswb paddb paddd paddq paddsb
412 syn keyword dAsmOpCode contained paddsw paddusb paddusw paddw pand
413 syn keyword dAsmOpCode contained pandn pavgb pavgw pcmpeqb pcmpeqd
414 syn keyword dAsmOpCode contained pcmpeqw pcmpgtb pcmpgtd pcmpgtw pextrw
415 syn keyword dAsmOpCode contained pinsrw pmaddwd pmaxsw pmaxub pminsw
416 syn keyword dAsmOpCode contained pminub pmovmskb pmulhuw pmulhw pmullw
417 syn keyword dAsmOpCode contained pmuludq pop popa popad popf
418 syn keyword dAsmOpCode contained popfd por prefetchnta prefetcht0 prefetcht1
419 syn keyword dAsmOpCode contained prefetcht2 psadbw pshufd pshufhw pshuflw
420 syn keyword dAsmOpCode contained pshufw pslld pslldq psllq psllw
421 syn keyword dAsmOpCode contained psrad psraw psrld psrldq psrlq
422 syn keyword dAsmOpCode contained psrlw psubb psubd psubq psubsb
423 syn keyword dAsmOpCode contained psubsw psubusb psubusw psubw punpckhbw
424 syn keyword dAsmOpCode contained punpckhdq punpckhqdq punpckhwd punpcklbw punpckldq
425 syn keyword dAsmOpCode contained punpcklqdq punpcklwd push pusha pushad
426 syn keyword dAsmOpCode contained pushf pushfd pxor rcl rcpps
427 syn keyword dAsmOpCode contained rcpss rcr rdmsr rdpmc rdtsc
428 syn keyword dAsmOpCode contained rep repe repne repnz repz
429 syn keyword dAsmOpCode contained ret retf rol ror rsm
430 syn keyword dAsmOpCode contained rsqrtps rsqrtss sahf sal sar
431 syn keyword dAsmOpCode contained sbb scas scasb scasd scasw
432 syn keyword dAsmOpCode contained seta setae setb setbe setc
433 syn keyword dAsmOpCode contained sete setg setge setl setle
434 syn keyword dAsmOpCode contained setna setnae setnb setnbe setnc
435 syn keyword dAsmOpCode contained setne setng setnge setnl setnle
436 syn keyword dAsmOpCode contained setno setnp setns setnz seto
437 syn keyword dAsmOpCode contained setp setpe setpo sets setz
438 syn keyword dAsmOpCode contained sfence sgdt shl shld shr
439 syn keyword dAsmOpCode contained shrd shufpd shufps sidt sldt
440 syn keyword dAsmOpCode contained smsw sqrtpd sqrtps sqrtsd sqrtss
441 syn keyword dAsmOpCode contained stc std sti stmxcsr stos
442 syn keyword dAsmOpCode contained stosb stosd stosw str sub
443 syn keyword dAsmOpCode contained subpd subps subsd subss sysenter
444 syn keyword dAsmOpCode contained sysexit test ucomisd ucomiss ud2
445 syn keyword dAsmOpCode contained unpckhpd unpckhps unpcklpd unpcklps verr
446 syn keyword dAsmOpCode contained verw wait wbinvd wrmsr xadd
447 syn keyword dAsmOpCode contained xchg xlat xlatb xor xorpd
448 syn keyword dAsmOpCode contained xorps
449 syn keyword dAsmOpCode contained addsubpd addsubps fisttp haddpd haddps
450 syn keyword dAsmOpCode contained hsubpd hsubps lddqu monitor movddup
451 syn keyword dAsmOpCode contained movshdup movsldup mwait
452 syn keyword dAsmOpCode contained pavgusb pf2id pfacc pfadd pfcmpeq
453 syn keyword dAsmOpCode contained pfcmpge pfcmpgt pfmax pfmin pfmul
454 syn keyword dAsmOpCode contained pfnacc pfpnacc pfrcp pfrcpit1 pfrcpit2
455 syn keyword dAsmOpCode contained pfrsqit1 pfrsqrt pfsub pfsubr pi2fd
456 syn keyword dAsmOpCode contained pmulhrw pswapd
457