Upstream version 11.39.250.0
[platform/framework/web/crosswalk.git] / src / native_client / src / trusted / validator_ragel / spec.py
1 #!/usr/bin/python
2 # Copyright (c) 2013 The Native Client Authors. All rights reserved.
3 # Use of this source code is governed by a BSD-style license that can be
4 # found in the LICENSE file.
5
6 # Executable specification of valid instructions and superinstructions (in terms
7 # of their disassembler listing).
8 # Should serve as formal and up-to-date ABI reference and as baseline for
9 # validator exhaustive tests.
10
11 # It is generally organized as a set of functions responsible for recognizing
12 # and validating specific patterns (jump instructions, regular instructions,
13 # superinstructions, etc.)
14 # There are three outcomes for running such function:
15 #   - function raises DoNotMatchError (which means instruction is of completely
16 #     different structure, for example when we call ValidateSuperinstruction on
17 #     nop)
18 #   - function raises SandboxingError (which means instruction generally matches
19 #     respective pattern, but some rules are violated)
20 #   - function returns (which means instruction(s) is(are) safe)
21 #
22 # Why exceptions instead of returning False or something? Because they carry
23 # stack traces, which makes it easier to investigate why particular instruction
24 # was rejected.
25 # Why distinguish DoNotMatchError and SandboxingError? Because on the topmost
26 # level we attempt to call all matchers and we need to see which error message
27 # was most relevant.
28
29 import re
30
31
32 class DoNotMatchError(Exception):
33   pass
34
35
36 class SandboxingError(Exception):
37   pass
38
39
40 BUNDLE_SIZE = 32
41
42
43 def _ValidateLongNop(instruction):
44   # Short nops do not require special exceptions (such as allowing repeated
45   # prefixes and segment access), so they are handled as regular instructions.
46   if re.match(r'nopw 0x0\(%[er]ax,%[er]ax,1\)$',
47       instruction.disasm):
48     return
49   if re.match(
50       r'(data32 )*nopw %cs:0x0\(%[er]ax,%[er]ax,1\)$',
51       instruction.disasm):
52     return
53   raise DoNotMatchError(instruction)
54
55
56 def _ValidateStringInstruction(instruction):
57   prefix_re = r'(rep |repz |repnz )?'
58   lods_re = r'lods %ds:\(%esi\),(%al|%ax|%eax)'
59   stos_re = r'stos (%al|%ax|%eax),%es:\(%edi\)'
60   scas_re = r'scas %es:\(%edi\),(%al|%ax|%eax)'
61   movs_re = r'movs[bwl] %ds:\(%esi\),%es:\(%edi\)'
62   cmps_re = r'cmps[bwl] %es:\(%edi\),%ds:\(%esi\)'
63
64   string_insn_re = '%s(%s)$' % (
65       prefix_re,
66       '|'.join([lods_re, stos_re, scas_re, movs_re, cmps_re]))
67
68   if re.match(string_insn_re, instruction.disasm):
69     return
70
71   raise DoNotMatchError(instruction)
72
73
74 def _ValidateTlsInstruction(instruction):
75   if re.match(r'mov %gs:(0x0|0x4),%e[a-z][a-z]$', instruction.disasm):
76     return
77
78   raise DoNotMatchError(instruction)
79
80
81 # What can follow 'j' in conditional jumps 'je', 'jno', etc.
82 _CONDITION_SUFFIX_RE = r'(a(e?)|b(e?)|g(e?)|l(e?)|(n?)e|(n?)o|(n?)p|(n?)s)'
83
84
85 def _AnyRegisterRE(group_name='register'):
86   # TODO(shcherbina): explicitly list all kinds of registers we care to
87   # distinguish for validation purposes.
88   return r'(?P<%s>%%(st\(\d+\)|\w+))' % group_name
89
90
91 def _HexRE(group_name='value'):
92   return r'(?P<%s>-?0x[\da-f]+)' % group_name
93
94
95 def _ImmediateRE(group_name='immediate'):
96   return r'(?P<%s>\$%s)' % (
97       group_name,
98       _HexRE(group_name=group_name + '_value'))
99
100
101 def _MemoryRE(group_name='memory'):
102   # Possible forms:
103   #   (%eax)
104   #   (%eax,%ebx,1)
105   #   (,%ebx,1)
106   #   0x42(...)
107   # and even
108   #   0x42
109   return r'(?P<%s>(?P<%s_segment>%%[cdefgs]s:)?%s?(\(%s?(,%s,\d)?\))?)' % (
110       group_name,
111       group_name,
112       _HexRE(group_name=group_name + '_offset'),
113       _AnyRegisterRE(group_name=group_name + '_base'),
114       _AnyRegisterRE(group_name=group_name + '_index'))
115
116
117 def _IndirectJumpTargetRE(group_name='target'):
118   return r'(?P<%s>\*(%s|%s))' % (
119       group_name,
120       _AnyRegisterRE(group_name=group_name + '_register'),
121       _MemoryRE(group_name=group_name + '_memory'))
122
123
124 def _OperandRE(group_name='operand'):
125   return r'(?P<%s>%s|%s|%s|%s)' % (
126       group_name,
127       _AnyRegisterRE(group_name=group_name + '_register'),
128       _ImmediateRE(group_name=group_name + '_immediate'),
129       _MemoryRE(group_name=group_name + '_memory'),
130       _IndirectJumpTargetRE(group_name=group_name + '_target'))
131
132
133 def _SplitOps(insn, args):
134   # We can't use just args.split(',') because operands can contain commas
135   # themselves, for example '(%r15,%rax,1)'.
136   ops = []
137   i = 0
138   while True:
139     # We do not use mere re.match(_OperandRE(), args, i) here because
140     # python backtracking regexes do not guarantee to find longest match.
141     m = re.compile(r'(%s)($|,)' % _OperandRE()).match(args, i)
142     assert m is not None, (args, i)
143     ops.append(m.group(1))
144     i = m.end(1)
145     if i == len(args):
146       break
147     assert args[i] == ',', (insn, args, i)
148     i += 1
149   return ops
150
151
152 def _ParseInstruction(instruction):
153   # Strip comment.
154   disasm, _, _ = instruction.disasm.partition('#')
155   elems = disasm.split()
156
157   if elems == []:
158     raise SandboxingError(
159         'disasm is empty', instruction)
160
161   prefixes = []
162   while elems != [] and elems[0] in [
163       'lock', 'rep', 'repz', 'repnz',
164       'data16', 'data32', 'addr16', 'addr32', 'addr64']:
165     prefixes.append(elems.pop(0))
166
167   if elems == []:
168     raise SandboxingError(
169         'dangling legacy prefixes', instruction)
170
171   name = elems[0]
172
173   if re.match(r'rex([.]W?R?X?B?)?$', name):
174     raise SandboxingError('dangling rex prefix', instruction)
175
176   # There could be branching expectation information in instruction names:
177   #    jo,pt      <addr>
178   #    jge,pn     <addr>
179   name_re = r'[a-z]\w*(,p[nt])?$'
180   assert re.match(name_re, name) or name == "nop/reserved", name
181
182   if len(elems) == 1:
183     ops = []
184   elif len(elems) == 2:
185     ops = _SplitOps(instruction, elems[1])
186   else:
187     assert False, instruction
188
189   return prefixes, name, ops
190
191
192 REG32_TO_REG64 = {
193     '%eax' : '%rax',
194     '%ebx' : '%rbx',
195     '%ecx' : '%rcx',
196     '%edx' : '%rdx',
197     '%esi' : '%rsi',
198     '%edi' : '%rdi',
199     '%esp' : '%rsp',
200     '%ebp' : '%rbp',
201     '%r8d' : '%r8',
202     '%r9d' : '%r9',
203     '%r10d' : '%r10',
204     '%r11d' : '%r11',
205     '%r12d' : '%r12',
206     '%r13d' : '%r13',
207     '%r14d' : '%r14',
208     '%r15d' : '%r15'}
209
210 REGS32 = REG32_TO_REG64.keys()
211 REGS64 = REG32_TO_REG64.values()
212
213
214 class Condition(object):
215   """Represents assertion about the state of 64-bit registers.
216
217   (used as precondition and postcondition)
218
219   Supported assertions:
220     0. %rpb and %rsp are sandboxed (and nothing is known about other registers)
221     1. {%rax} is restricted, %rbp and %rsp are sandboxed
222     2-13. same for %rbx-%r14 not including %rbp and %rsp
223     14. %rbp is restricted, %rsp is sandboxed
224     15. %rsp is restricted, %rpb is sandboxed
225
226   It can be observed that all assertions 1..15 differ from default 0 in a single
227   register, which prompts internal representation of a single field,
228   _restricted_register, which stores name of this standing out register
229   (or None).
230
231   * 'restricted' means higher 32 bits are zeroes
232   * 'sandboxed' means within [%r15, %r15 + 2**32) range
233   It goes without saying that %r15 is never changed and by definition sandboxed.
234   """
235
236   def __init__(self, restricted=None, restricted_instead_of_sandboxed=None):
237     self._restricted_register = None
238     if restricted is not None:
239       assert restricted_instead_of_sandboxed is None
240       assert restricted in REGS64
241       assert restricted not in ['%r15', '%rbp', '%rsp']
242       self._restricted_register = restricted
243     if restricted_instead_of_sandboxed is not None:
244       assert restricted is None
245       assert restricted_instead_of_sandboxed in ['%rbp', '%rsp']
246       self._restricted_register = restricted_instead_of_sandboxed
247
248   def GetAlteredRegisters(self):
249     """ Return pair (restricted, restricted_instead_of_sandboxed).
250
251     Each item is either register name or None.
252     """
253     if self._restricted_register is None:
254       return None, None
255     elif self._restricted_register in ['%rsp', '%rbp']:
256       return None, self._restricted_register
257     else:
258       return self._restricted_register, None
259
260   def __eq__(self, other):
261     return self._restricted_register == other._restricted_register
262
263   def __ne__(self, other):
264     return not self == other
265
266   def Implies(self, other):
267     return self.WhyNotImplies(other) is None
268
269   def WhyNotImplies(self, other):
270     if other._restricted_register is None:
271       if self._restricted_register in ['%rbp', '%rsp']:
272         return '%s should not be restricted' % self._restricted_register
273       else:
274         return None
275     else:
276       if self._restricted_register != other._restricted_register:
277         return (
278             'register %s should be restricted, '
279             'while in fact %r is restricted' % (
280                 other._restricted_register, self._restricted_register))
281       else:
282         return None
283
284   def __repr__(self):
285     if self._restricted_register is None:
286       return 'Condition(default)'
287     elif self._restricted_register in ['%rbp', '%rsp']:
288       return ('Condition(%s restricted instead of sandboxed)'
289               % self._restricted_register)
290     else:
291       return 'Condition(%s restricted)' % self._restricted_register
292
293   @staticmethod
294   def All():
295     yield Condition()
296     for reg in REGS64:
297       if reg not in ['%r15', '%rbp', '%rsp']:
298         yield Condition(restricted=reg)
299     yield Condition(restricted_instead_of_sandboxed='%rbp')
300     yield Condition(restricted_instead_of_sandboxed='%rsp')
301
302
303 def _ValidateSpecialStackInstruction(instruction):
304   # Validate 64-bit instruction that is in special relationship with rsp/rbp.
305
306   if instruction.disasm in ['mov %rsp,%rbp', 'mov %rbp,%rsp']:
307     return Condition(), Condition()
308
309   m = re.match(
310       'and %s,%%rsp$' % _ImmediateRE(),
311       instruction.disasm)
312   if m is not None:
313     # We only allow 1-byte immediate, so we have to look at machine code.
314     if (len(instruction.bytes) == 4 and
315         0x48 <= instruction.bytes[0] <= 0x4f and
316         instruction.bytes[1:3] == [0x83, 0xe4]):
317       # We extract mask from bytes, not from textual representation, because
318       # objdump and RDFA decoder print it differently
319       # (-1 is displayed as '0xffffffffffffffff' by objdump and as '0xff' by
320       # RDFA decoder).
321       # See https://code.google.com/p/nativeclient/issues/detail?id=3164
322       mask = instruction.bytes[3]
323       assert mask == int(m.group('immediate_value'), 16) & 0xff
324       if mask < 0x80:
325         raise SandboxingError(
326             'mask should be negative to ensure that higher '
327             'bits of %rsp do not change',
328             instruction)
329     else:
330       raise SandboxingError(
331           'unsupported form of "and <mask>,%rsp" instruction', instruction)
332     return Condition(), Condition()
333
334   if (instruction.disasm in ['add %r15,%rbp', 'add %r15,%rbp'] or
335       re.match(r'lea (0x0+)?\(%rbp,%r15,1\),%rbp$', instruction.disasm)):
336     return Condition(restricted_instead_of_sandboxed='%rbp'), Condition()
337
338   if (instruction.disasm in ['add %r15,%rsp', 'add %r15,%rsp'] or
339       re.match(r'lea (0x0+)?\(%rsp,%r15,1\),%rsp$', instruction.disasm)):
340     return Condition(restricted_instead_of_sandboxed='%rsp'), Condition()
341
342   # TODO(shcherbina): disallow this instruction once
343   # http://code.google.com/p/nativeclient/issues/detail?id=3070
344   # is fixed.
345   if instruction.disasm == 'or %r15,%rsp':
346     return Condition(restricted_instead_of_sandboxed='%rsp'), Condition()
347
348   raise DoNotMatchError(instruction)
349
350
351 def _GetLegacyPrefixes(instruction):
352   result = []
353   for b in instruction.bytes:
354     if b not in [
355         0x66, 0x67, 0x2e, 0x3e, 0x26, 0x64, 0x65, 0x36, 0xf0, 0xf3, 0xf2]:
356       break
357     if b == 0x67:
358       raise SandboxingError('addr prefix is not allowed', instruction)
359     if b in result:
360       raise SandboxingError('duplicate legacy prefix', instruction)
361     result.append(b)
362   return result
363
364
365 def _ProcessMemoryAccess(instruction, operands):
366   """Make sure that memory access is valid and return precondition required.
367
368   (only makes sense for 64-bit instructions)
369
370   Args:
371     instruction: Instruction tuple
372     operands: list of instruction operands as strings, for example
373               ['%eax', '(%r15,%rbx,1)']
374   Returns:
375     Condition object representing precondition required for memory access (if
376     it's present among operands) to be valid.
377   Raises:
378     SandboxingError if memory access is invalid.
379   """
380   precondition = Condition()
381   for op in operands:
382     m = re.match(_MemoryRE() + r'$', op)
383     if m is not None:
384       assert m.group('memory_segment') is None
385       base = m.group('memory_base')
386       index = m.group('memory_index')
387       allowed_bases = ['%r15', '%rbp', '%rsp', '%rip']
388       if base not in allowed_bases:
389         raise SandboxingError(
390             'memory access only is allowed with base from %s'
391             % allowed_bases,
392             instruction)
393       if index is not None:
394         if index == '%riz':
395           pass
396         elif index in REGS64:
397           if index in ['%r15', '%rsp', '%rbp']:
398             raise SandboxingError(
399                 '%s can\'t be used as index in memory access' % index,
400                 instruction)
401           else:
402             assert precondition == Condition()
403             precondition = Condition(restricted=index)
404         else:
405           raise SandboxingError(
406               'unrecognized register is used for memory access as index',
407               instruction)
408   return precondition
409
410
411 def _ProcessOperandWrites(instruction, write_operands, zero_extending=False):
412   """Check that writes to operands are valid, return postcondition established.
413
414   (only makes sense for 64-bit instructions)
415
416   Args:
417     instruction: Instruction tuple
418     write_operands: list of operands instruction writes to as strings,
419                     for example ['%eax', '(%r15,%rbx,1)']
420     zero_extending: whether instruction is considered zero extending
421   Returns:
422     Condition object representing postcondition established by operand writes.
423   Raises:
424     SandboxingError if write is invalid.
425   """
426   postcondition = Condition()
427   for i, op in enumerate(write_operands):
428     if op in ['%r15', '%r15d', '%r15w', '%r15b']:
429       raise SandboxingError('changes to r15 are not allowed', instruction)
430     if op in ['%bpl', '%bp', '%rbp']:
431       raise SandboxingError('changes to rbp are not allowed', instruction)
432     if op in ['%spl', '%sp', '%rsp']:
433       raise SandboxingError('changes to rsp are not allowed', instruction)
434
435     if op in REGS32:
436       # Only last of the operand writes is considered zero-extending.
437       # For example,
438       #   xchg %eax, (%rbp)
439       # does not zero-extend %rax.
440       if zero_extending and i == len(write_operands) - 1:
441         r = REG32_TO_REG64[op]
442         if r in ['%rbp', '%rsp']:
443           postcondition = Condition(restricted_instead_of_sandboxed=r)
444         else:
445           postcondition = Condition(restricted=r)
446       else:
447         if op in ['%ebp', '%esp']:
448           raise SandboxingError(
449               'non-zero-extending changes to ebp and esp are not allowed',
450               instruction)
451
452   return postcondition
453
454
455 def _InstructionNameIn(name, candidates):
456   return re.match('(%s)[bwlq]?$' % '|'.join(candidates), name) is not None
457
458
459 _X87_INSTRUCTIONS = set([
460   'f2xm1',
461   'fabs',
462   'fadd', 'fadds', 'faddl', 'faddp',
463   'fiadd', 'fiaddl',
464   'fbld',
465   'fbstp',
466   'fchs',
467   'fnclex',
468   'fcmovb', 'fcmovbe', 'fcmove', 'fcmovnb',
469   'fcmovnbe', 'fcmovne', 'fcmovnu', 'fcmovu',
470   'fcom', 'fcoms', 'fcoml',
471   'fcomp', 'fcomps', 'fcompl',
472   'fcompp',
473   'fcomi',
474   'fcomip',
475   'fcos',
476   'fdecstp',
477   'fdiv', 'fdivs', 'fdivl',
478   'fdivp',
479   'fdivr', 'fdivrs', 'fdivrl',
480   'fdivrp',
481   'fidiv', 'fidivl',
482   'fidivp',
483   'fidivr', 'fidivrl',
484   'ffree',
485   'ficom', 'ficoml',
486   'ficomp', 'ficompl',
487   'fild', 'fildl', 'fildll',
488   'fincstp',
489   'fninit',
490   'fist', 'fistl',
491   'fistp', 'fistpl', 'fistpll',
492   'fisttp', 'fisttpl', 'fisttpll',
493   'fld', 'flds', 'fldl', 'fldt',
494   'fld1',
495   'fldcw',
496   'fldenv',
497   'fldl2e',
498   'fldl2t',
499   'fldlg2',
500   'fldln2',
501   'fldpi',
502   'fldz',
503   'fmul', 'fmuls', 'fmull',
504   'fmulp',
505   'fimul', 'fimull',
506   'fnop',
507   'fpatan',
508   'fprem',
509   'fprem1',
510   'fptan',
511   'frndint',
512   'frstor',
513   'fnsave',
514   'fscale',
515   'fsin',
516   'fsincos',
517   'fsqrt',
518   'fst', 'fsts', 'fstl',
519   'fstp', 'fstps', 'fstpl', 'fstpt',
520   'fnstcw',
521   'fnstenv',
522   'fnstsw',
523   'fsub', 'fsubs', 'fsubl',
524   'fsubp',
525   'fsubr', 'fsubrs', 'fsubrl',
526   'fsubrp',
527   'fisub', 'fisubl',
528   'fisubr', 'fisubrl',
529   'ftst',
530   'fucom', 'fucomp', 'fucompp',
531   'fucomi', 'fucomip',
532   'fwait',
533   'fxam',
534   'fxch',
535   'fxtract',
536   'fyl2x',
537   'fyl2xp1',
538 ])
539
540
541 # Instructions from mmx_instructions.def (besides MMX, they include SSE2/3
542 # and other stuff that works with MMX registers).
543 _MMX_INSTRUCTIONS = set([
544   'cvtpd2pi',
545   'cvtpi2pd',
546   'cvtpi2ps',
547   'cvtps2pi',
548   'cvttpd2pi',
549   'cvttps2pi',
550   'emms',
551   'femms',
552   'frstor',
553   'fnsave',
554   'movntq',
555   'movdq2q',
556   'movq2dq',
557   'pabsb',
558   'pabsd',
559   'pabsw',
560   'packssdw',
561   'packsswb',
562   'packuswb',
563   'paddb',
564   'paddd',
565   'paddq',
566   'paddsb',
567   'paddsw',
568   'paddusb',
569   'paddusw',
570   'paddw',
571   'palignr',
572   'pand',
573   'pandn',
574   'pavgb',
575   'pavgusb',
576   'pavgw',
577   'pcmpeqb',
578   'pcmpeqd',
579   'pcmpeqw',
580   'pcmpgtb',
581   'pcmpgtd',
582   'pcmpgtw',
583   'pextrw',
584   'pf2id',
585   'pf2iw',
586   'pfacc',
587   'pfadd',
588   'pfcmpeq',
589   'pfcmpge',
590   'pfcmpgt',
591   'pfmax',
592   'pfmin',
593   'pfmul',
594   'pfnacc',
595   'pfpnacc',
596   'pfrcp',
597   'pfrcpit1',
598   'pfrcpit2',
599   'pfrsqit1',
600   'pfrsqrt',
601   'pfsub',
602   'pfsubr',
603   'phaddd',
604   'phaddsw',
605   'phaddw',
606   'phsubd',
607   'phsubsw',
608   'phsubw',
609   'pi2fd',
610   'pi2fw',
611   'pinsrw',
612   'pmaddubsw',
613   'pmaddwd',
614   'pmaxsw',
615   'pmaxub',
616   'pminsw',
617   'pminub',
618   'pmovmskb',
619   'pmulhrw',
620   'pmulhuw',
621   'pmulhw',
622   'pmulhrsw',
623   'pmullw',
624   'pmuludq',
625   'por',
626   'psadbw',
627   'pshufb',
628   'pshufw',
629   'psignb',
630   'psignd',
631   'psignw',
632   'pslld',
633   'psllq',
634   'psllw',
635   'psrad',
636   'psraw',
637   'psrld',
638   'psrlq',
639   'psrlw',
640   'psubb',
641   'psubd',
642   'psubq',
643   'psubsb',
644   'psubsw',
645   'psubusb',
646   'psubusw',
647   'psubw',
648   'pswapd',
649   'punpckhbw',
650   'punpckhdq',
651   'punpckhwd',
652   'punpcklbw',
653   'punpckldq',
654   'punpcklwd',
655   'pxor',
656 ])
657
658
659 # Instructions from xmm_instructions.def (that is, instructions that work
660 # with XMM registers). These instruction names can be prepended with 'v', which
661 # results in their AVX counterpart.
662 _XMM_AVX_INSTRUCTIONS = set([
663   'addpd',
664   'addps',
665   'addsd',
666   'addss',
667   'addsubpd',
668   'addsubps',
669   'aesdec',
670   'aesdeclast',
671   'aesenc',
672   'aesenclast',
673   'aesimc',
674   'aeskeygenassist',
675   'andnpd',
676   'andnps',
677   'andpd',
678   'andps',
679   'blendpd',
680   'blendps',
681   'blendvpd',
682   'blendvps',
683   'comisd',
684   'comiss',
685   'cvtdq2pd',
686   'cvtdq2ps',
687   'cvtpd2dq',
688   'cvtpd2ps',
689   'cvtps2dq',
690   'cvtps2pd',
691   'cvtsd2si',
692   'cvtsd2ss',
693   'cvtsi2sd', 'cvtsi2sdl', 'cvtsi2sdq',
694   'cvtsi2ss', 'cvtsi2ssl', 'cvtsi2ssq',
695   'cvtss2sd',
696   'cvtss2si',
697   'cvttpd2dq',
698   'cvttps2dq',
699   'cvttsd2si',
700   'cvttss2si',
701   'divpd',
702   'divps',
703   'divsd',
704   'divss',
705   'dppd',
706   'dpps',
707   'extractps',
708   'extrq',
709   'haddpd',
710   'haddps',
711   'hsubpd',
712   'hsubps',
713   'insertps',
714   'insertq',
715   'lddqu',
716   'ldmxcsr',
717   'maxpd',
718   'maxps',
719   'maxsd',
720   'maxss',
721   'minpd',
722   'minps',
723   'minsd',
724   'minss',
725   'movapd',
726   'movaps',
727   'movddup',
728   'movdqa',
729   'movdqu',
730   'movhlps',
731   'movhpd',
732   'movhps',
733   'movlhps',
734   'movlpd',
735   'movlps',
736   'movmskpd',
737   'movmskps',
738   'movntdq',
739   'movntdqa',
740   'movntpd',
741   'movntps',
742   'movsd',
743   'movshdup',
744   'movsldup',
745   'movss',
746   'movupd',
747   'movups',
748   'mpsadbw',
749   'mulpd',
750   'mulps',
751   'mulsd',
752   'mulss',
753   'orpd',
754   'orps',
755   'pabsb',
756   'pabsd',
757   'pabsw',
758   'packssdw',
759   'packsswb',
760   'packusdw',
761   'packuswb',
762   'paddb',
763   'paddd',
764   'paddq',
765   'paddsb',
766   'paddsw',
767   'paddusb',
768   'paddusw',
769   'paddw',
770   'palignr',
771   'pand',
772   'pandn',
773   'pavgb',
774   'pavgw',
775   'pblendvb',
776   'pblendw',
777   'pclmulqdq',
778   'pclmullqlqdq',
779   'pclmulhqlqdq',
780   'pclmullqhqdq',
781   'pclmulhqhqdq',
782   'pcmpeqb',
783   'pcmpeqd',
784   'pcmpeqq',
785   'pcmpeqw',
786   'pcmpestri',
787   'pcmpestrm',
788   'pcmpgtb',
789   'pcmpgtd',
790   'pcmpgtq',
791   'pcmpgtw',
792   'pcmpistri',
793   'pcmpistrm',
794   'pextrb',
795   'pextrd',
796   'pextrq',
797   'pextrw',
798   'phaddd',
799   'phaddsw',
800   'phaddw',
801   'phminposuw',
802   'phsubd',
803   'phsubsw',
804   'phsubw',
805   'pinsrb',
806   'pinsrd',
807   'pinsrq',
808   'pinsrw',
809   'pmaddubsw',
810   'pmaddwd',
811   'pmaxsb',
812   'pmaxsd',
813   'pmaxsw',
814   'pmaxub',
815   'pmaxud',
816   'pmaxuw',
817   'pminsb',
818   'pminsd',
819   'pminsw',
820   'pminub',
821   'pminud',
822   'pminuw',
823   'pmovmskb',
824   'pmovsxbd',
825   'pmovsxbq',
826   'pmovsxbw',
827   'pmovsxdq',
828   'pmovsxwd',
829   'pmovsxwq',
830   'pmovzxbd',
831   'pmovzxbq',
832   'pmovzxbw',
833   'pmovzxdq',
834   'pmovzxwd',
835   'pmovzxwq',
836   'pmuldq',
837   'pmulhrsw',
838   'pmulhuw',
839   'pmulhw',
840   'pmulld',
841   'pmullw',
842   'pmuludq',
843   'por',
844   'psadbw',
845   'pshufb',
846   'pshufd',
847   'pshufhw',
848   'pshuflw',
849   'psignb',
850   'psignd',
851   'psignw',
852   'pslld',
853   'pslldq',
854   'psllq',
855   'psllw',
856   'psrad',
857   'psraw',
858   'psrld',
859   'psrldq',
860   'psrlq',
861   'psrlw',
862   'psubb',
863   'psubd',
864   'psubq',
865   'psubsb',
866   'psubsw',
867   'psubusb',
868   'psubusw',
869   'psubw',
870   'ptest',
871   'punpckhbw',
872   'punpckhdq',
873   'punpckhqdq',
874   'punpckhwd',
875   'punpcklbw',
876   'punpckldq',
877   'punpcklqdq',
878   'punpcklwd',
879   'pxor',
880   'rcpps',
881   'rcpss',
882   'roundpd',
883   'roundps',
884   'roundsd',
885   'roundss',
886   'rsqrtps',
887   'rsqrtss',
888   'shufpd',
889   'shufps',
890   'sqrtpd',
891   'sqrtps',
892   'sqrtsd',
893   'sqrtss',
894   'stmxcsr',
895   'subpd',
896   'subps',
897   'subsd',
898   'subss',
899   'ucomisd',
900   'ucomiss',
901   'unpckhpd',
902   'unpckhps',
903   'unpcklpd',
904   'unpcklps',
905   'xorpd',
906   'xorps',
907 ])
908
909 _XMM_AVX_INSTRUCTIONS.update(['v' + name for name in _XMM_AVX_INSTRUCTIONS])
910
911 _XMM_AVX_INSTRUCTIONS.update([
912   'movntsd',
913   'movntss',
914   'vbroadcastf128',
915   'vbroadcastsd',
916   'vbroadcastss',
917   'vcvtph2ps',
918   'vcvtps2ph',
919   'vextractf128',
920   'vfrczpd',
921   'vfrczps',
922   'vfrczsd',
923   'vfrczss',
924   'vinsertf128',
925   'vmaskmovpd',
926   'vmaskmovps',
927   'vpcmov',
928   'vpcomb',
929   'vpcomd',
930   'vpcomq',
931   'vpcomub',
932   'vpcomud',
933   'vpcomuq',
934   'vpcomuw',
935   'vpcomw',
936   'vperm2f128',
937   'vpermil2pd',
938   'vpermil2ps',
939   'vpermilpd',
940   'vpermilps',
941   'vphaddbd',
942   'vphaddbq',
943   'vphaddbw',
944   'vphadddq',
945   'vphaddubd',
946   'vphaddubq',
947   'vphaddubw',
948   'vphaddudq',
949   'vphadduwd',
950   'vphadduwq',
951   'vphaddwd',
952   'vphaddwq',
953   'vphsubbw',
954   'vphsubdq',
955   'vphsubwd',
956   'vpmacsdd',
957   'vpmacsdqh',
958   'vpmacsdql',
959   'vpmacssdd',
960   'vpmacssdqh',
961   'vpmacssdql',
962   'vpmacsswd',
963   'vpmacssww',
964   'vpmacswd',
965   'vpmacsww',
966   'vpmadcsswd',
967   'vpmadcswd',
968   'vpperm',
969   'vprotb',
970   'vprotd',
971   'vprotq',
972   'vprotw',
973   'vpshab',
974   'vpshad',
975   'vpshaq',
976   'vpshaw',
977   'vpshlb',
978   'vpshld',
979   'vpshlq',
980   'vpshlw',
981   'vtestpd',
982   'vtestps',
983   'vzeroall',
984   'vzeroupper',
985 ])
986
987 # Add instructions like VFMADDPD/VFMADD132PD/VFMADD213PD/VFMADD231PD.
988 for fma_name in [
989     'vfmadd%spd',
990     'vfmadd%sps',
991     'vfmadd%ssd',
992     'vfmadd%sss',
993     'vfnmadd%spd',
994     'vfnmadd%sps',
995     'vfnmadd%ssd',
996     'vfnmadd%sss',
997     'vfmsub%spd',
998     'vfmsub%sps',
999     'vfmsub%ssd',
1000     'vfmsub%sss',
1001     'vfnmsub%spd',
1002     'vfnmsub%sps',
1003     'vfnmsub%ssd',
1004     'vfnmsub%sss',
1005     'vfmaddsub%spd',
1006     'vfmaddsub%sps',
1007     'vfmsubadd%spd',
1008     'vfmsubadd%sps',
1009     ]:
1010   for operand_order_suffix in ['', '132', '213', '231']:
1011     _XMM_AVX_INSTRUCTIONS.add(fma_name % operand_order_suffix)
1012
1013 for cmp_suffix in ['pd', 'ps', 'sd', 'ss']:
1014   for cmp_op in ['', 'eq', 'lt', 'le', 'unord', 'neq', 'nlt', 'nle', 'ord']:
1015     _XMM_AVX_INSTRUCTIONS.add('cmp%s%s' % (cmp_op, cmp_suffix))
1016     _XMM_AVX_INSTRUCTIONS.add('vcmp%s%s' % (cmp_op, cmp_suffix))
1017   for cmp_op in [
1018       'eq_uq', 'nge', 'ngt', 'false',
1019       'neq_oq', 'ge', 'gt', 'true',
1020       'eq_os', 'lt_oq', 'le_oq', 'unord_s',
1021       'neq_us', 'nlt_uq', 'nle_uq', 'ord_s',
1022       'eq_us', 'nge_uq', 'ngt_uq', 'false_os',
1023       'neq_os', 'ge_oq', 'gt_oq', 'true_us']:
1024     _XMM_AVX_INSTRUCTIONS.add('vcmp%s%s' % (cmp_op, cmp_suffix))
1025
1026
1027 def ValidateRegularInstruction(instruction, bitness):
1028   """Validate regular instruction (not direct jump).
1029
1030   Args:
1031     instruction: objdump_parser.Instruction tuple
1032     bitness: 32 or 64
1033   Returns:
1034     Pair (precondition, postcondition) of Condition instances.
1035     (for 32-bit case they are meaningless and are not used)
1036   Raises:
1037     According to usual convention.
1038   """
1039   assert bitness in [32, 64]
1040
1041   if instruction.disasm.startswith('.byte ') or '(bad)' in instruction.disasm:
1042     raise SandboxingError('objdump failed to decode', instruction)
1043
1044   try:
1045     _ValidateLongNop(instruction)
1046     return Condition(), Condition()
1047   except DoNotMatchError:
1048     pass
1049
1050   # Report error on duplicate prefixes (note that they are allowed in
1051   # long nops).
1052   _GetLegacyPrefixes(instruction)
1053
1054   if bitness == 32:
1055     try:
1056       _ValidateStringInstruction(instruction)
1057       return Condition(), Condition()
1058     except DoNotMatchError:
1059       pass
1060
1061     try:
1062       _ValidateTlsInstruction(instruction)
1063       return Condition(), Condition()
1064     except DoNotMatchError:
1065       pass
1066
1067   if bitness == 64:
1068     try:
1069       return _ValidateSpecialStackInstruction(instruction)
1070     except DoNotMatchError:
1071       pass
1072
1073   prefixes, name, ops = _ParseInstruction(instruction)
1074
1075   for prefix in prefixes:
1076     if prefix != 'lock':
1077       raise SandboxingError('prefix %s is not allowed' % prefix, instruction)
1078
1079   for op in ops:
1080     if op in ['%cs', '%ds', '%es', '%ss', '%fs', '%gs']:
1081       raise SandboxingError(
1082           'access to segment registers is not allowed', instruction)
1083     if op.startswith('%cr'):
1084       raise SandboxingError(
1085           'access to control registers is not allowed', instruction)
1086     if op.startswith('%db'):
1087       raise SandboxingError(
1088           'access to debug registers is not allowed', instruction)
1089     if op.startswith('%tr'):
1090       raise SandboxingError(
1091           'access to test registers is not allowed', instruction)
1092
1093     m = re.match(_MemoryRE() + r'$', op)
1094     if m is not None and m.group('memory_segment') is not None:
1095       raise SandboxingError(
1096           'segments in memory references are not allowed', instruction)
1097
1098
1099   if bitness == 32:
1100     if _InstructionNameIn(
1101         name,
1102         ['mov',  # including MOVQ
1103          'add', 'sub', 'and', 'or', 'xor',
1104          'xchg', 'xadd',
1105          'inc', 'dec', 'neg', 'not',
1106          'shl', 'shr', 'sar', 'rol', 'ror', 'rcl', 'rcr',
1107          'shld', 'shrd',
1108          'pop', 'cmpxchg8b',
1109          'lea',
1110          'nop',
1111          'prefetch', 'prefetchnta', 'prefetcht0', 'prefetcht1', 'prefetcht2',
1112          'prefetchw',
1113          'adc', 'sbb', 'bsf', 'bsr',
1114          'lzcnt', 'tzcnt', 'popcnt', 'crc32', 'cmpxchg',
1115          'movbe',
1116          'movmskpd', 'movmskps', 'movnti',
1117          'btc', 'btr', 'bts', 'bt',
1118          'cmp', 'test',
1119          'imul', 'mul', 'div', 'idiv', 'push',
1120         ]) or name in ['movd', 'vmovd']:
1121       return Condition(), Condition()
1122
1123     elif name in [
1124         'cpuid', 'hlt', 'lahf', 'sahf', 'rdtsc', 'pause',
1125         'sfence', 'lfence', 'mfence',
1126         'leave',
1127         'cmc', 'clc', 'cld', 'stc', 'std',
1128         'cwtl', 'cbtw', 'cltq',  # CBW/CWDE/CDQE
1129         'cltd', 'cwtd', 'cqto',  # CWD/CDQ/CQO
1130         'ud2', 'ud2a',
1131         ]:
1132       return Condition(), Condition()
1133
1134     elif re.match(r'mov[sz][bwl][lqw]$', name):  # MOVSX, MOVSXD, MOVZX
1135       return Condition(), Condition()
1136
1137     elif name == 'bswap':
1138       if ops[0] not in REGS32:
1139         raise SandboxingError(
1140             'bswap is only allowed with 32-bit operands',
1141             instruction)
1142       return Condition(), Condition()
1143
1144     elif re.match(r'(cmov|set)%s$' % _CONDITION_SUFFIX_RE, name):
1145       return Condition(), Condition()
1146
1147     elif name in _X87_INSTRUCTIONS:
1148       return Condition(), Condition()
1149
1150     elif name in _MMX_INSTRUCTIONS:
1151       return Condition(), Condition()
1152
1153     elif name in _XMM_AVX_INSTRUCTIONS:
1154       return Condition(), Condition()
1155
1156     elif name in ['maskmovq', 'maskmovdqu', 'vmaskmovdqu']:
1157       # In 64-bit mode these instructions are processed in
1158       # ValidateSuperinstruction64, together with string instructions.
1159       return Condition(), Condition()
1160
1161     else:
1162       raise DoNotMatchError(instruction)
1163
1164   elif bitness == 64:
1165     precondition = Condition()
1166     postcondition = Condition()
1167     zero_extending = False
1168     touches_memory = True
1169
1170     # Here we determine which operands instruction writes to. Note that for
1171     # our purposes writes are only relevant when they either have potential to
1172     # zero-extend regular register, or can modify protected registers (r15,
1173     # rbp, rsp).
1174     # This means that we don't have to worry about implicit operands (for
1175     # example it does not matter to us that mul writes to rdx and rax).
1176
1177     if (_InstructionNameIn(
1178           name, [
1179             'mov',  # including MOVQ
1180             'movabs',
1181             'movd',
1182             'add', 'sub', 'and', 'or', 'xor']) or
1183         name in ['movd', 'vmovd', 'vmovq']):
1184       # Technically, movabs is not allowed, but it's ok to accept it here,
1185       # because it will later be rejected because of improper memory access.
1186       # On the other hand, because of objdump quirk it prints regular
1187       # mov with 64-bit immediate as movabs:
1188       #   48 b8 00 00 00 00 00 00 00 00
1189       #   movabs $0x0,%rax
1190       assert len(ops) == 2
1191       zero_extending = True
1192       write_ops = [ops[1]]
1193
1194     elif re.match(r'mov[sz][bwl][lqw]$', name):  # MOVSX, MOVSXD, MOVZX
1195       assert len(ops) == 2
1196       zero_extending = True
1197       write_ops = [ops[1]]
1198
1199     elif _InstructionNameIn(name, ['xchg', 'xadd']):
1200       assert len(ops) == 2
1201       zero_extending = True
1202       write_ops = ops
1203
1204     elif _InstructionNameIn(name, ['inc', 'dec', 'neg', 'not']):
1205       assert len(ops) == 1
1206       zero_extending = True
1207       write_ops = ops
1208
1209     elif _InstructionNameIn(name, [
1210         'shl', 'shr', 'sar', 'rol', 'ror', 'rcl', 'rcr']):
1211       assert len(ops) in [1, 2]
1212       write_ops = [ops[-1]]
1213
1214     elif _InstructionNameIn(name, ['shld', 'shrd']):
1215       assert len(ops) == 3
1216       write_ops = [ops[2]]
1217
1218     elif _InstructionNameIn(name, [
1219         'pop', 'cmpxchg8b', 'cmpxchg16b']):
1220       assert len(ops) == 1
1221       write_ops = ops
1222
1223     elif name == 'lea':
1224       assert len(ops) == 2
1225       write_ops = [ops[1]]
1226       touches_memory = False
1227       zero_extending = True
1228
1229     elif _InstructionNameIn(name, ['nop']):
1230       assert len(ops) in [0, 1]
1231       write_ops = []
1232       touches_memory = False
1233
1234     elif name in [
1235         'prefetch', 'prefetchnta', 'prefetcht0', 'prefetcht1', 'prefetcht2',
1236         'prefetchw']:
1237       assert len(ops) == 1
1238       write_ops = []
1239       touches_memory = False
1240
1241     elif _InstructionNameIn(
1242         name,
1243         ['adc', 'sbb', 'bsf', 'bsr',
1244          'lzcnt', 'tzcnt', 'popcnt', 'crc32', 'cmpxchg',
1245          'movbe',
1246          'movmskpd', 'movmskps', 'movnti']):
1247       assert len(ops) == 2
1248       write_ops = [ops[1]]
1249
1250     elif _InstructionNameIn(name, ['btc', 'btr', 'bts', 'bt']):
1251       assert len(ops) == 2
1252       # bt* accept arbitrarily large bit offset when second
1253       # operand is memory and offset is in register.
1254       # Interestingly, when offset is immediate, it's taken modulo operand size,
1255       # even when second operand is memory.
1256       # Also, validator currently disallows
1257       #   bt* <register>, <register>
1258       # which is techincally safe. We disallow it in spec as well for
1259       # simplicity.
1260       if not re.match(_ImmediateRE() + r'$', ops[0]):
1261         raise SandboxingError(
1262             'bt* is only allowed with immediate as bit offset',
1263             instruction)
1264       if _InstructionNameIn(name, ['bt']):
1265         write_ops = []
1266       else:
1267         write_ops = [ops[1]]
1268
1269     elif _InstructionNameIn(name, ['cmp', 'test']):
1270       assert len(ops) == 2
1271       write_ops = []
1272
1273     elif name == 'bswap':
1274       assert len(ops) == 1
1275       if ops[0] not in REGS32 + REGS64:
1276         raise SandboxingError(
1277             'bswap is only allowed with 32-bit and 64-bit operands',
1278             instruction)
1279       write_ops = ops
1280
1281     elif name in [
1282         'cpuid', 'hlt', 'lahf', 'sahf', 'rdtsc', 'pause',
1283         'sfence', 'lfence', 'mfence',
1284         'cmc', 'clc', 'cld', 'stc', 'std',
1285         'cwtl', 'cbtw', 'cltq',  # CBW/CWDE/CDQE
1286         'cltd', 'cwtd', 'cqto',  # CWD/CDQ/CQO
1287         'ud2', 'ud2a',
1288         ]:
1289       assert len(ops) == 0
1290       write_ops = []
1291
1292     elif _InstructionNameIn(name, ['imul']):
1293       if len(ops) == 1:
1294         write_ops = []
1295       elif len(ops) == 2:
1296         zero_extending = True
1297         write_ops = [ops[1]]
1298       elif len(ops) == 3:
1299         zero_extending = True
1300         write_ops = [ops[2]]
1301       else:
1302         assert False
1303
1304     elif _InstructionNameIn(name, ['mul', 'div', 'idiv', 'push']):
1305       assert len(ops) == 1
1306       write_ops = []
1307
1308     elif re.match(r'cmov%s$' % _CONDITION_SUFFIX_RE, name):
1309       assert len(ops) == 2
1310       write_ops = [ops[1]]
1311
1312     elif re.match(r'set%s$' % _CONDITION_SUFFIX_RE, name):
1313       assert len(ops) == 1
1314       write_ops = ops
1315
1316     elif name in _X87_INSTRUCTIONS:
1317       assert 0 <= len(ops) <= 2
1318       # Actually, x87 instructions can write to x87 registers and to memory,
1319       # and there is even one instruction (fstsw/fnstsw) that writes to ax.
1320       # But these writes do not matter for sandboxing purposes.
1321       write_ops = []
1322
1323     elif name in _MMX_INSTRUCTIONS:
1324       assert 0 <= len(ops) <= 3
1325       write_ops = ops[-1:]
1326
1327     elif name in _XMM_AVX_INSTRUCTIONS:
1328       assert 0 <= len(ops) <= 5
1329       write_ops = ops[-1:]
1330
1331     else:
1332       raise DoNotMatchError(instruction)
1333
1334     if touches_memory:
1335       precondition = _ProcessMemoryAccess(instruction, ops)
1336
1337     postcondition = _ProcessOperandWrites(
1338         instruction, write_ops, zero_extending)
1339
1340     return precondition, postcondition
1341
1342   else:
1343     assert False, bitness
1344
1345
1346 def ValidateDirectJump(instruction, bitness):
1347   assert bitness in [32, 64]
1348   cond_jumps_re = re.compile(
1349       r'(data16 )?'
1350       r'(?P<name>j%s|loop(n?e)?|j[er]?cxz)(?P<branch_hint>,p[nt])? %s$'
1351       % (_CONDITION_SUFFIX_RE, _HexRE('destination')))
1352   m = cond_jumps_re.match(instruction.disasm)
1353   if m is not None:
1354     if (m.group('name') == 'jcxz' or
1355         (m.group('name') == 'jecxz' and bitness == 64)):
1356       raise SandboxingError('disallowed form of jcxz instruction', instruction)
1357
1358     if (m.group('name').startswith('loop') and
1359         m.group('branch_hint') is not None):
1360       raise SandboxingError(
1361           'branch hints are not allowed with loop instruction', instruction)
1362     # Unfortunately we can't rely on presence of 'data16' prefix in disassembly,
1363     # because neither nacl-objdump nor objdump we base our decoder print it.
1364     # So we look at bytes.
1365     if 0x66 in _GetLegacyPrefixes(instruction):
1366       raise SandboxingError(
1367           '16-bit conditional jumps are disallowed', instruction)
1368     return int(m.group('destination'), 16)
1369
1370   jumps_re = re.compile(r'(jmp|call)(|w|q) %s$' % _HexRE('destination'))
1371   m = jumps_re.match(instruction.disasm)
1372   if m is not None:
1373     if m.group(2) == 'w':
1374       raise SandboxingError('16-bit jumps are disallowed', instruction)
1375     return int(m.group('destination'), 16)
1376
1377   raise DoNotMatchError(instruction)
1378
1379
1380 def ValidateDirectJumpOrRegularInstruction(instruction, bitness):
1381   """Validate anything that is not superinstruction.
1382
1383   Args:
1384     instruction: objdump_parser.Instruction tuple.
1385     bitness: 32 or 64.
1386   Returns:
1387     Triple (jump_destination, precondition, postcondition).
1388     jump_destination is either absolute offset or None if instruction is not
1389     jump. Pre/postconditions are as in ValidateRegularInstructions.
1390   Raises:
1391     According to usual convention.
1392   """
1393   assert bitness in [32, 64]
1394   try:
1395     destination = ValidateDirectJump(instruction, bitness)
1396     return destination, Condition(), Condition()
1397   except DoNotMatchError:
1398     pass
1399
1400   precondition, postcondition = ValidateRegularInstruction(instruction, bitness)
1401   return None, precondition, postcondition
1402
1403
1404 def ValidateSuperinstruction32(superinstruction):
1405   """Validate superinstruction with ia32 set of regexps.
1406
1407   If set of instructions includes something unknown (unknown functions
1408   or prefixes, wrong number of instructions, etc), then assert is triggered.
1409
1410   There corner case exist: naclcall/nacljmp instruction sequences are too
1411   complex to process by DFA alone (it produces too large DFA and MSVC chokes
1412   on it) thus it's verified partially by DFA and partially by code in
1413   actions.  For these we generate either "True" or "False".
1414
1415   Args:
1416       superinstruction: list of objdump_parser.Instruction tuples
1417   """
1418
1419   call_jmp = re.compile(
1420       r'(call|jmp) '  # call or jmp
1421       r'[*](?P<register>%e[a-z]+)$')  # register name
1422
1423   # TODO(shcherbina): actually we only want to allow 0xffffffe0 as a mask,
1424   # but it's safe anyway because what really matters is that lower 5 bits
1425   # of the mask are zeroes.
1426   # Disallow 0xe0 once
1427   # https://code.google.com/p/nativeclient/issues/detail?id=3164 is fixed.
1428   and_for_call_jmp = re.compile(
1429       r'and [$]0x(ffffff)?e0,(?P<register>%e[a-z]+)$')
1430
1431   dangerous_instruction = superinstruction[-1].disasm
1432
1433   if call_jmp.match(dangerous_instruction):
1434     # If "dangerous instruction" is call or jmp then we need to check if two
1435     # lines match
1436
1437     if len(superinstruction) != 2:
1438       raise DoNotMatchError(superinstruction)
1439
1440     m = and_for_call_jmp.match(superinstruction[0].disasm)
1441     if m is None:
1442       raise DoNotMatchError(superinstruction)
1443     register_and = m.group('register')
1444
1445     m = call_jmp.match(dangerous_instruction)
1446     if m is None:
1447       raise DoNotMatchError(superinstruction)
1448     register_call_jmp = m.group('register')
1449
1450     if register_and == register_call_jmp:
1451       for instruction in superinstruction:
1452         _GetLegacyPrefixes(instruction)  # to detect repeated prefixes
1453       return
1454
1455     raise SandboxingError(
1456         'nacljump32/naclcall32: {0} != {1}'.format(
1457             register_and, register_call_jmp),
1458         superinstruction)
1459
1460   raise DoNotMatchError(superinstruction)
1461
1462
1463 def ValidateSuperinstruction64(superinstruction):
1464   """Validate superinstruction with x86-64 set of regexps.
1465
1466   If set of instructions includes something unknown (unknown functions
1467   or prefixes, wrong number of instructions, etc), then assert is triggered.
1468
1469   There corner case exist: naclcall/nacljmp instruction sequences are too
1470   complex to process by DFA alone (it produces too large DFA and MSVC chokes
1471   on it) thus it's verified partially by DFA and partially by code in
1472   actions.  For these we generate either "True" or "False", other
1473   superinstruction always produce "True" or throw an error.
1474
1475   Args:
1476       superinstruction: list of objdump_parser.Instruction tuples
1477   """
1478
1479   dangerous_instruction = superinstruction[-1].disasm
1480
1481   # This is dangerous instructions in naclcall/nacljmp
1482   callq_jmpq = re.compile(
1483       r'(callq|jmpq) ' # callq or jmpq
1484       r'[*](?P<register>%r[0-9a-z]+)$') # register name
1485   # These are sandboxing instructions for naclcall/nacljmp
1486   # TODO(shcherbina): actually we only want to allow 0xffffffe0 as a mask,
1487   # but it's safe anyway because what really matters is that lower 5 bits
1488   # of the mask are zeroes.
1489   # Disallow 0xe0 once
1490   # https://code.google.com/p/nativeclient/issues/detail?id=3164 is fixed.
1491   and_for_callq_jmpq = re.compile(
1492       r'and [$]0x(f)*e0,(?P<register>%e[a-z][a-z]|%r[89]d|%r1[0-4]d)$')
1493   add_for_callq_jmpq = re.compile(
1494       r'add %r15,(?P<register>%r[0-9a-z]+)$')
1495
1496   if callq_jmpq.match(dangerous_instruction):
1497     # If "dangerous instruction" is callq or jmpq then we need to check if all
1498     # three lines match
1499
1500     if len(superinstruction) != 3:
1501       raise DoNotMatchError(superinstruction)
1502
1503     m = and_for_callq_jmpq.match(superinstruction[0].disasm)
1504     if m is None:
1505       raise DoNotMatchError(superinstruction)
1506     register_and = m.group('register')
1507
1508     m = add_for_callq_jmpq.match(superinstruction[1].disasm)
1509     if m is None:
1510       raise DoNotMatchError(superinstruction)
1511     register_add = m.group('register')
1512
1513     m = callq_jmpq.match(dangerous_instruction)
1514     if m is None:
1515       raise DoNotMatchError(superinstruction)
1516     register_callq_jmpq = m.group('register')
1517
1518     # Double-check that registers are 32-bit and convert them to 64-bit so
1519     # they can be compared
1520     if register_and[1] == 'e':
1521       register_and = '%r' + register_and[2:]
1522     elif re.match(r'%r\d+d', register_and):
1523       register_and = register_and[:-1]
1524     else:
1525       assert False, ('Unknown (or possible non-32-bit) register found. '
1526                      'This should never happen!')
1527     if register_and == register_add == register_callq_jmpq:
1528       for instruction in superinstruction:
1529         _GetLegacyPrefixes(instruction)  # to detect repeated prefixes
1530       return
1531
1532     raise SandboxingError(
1533         'nacljump64/naclcall64: registers do not match ({0}, {1}, {2})'.format(
1534             register_and, register_add, register_callq_jmpq),
1535         superinstruction)
1536
1537     raise DoNotMatchError(superinstruction)
1538
1539   # These are dangerous string instructions (there are three cases)
1540   string_instruction_rdi_no_rsi = re.compile(
1541       r'(maskmovq %mm[0-7],%mm[0-7]|' # maskmovq
1542       r'v?maskmovdqu %xmm([0-9]|1[0-5]),%xmm([0-9]|1[0-5])|' # [v]maskmovdqu
1543       r'((repnz|repz) )?scas %es:[(]%rdi[)],(%al|%ax|%eax|%rax)|' # scas
1544       r'(rep )?stos (%al|%ax|%eax|%rax),%es:[(]%rdi[)])$') # stos
1545   string_instruction_rsi_no_rdi = re.compile(
1546       r'(rep )?lods %ds:[(]%rsi[)],(%al|%ax|%eax|%rax)$') # lods
1547   string_instruction_rsi_rdi = re.compile(
1548       r'(((repnz|repz) )?cmps[blqw] %es:[(]%rdi[)],%ds:[(]%rsi[)]|' # cmps
1549       r'(rep )?movs[blqw] %ds:[(]%rsi[)],%es:[(]%rdi[)])$') # movs
1550   # These are sandboxing instructions for string instructions
1551   mov_esi_esi = re.compile(r'mov %esi,%esi$')
1552   lea_r15_rsi_rsi = re.compile(r'lea [(]%r15,%rsi,1[)],%rsi$')
1553   mov_edi_edi = re.compile(r'mov %edi,%edi$')
1554   lea_r15_rdi_rdi = re.compile(r'lea [(]%r15,%rdi,1[)],%rdi$')
1555
1556   if string_instruction_rsi_no_rdi.match(dangerous_instruction):
1557     if len(superinstruction) != 3:
1558       raise DoNotMatchError(superinstruction)
1559     if mov_esi_esi.match(superinstruction[0].disasm) is None:
1560       raise DoNotMatchError(superinstruction)
1561     if lea_r15_rsi_rsi.match(superinstruction[1].disasm) is None:
1562       raise DoNotMatchError(superinstruction)
1563
1564   elif string_instruction_rdi_no_rsi.match(dangerous_instruction):
1565     if len(superinstruction) != 3:
1566       raise DoNotMatchError(superinstruction)
1567     if mov_edi_edi.match(superinstruction[0].disasm) is None:
1568       raise DoNotMatchError(superinstruction)
1569     if lea_r15_rdi_rdi.match(superinstruction[1].disasm) is None:
1570       raise DoNotMatchError(superinstruction)
1571     # vmaskmovdqu is disabled for compatibility with the previous validator
1572     if dangerous_instruction.startswith('vmaskmovdqu '):
1573       raise SandboxingError('vmaskmovdqu is disallowed', superinstruction)
1574
1575   elif string_instruction_rsi_rdi.match(dangerous_instruction):
1576     if len(superinstruction) != 5:
1577       raise DoNotMatchError(superinstruction)
1578     if mov_esi_esi.match(superinstruction[0].disasm) is None:
1579       raise DoNotMatchError(superinstruction)
1580     if lea_r15_rsi_rsi.match(superinstruction[1].disasm) is None:
1581       raise DoNotMatchError(superinstruction)
1582     if mov_edi_edi.match(superinstruction[2].disasm) is None:
1583       raise DoNotMatchError(superinstruction)
1584     if lea_r15_rdi_rdi.match(superinstruction[3].disasm) is None:
1585       raise DoNotMatchError(superinstruction)
1586
1587   else:
1588     raise DoNotMatchError(superinstruction)
1589
1590   for instruction in superinstruction:
1591     _GetLegacyPrefixes(instruction)  # to detect repeated prefixes