File: arch_alpha.ml

package info (click to toggle)
ocaml 1.05-2
  • links: PTS
  • area: non-free
  • in suites: hamm, slink
  • size: 7,472 kB
  • ctags: 12,935
  • sloc: ml: 37,142; ansic: 24,745; asm: 11,632; lisp: 1,957; sh: 1,801; makefile: 1,512; perl: 29; sed: 28
file content (66 lines) | stat: -rw-r--r-- 2,256 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
(***********************************************************************)
(*                                                                     *)
(*                           Objective Caml                            *)
(*                                                                     *)
(*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
(*                                                                     *)
(*  Copyright 1996 Institut National de Recherche en Informatique et   *)
(*  Automatique.  Distributed only by permission.                      *)
(*                                                                     *)
(***********************************************************************)

(* $Id: arch_alpha.ml,v 1.4 1996/04/30 14:42:00 xleroy Exp $ *)

(* Specific operations for the Alpha processor *)

open Format

(* Addressing modes *)

type addressing_mode =
    Ibased of string * int              (* symbol + displ *)
  | Iindexed of int                     (* reg + displ *)

(* Specific operations *)

type specific_operation =
    Iadd4 | Iadd8 | Isub4 | Isub8       (* Scaled adds and subs *)

(* Sizes, endianness *)

let big_endian = false

let size_addr = 8
let size_int = 8
let size_float = 8

(* Operations on addressing modes *)

let identity_addressing = Iindexed 0

let offset_addressing addr delta =
  match addr with
    Ibased(s, n) -> Ibased(s, n + delta)
  | Iindexed n -> Iindexed(n + delta)

let num_args_addressing = function
    Ibased(s, n) -> 0
  | Iindexed n -> 1

(* Printing operations and addressing modes *)

let print_addressing printreg addr arg =
  match addr with
    Ibased(s, n) ->
      print_string "\""; print_string s; print_string "\"";
      if n <> 0 then begin print_string " + "; print_int n end
  | Iindexed n ->
      printreg arg.(0);
      if n <> 0 then begin print_string " + "; print_int n end

let print_specific_operation printreg op arg =
  match op with
    Iadd4 -> printreg arg.(0); print_string " * 4 + "; printreg arg.(1)
  | Iadd8 -> printreg arg.(0); print_string " * 8 + "; printreg arg.(1)
  | Isub4 -> printreg arg.(0); print_string " * 4 - "; printreg arg.(1)
  | Isub8 -> printreg arg.(0); print_string " * 8 - "; printreg arg.(1)