]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/asmcomp/power/arch.ml
update
[l4.git] / l4 / pkg / ocaml / contrib / asmcomp / power / arch.ml
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: arch.ml 7430 2006-05-31 08:16:34Z xleroy $ *)
14
15 (* Specific operations for the PowerPC processor *)
16
17 open Misc
18 open Format
19
20 (* Machine-specific command-line options *)
21
22 let command_line_options = []
23
24 (* Specific operations *)
25
26 type specific_operation =
27     Imultaddf                           (* multiply and add *)
28   | Imultsubf                           (* multiply and subtract *)
29   | Ialloc_far of int                   (* allocation in large functions *)
30
31 (* Addressing modes *)
32
33 type addressing_mode =
34     Ibased of string * int              (* symbol + displ *)
35   | Iindexed of int                     (* reg + displ *)
36   | Iindexed2                           (* reg + reg *)
37
38 (* Sizes, endianness *)
39
40 let big_endian = true
41
42 let ppc64 =
43   match Config.model with "ppc64" -> true | _ -> false
44
45 let size_addr = if ppc64 then 8 else 4
46 let size_int = size_addr
47 let size_float = 8
48
49 (* Operations on addressing modes *)
50
51 let identity_addressing = Iindexed 0
52
53 let offset_addressing addr delta =
54   match addr with
55     Ibased(s, n) -> Ibased(s, n + delta)
56   | Iindexed n -> Iindexed(n + delta)
57   | Iindexed2 -> assert false
58
59 let num_args_addressing = function
60     Ibased(s, n) -> 0
61   | Iindexed n -> 1
62   | Iindexed2 -> 2
63
64 (* Printing operations and addressing modes *)
65
66 let print_addressing printreg addr ppf arg =
67   match addr with
68   | Ibased(s, n) ->
69       let idx = if n <> 0 then Printf.sprintf " + %i" n else "" in
70       fprintf ppf "\"%s\"%s" s idx
71   | Iindexed n ->
72       let idx = if n <> 0 then Printf.sprintf " + %i" n else "" in
73       fprintf ppf "%a%s" printreg arg.(0) idx
74   | Iindexed2 ->
75       fprintf ppf "%a + %a" printreg arg.(0) printreg arg.(1)
76
77 let print_specific_operation printreg op ppf arg =
78   match op with
79   | Imultaddf ->
80       fprintf ppf "%a *f %a +f %a"
81         printreg arg.(0) printreg arg.(1) printreg arg.(2)
82   | Imultsubf ->
83       fprintf ppf "%a *f %a -f %a"
84         printreg arg.(0) printreg arg.(1) printreg arg.(2)
85   | Ialloc_far n ->
86       fprintf ppf "alloc_far %d" n
87