{ module Bindings.Bfd.Disasm.I386.Parse where import Data.Array import qualified Data.IntMap as IntMap import qualified Data.Map as Map import Data.Maybe import Data.Word import Bindings.Bfd.Disasm.I386.Address import Bindings.Bfd.Disasm.I386.EffectiveAddr import Bindings.Bfd.Disasm.I386.Insn as I import Bindings.Bfd.Disasm.I386.Lex as L import Bindings.Bfd.Disasm.I386.Mnemonic as R import Bindings.Bfd.Disasm.I386.Operand as O import Bindings.Bfd.Disasm.I386.Prefix import Bindings.Bfd.Disasm.I386.Register } %name parse %tokentype { Token } %token OFFSET { Offset $$ } CONSTANT { Constant $$ } ADDRESS { Address $$ } PREFIXEDMNEMONIC { PrefixedMnemonic $$ } MNEMONIC { L.Mnemonic $$ } REGISTER { Register $$ } '(' { ParensL } ')' { ParensR } ',' { Comma } ':' { Colon } '#' { Hash } '*' { Star } %% insn :: { Insn } : PREFIXEDMNEMONIC operands { Insn 0 (toPrefix $ head $1) (toMnemonic $ head $ tail $1) $2 } | MNEMONIC operands { Insn 0 (Nothing ) (toMnemonic $1) $2 } operands :: { [Operand] } : {- empty -} { [ ]} -- nop | absolute { [$1 ]} -- jle 12345 | immed { [$1 ]} -- pushq $12345 | directD { [$1 ]} -- inc %rax | directJ { [$1 ]} -- callq *%rdx | indirD address { [$1 { O.mbAddress = $2 } ]} -- inc 12345(%rax) | indirJ address { [$1 { O.mbAddress = $2 } ]} -- callq *12345(%rbx) | directD ',' directD { [$1 , $3 ]} -- mov %rax,%rbx | directD ',' indirD address { [$1 , $3 { O.mbAddress = $4 } ]} -- mov %rax,12345(%rbx) | directD ',' immed { [$1 , $3 ]} -- out %ax,$0x12 | indirD ',' directD address { [$1 { O.mbAddress = $4 }, $3 ]} -- mov 12345(%rbx),%rax | indirD ',' indirD { [$1 , $3 ]} -- rep movsq %ds:(%rsi),%es:(%rdi) | immed ',' directD { [$1 , $3 ]} -- mov $12345,%rax | immed ',' indirD address { [$1 , $3 { O.mbAddress = $4 } ]} -- mov $12345,12345(%rax) | immed ',' directD ',' directD { [$1 , $3 , $5]} -- imul $12345,%rax,%rbx | immed ',' indirD ',' directD address { [$1 , $3 , $5]} -- imul $12345,12345(%rbp),%eax address :: { Maybe Address } : {- empty -} { Nothing } | '#' ADDRESS { Just $ Left $2 } absolute :: { Operand } : ADDRESS { Abs $ Left $1 } immed :: { Operand } : CONSTANT { Imm $1 } directD :: { Operand } : register { DirD $1 } directJ :: { Operand } : '*' register { DirJ $2 } indirD :: { Operand } : indir1 { IndD Nothing (fst $1) (snd $1) Nothing } | register ':' indir1 { IndD (Just $1) (fst $3) (snd $3) Nothing } indirJ :: { Operand } : '*' indir1 { IndJ (fst $2) (snd $2) Nothing } indir1 :: { (EffectiveAddr, Maybe Int) } : OFFSET effAddr { ($2 , Just $1) } | effAddr { ($1 , Nothing) } | OFFSET { (NoEA, Just $1) } effAddr :: { EffectiveAddr } : '(' register ')' { EA (Just $2) Nothing 1 } | '(' ',' register ',' OFFSET ')' { EA Nothing (Just $3) $5 } | '(' register ',' register ',' OFFSET ')' { EA (Just $2) (Just $4) $6 } register :: { Register } : REGISTER { toRegister $1 } { happyError :: [Token] -> a happyError tks = error $ "Parse.y: parse error at: " ++ (show $ take 10 tks) }