Home | History | Annotate | Download | only in ocaml
      1 (* Capstone Disassembly Engine
      2 * By Guillaume Jeanne <guillaume.jeanne (a] ensimag.fr>, 2014> *)
      3 
      4 open Printf
      5 open Capstone
      6 open Xcore
      7 
      8 
      9 let print_string_hex comment str =
     10 	printf "%s" comment;
     11 	for i = 0 to (Array.length str - 1) do
     12 		printf "0x%02x " str.(i)
     13 	done;
     14 	printf "\n"
     15 
     16 
     17 let _XCORE_CODE = "\xfe\x0f\xfe\x17\x13\x17\xc6\xfe\xec\x17\x97\xf8\xec\x4f\x1f\xfd\xec\x37\x07\xf2\x45\x5b\xf9\xfa\x02\x06\x1b\x10";;
     18 
     19 let all_tests = [
     20         (CS_ARCH_XCORE, [CS_MODE_LITTLE_ENDIAN], _XCORE_CODE, "XCore");
     21 ];;
     22 
     23 let print_op handle i op =
     24 	( match op.value with
     25 	| XCORE_OP_INVALID _ -> ();	(* this would never happens *)
     26 	| XCORE_OP_REG reg -> printf "\t\top[%d]: REG = %s\n" i (cs_reg_name handle reg);
     27 	| XCORE_OP_IMM imm -> printf "\t\top[%d]: IMM = 0x%x\n" i imm;
     28 	| XCORE_OP_MEM mem -> ( printf "\t\top[%d]: MEM\n" i;
     29 		if mem.base != 0 then
     30 			printf "\t\t\toperands[%u].mem.base: REG = %s\n" i (cs_reg_name handle mem.base);
     31 		if mem.index != 0 then
     32 			printf "\t\t\toperands[%u].mem.index: 0x%x\n" i mem.index;
     33 		if mem.disp != 0 then
     34 			printf "\t\t\toperands[%u].mem.disp: 0x%x\n" i mem.disp;
     35 		if mem.direct != 0 then
     36 			printf "\t\t\toperands[%u].mem.direct: 0x%x\n" i mem.direct;
     37 		);
     38 	);
     39 
     40 	();;
     41 
     42 
     43 let print_detail handle insn =
     44 	match insn.arch with
     45 	| CS_INFO_XCORE xcore -> (
     46 			(* print all operands info (type & value) *)
     47 			if (Array.length xcore.operands) > 0 then (
     48 				printf "\top_count: %d\n" (Array.length xcore.operands);
     49 				Array.iteri (print_op handle) xcore.operands;
     50 			);
     51 			printf "\n";
     52 		);
     53 	| _ -> ();
     54 	;;
     55 
     56 
     57 let print_insn handle insn =
     58 	printf "0x%x\t%s\t%s\n" insn.address insn.mnemonic insn.op_str;
     59 	print_detail handle insn
     60 
     61 
     62 let print_arch x =
     63 	let (arch, mode, code, comment) = x in
     64 		let handle = cs_open arch mode in
     65 		let err = cs_option handle CS_OPT_DETAIL _CS_OPT_ON in
     66 		match err with
     67 		| _ -> ();
     68 		let insns = cs_disasm handle code 0x1000L 0L in
     69 			printf "*************\n";
     70 			printf "Platform: %s\n" comment;
     71 			List.iter (print_insn handle) insns;
     72 		match cs_close handle with
     73 		| 0 -> ();
     74 		| _ -> printf "Failed to close handle";
     75 		;;
     76 
     77 
     78 List.iter print_arch all_tests;;
     79