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