Fix compile by putting time_f in sys.mlp & put equals into Typestruct.DiscreteType
[ocaml.git] / stdlib / typestruct.ml
blobebb721a03f1e07fa530b4ca39516463373378b79
1 (***********************************************************************)
2 (* *)
3 (* (community) Objective Caml *)
4 (* *)
5 (* Edgar Friendly <thelema314@gmail.com> *)
6 (* *)
7 (* Copyright 2008 Edgar Friendly. *)
8 (* 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 (* Copyright 2008 <bluestorm dot dylc on-the-server gmail dot com> *)
13 (***********************************************************************)
15 module type OrderedType =
16 sig
17 type t
18 val compare: t -> t -> int
19 end
21 module type ComparableType =
22 sig
23 type t
24 val compare: t -> t -> int
25 val equal : t -> t -> bool
26 end
28 module type PrintableType =
29 sig
30 type t
31 val to_string : t -> string
32 end
34 module type SerializableType =
35 sig
36 type t
37 val to_string : t -> string
38 val of_string : string -> t
39 end
41 module type DiscreteType = sig
42 type t
43 val succ : t -> t
44 val pred : t -> t
46 val min_num : t
47 val max_num : t
49 val of_int : int -> t
50 val to_int : t -> int (* may raise error if not with int range *)
52 val of_string : string -> t
53 val to_string : t -> string
55 val compare : t -> t -> int
56 val equal : t -> t -> bool
57 end
59 module type NumericType = sig
60 include DiscreteType
62 val zero : t
63 val one : t
65 val neg : t -> t
66 val abs : t -> t
68 val add : t -> t -> t
69 val sub : t -> t -> t
70 val mul : t -> t -> t
71 val div : t -> t -> t
73 val modulo : t -> t -> t
74 val pow : t -> t -> t
75 end
77 let generic_pow zero one div_two mod_two ( * ) =
78 let rec pow a n =
79 if n = zero then one
80 else if n = one then a
81 else
82 let b = pow a (div_two n) in
83 b * b * (if mod_two n = zero then one else a)
84 in pow
86 module Int = struct
87 type t = int
89 let zero, one = 0, 1
91 let neg = (~-)
92 let succ, pred, abs = succ, pred, abs
94 let add, sub, mul, div = (+), (-), ( * ), (/)
96 let modulo a b = a mod b
97 let pow = generic_pow 0 1 (fun n -> n asr 1) (fun n -> n land 1) ( * )
99 let min_num, max_num = min_int, max_int
100 let compare = (-)
101 let equal (a:int) b = a = b
103 let of_int (n:int) = n
104 let to_int (n:int) = n
105 let of_string = int_of_string
106 let to_string = string_of_int
109 module Float = struct
110 type t = float
111 let zero, one = 0., 1.
112 let neg = (~-.)
114 let succ x = x +. 1.
115 let pred x = x -. 1.
116 let abs = abs_float
118 let add, sub, mul, div = (+.), (-.), ( *.), (/.)
119 let modulo = mod_float
120 let pow = ( ** )
122 let min_num, max_num = neg_infinity, infinity
123 let compare = compare
124 let epsilon = ref 0.00001
125 let set_precision e = epsilon := e
126 let equal a b = abs(b-.a) < !epsilon
128 let of_int = float_of_int
129 let to_int = int_of_float
131 let of_string = float_of_string
132 let to_string = string_of_float