]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/stdlib/nativeint.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / stdlib / nativeint.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 GNU Library General Public License, with    *)
10 (*  the special exception on linking described in file ../LICENSE.     *)
11 (*                                                                     *)
12 (***********************************************************************)
13
14 (* $Id: nativeint.ml 7818 2007-01-30 09:34:36Z xleroy $ *)
15
16 (* Module [Nativeint]: processor-native integers *)
17
18 external neg: nativeint -> nativeint = "%nativeint_neg"
19 external add: nativeint -> nativeint -> nativeint = "%nativeint_add"
20 external sub: nativeint -> nativeint -> nativeint = "%nativeint_sub"
21 external mul: nativeint -> nativeint -> nativeint = "%nativeint_mul"
22 external div: nativeint -> nativeint -> nativeint = "%nativeint_div"
23 external rem: nativeint -> nativeint -> nativeint = "%nativeint_mod"
24 external logand: nativeint -> nativeint -> nativeint = "%nativeint_and"
25 external logor: nativeint -> nativeint -> nativeint = "%nativeint_or"
26 external logxor: nativeint -> nativeint -> nativeint = "%nativeint_xor"
27 external shift_left: nativeint -> int -> nativeint = "%nativeint_lsl"
28 external shift_right: nativeint -> int -> nativeint = "%nativeint_asr"
29 external shift_right_logical: nativeint -> int -> nativeint = "%nativeint_lsr"
30 external of_int: int -> nativeint = "%nativeint_of_int"
31 external to_int: nativeint -> int = "%nativeint_to_int"
32 external of_float : float -> nativeint = "caml_nativeint_of_float"
33 external to_float : nativeint -> float = "caml_nativeint_to_float"
34 external of_int32: int32 -> nativeint = "%nativeint_of_int32"
35 external to_int32: nativeint -> int32 = "%nativeint_to_int32"
36
37 let zero = 0n
38 let one = 1n
39 let minus_one = -1n
40 let succ n = add n 1n
41 let pred n = sub n 1n
42 let abs n = if n >= 0n then n else neg n
43 let size = Sys.word_size
44 let min_int = shift_left 1n (size - 1)
45 let max_int = sub min_int 1n
46 let lognot n = logxor n (-1n)
47
48 external format : string -> nativeint -> string = "caml_nativeint_format"
49 let to_string n = format "%d" n
50
51 external of_string: string -> nativeint = "caml_nativeint_of_string"
52
53 type t = nativeint
54
55 let compare (x: t) (y: t) = Pervasives.compare x y