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