]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/asmcomp/amd64/reload.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / asmcomp / amd64 / reload.ml
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 2000 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: reload.ml 8477 2007-11-06 15:16:56Z frisch $ *)
14
15 open Cmm
16 open Arch
17 open Reg
18 open Mach
19
20 (* Reloading for the AMD64 *)
21
22 (* Summary of instruction set constraints:
23    "S" means either stack or register, "R" means register only.
24    Operation                    Res     Arg1    Arg2
25      Imove                      R       S
26                              or S       R
27      Iconst_int                 S if 32-bit signed, R otherwise
28      Iconst_float               R
29      Iconst_symbol (not PIC)    S
30      Iconst_symbol (PIC)        R
31      Icall_ind                          R
32      Itailcall_ind                      R
33      Iload                      R       R       R
34      Istore                             R       R
35      Iintop(Icomp)              R       R       S
36                             or  S       S       R
37      Iintop(Imul|Idiv|mod)      R       R       S
38      Iintop(shift)              S       S       R
39      Iintop(others)             R       R       S
40                             or  S       S       R
41      Iintop_imm(Iadd, n)/lea    R       R
42      Iintop_imm(others)         S       S
43      Inegf...Idivf              R       R       S
44      Ifloatofint                R       S
45      Iintoffloat                R       S
46      Ispecific(Ilea)            R       R       R
47      Ispecific(Ifloatarithmem)  R       R       R
48
49    Conditional branches:
50      Iinttest                           S       R
51                                     or  R       S
52      Ifloattest                         R       S
53      other tests                        S
54 *)
55
56 let stackp r =
57   match r.loc with
58     Stack _ -> true
59   | _ -> false
60
61 class reload = object (self)
62
63 inherit Reloadgen.reload_generic as super
64
65 method reload_operation op arg res =
66   match op with
67     Iintop(Iadd|Isub|Iand|Ior|Ixor|Icomp _|Icheckbound) ->
68       (* One of the two arguments can reside in the stack, but not both *)
69       if stackp arg.(0) && stackp arg.(1)
70       then ([|arg.(0); self#makereg arg.(1)|], res)
71       else (arg, res)
72   | Iintop_imm(Iadd, _) when arg.(0).loc <> res.(0).loc ->
73       (* This add will be turned into a lea; args and results must be
74          in registers *)
75       super#reload_operation op arg res
76   | Iintop(Idiv | Imod | Ilsl | Ilsr | Iasr)
77   | Iintop_imm(_, _) ->
78       (* The argument(s) and results can be either in register or on stack *)
79       (* Note: Idiv, Imod: arg(0) and res(0) already forced in regs
80                Ilsl, Ilsr, Iasr: arg(1) already forced in regs *)
81       (arg, res)
82   | Iintop(Imul) | Iaddf | Isubf | Imulf | Idivf ->
83       (* First argument (= result) must be in register, second arg
84          can reside in the stack *)
85       if stackp arg.(0)
86       then (let r = self#makereg arg.(0) in ([|r; arg.(1)|], [|r|]))
87       else (arg, res)
88   | Ifloatofint | Iintoffloat ->
89       (* Result must be in register, but argument can be on stack *)
90       (arg, (if stackp res.(0) then [| self#makereg res.(0) |] else res))
91   | Iconst_int n ->
92       if n <= 0x7FFFFFFFn && n >= -0x80000000n
93       then (arg, res)
94       else super#reload_operation op arg res
95   | Iconst_symbol _ ->
96       if !pic_code || !Clflags.dlcode
97       then super#reload_operation op arg res
98       else (arg, res)
99   | _ -> (* Other operations: all args and results in registers *)
100       super#reload_operation op arg res
101
102 method reload_test tst arg =
103   match tst with
104     Iinttest cmp ->
105       (* One of the two arguments can reside on stack *)
106       if stackp arg.(0) && stackp arg.(1)
107       then [| self#makereg arg.(0); arg.(1) |]
108       else arg
109   | Ifloattest(_, _) ->
110       (* Second argument can be on stack, first must be in register *)
111       if stackp arg.(0)
112       then [| self#makereg arg.(0); arg.(1) |]
113       else arg
114   | _ ->
115       (* The argument(s) can be either in register or on stack *)
116       arg
117
118 end
119
120 let fundecl f =
121   (new reload)#fundecl f