]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/asmcomp/mips/arch.ml
update
[l4.git] / l4 / pkg / ocaml / contrib / asmcomp / mips / 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 5304 2002-11-29 15:03:37Z xleroy $ *)
14
15 (* Specific operations for the Mips processor *)
16
17 open Misc
18 open Format
19
20 (* Machine-specific command-line options *)
21
22 let command_line_options = []
23
24 (* Addressing modes *)
25
26 type addressing_mode =
27     Ibased of string * int              (* symbol + displ *)
28   | Iindexed of int                     (* reg + displ *)
29
30 (* Specific operations *)
31
32 type specific_operation = unit          (* none *)
33
34 (* Sizes, endianness *)
35
36 let big_endian =
37   match Config.system with
38     "ultrix" -> false
39   | "irix" -> true
40   | _ -> fatal_error "Arch_mips.big_endian"
41
42 let size_addr = 4
43 let size_int = 4
44 let size_float = 8
45
46 (* Operations on addressing modes *)
47
48 let identity_addressing = Iindexed 0
49
50 let offset_addressing addr delta =
51   match addr with
52     Ibased(s, n) -> Ibased(s, n + delta)
53   | Iindexed n -> Iindexed(n + delta)
54
55 let num_args_addressing = function
56     Ibased(s, n) -> 0
57   | Iindexed n -> 1
58
59 (* Printing operations and addressing modes *)
60
61 let print_addressing printreg addr ppf arg =
62   match addr with
63   | Ibased(s, n) ->
64       let idx = if n <> 0 then Printf.sprintf " + %i" n else "" in
65       fprintf ppf "\"%s\"%s" s idx
66   | Iindexed n ->
67       let idx = if n <> 0 then Printf.sprintf " + %i" n else "" in
68       fprintf ppf "%a%s" printreg arg.(0) idx
69
70 let print_specific_operation printreg op ppf arg =
71   fatal_error "Arch_mips.print_specific_operation"