2000-02-13 08:44:06 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Objective Caml *)
|
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
2001-12-07 05:41:02 -08:00
|
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
2000-02-13 08:44:06 -08:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
|
|
|
(* Module [Nativeint]: processor-native integers *)
|
|
|
|
|
2000-02-21 10:14:56 -08:00
|
|
|
external neg: nativeint -> nativeint = "%nativeint_neg"
|
|
|
|
external add: nativeint -> nativeint -> nativeint = "%nativeint_add"
|
|
|
|
external sub: nativeint -> nativeint -> nativeint = "%nativeint_sub"
|
|
|
|
external mul: nativeint -> nativeint -> nativeint = "%nativeint_mul"
|
|
|
|
external div: nativeint -> nativeint -> nativeint = "%nativeint_div"
|
|
|
|
external rem: nativeint -> nativeint -> nativeint = "%nativeint_mod"
|
|
|
|
external logand: nativeint -> nativeint -> nativeint = "%nativeint_and"
|
|
|
|
external logor: nativeint -> nativeint -> nativeint = "%nativeint_or"
|
|
|
|
external logxor: nativeint -> nativeint -> nativeint = "%nativeint_xor"
|
|
|
|
external shift_left: nativeint -> int -> nativeint = "%nativeint_lsl"
|
|
|
|
external shift_right: nativeint -> int -> nativeint = "%nativeint_asr"
|
|
|
|
external shift_right_logical: nativeint -> int -> nativeint = "%nativeint_lsr"
|
|
|
|
external of_int: int -> nativeint = "%nativeint_of_int"
|
|
|
|
external to_int: nativeint -> int = "%nativeint_to_int"
|
2000-04-18 01:51:28 -07:00
|
|
|
external of_float : float -> nativeint = "nativeint_of_float"
|
|
|
|
external to_float : nativeint -> float = "nativeint_to_float"
|
2000-03-05 11:17:54 -08:00
|
|
|
external of_int32: int32 -> nativeint = "%nativeint_of_int32"
|
|
|
|
external to_int32: nativeint -> int32 = "%nativeint_to_int32"
|
2000-02-13 08:44:06 -08:00
|
|
|
|
|
|
|
let zero = of_int 0
|
|
|
|
let one = of_int 1
|
|
|
|
let minus_one = of_int (-1)
|
|
|
|
let succ n = add n one
|
|
|
|
let pred n = sub n one
|
|
|
|
let abs n = if n >= zero then n else neg n
|
2001-01-21 04:34:41 -08:00
|
|
|
let size = Sys.word_size
|
|
|
|
let min_int = shift_left one (size - 1)
|
2000-04-16 07:37:21 -07:00
|
|
|
let max_int = sub min_int one
|
2000-02-13 08:44:06 -08:00
|
|
|
let lognot n = logxor n minus_one
|
|
|
|
|
2000-02-21 10:14:56 -08:00
|
|
|
external format : string -> nativeint -> string = "nativeint_format"
|
2000-02-13 08:44:06 -08:00
|
|
|
let to_string n = format "%d" n
|
|
|
|
|
2000-02-21 10:14:56 -08:00
|
|
|
external of_string: string -> nativeint = "nativeint_of_string"
|