diff options
-rw-r--r-- | stdlib/.depend | 24 | ||||
-rw-r--r-- | stdlib/Makefile | 2 | ||||
-rw-r--r-- | stdlib/Makefile.Mac | 2 | ||||
-rw-r--r-- | stdlib/Makefile.nt | 2 | ||||
-rw-r--r-- | stdlib/complex.ml | 80 | ||||
-rw-r--r-- | stdlib/complex.mli | 85 |
6 files changed, 181 insertions, 14 deletions
diff --git a/stdlib/.depend b/stdlib/.depend index f7fead2df..c22ca15c6 100644 --- a/stdlib/.depend +++ b/stdlib/.depend @@ -1,26 +1,28 @@ format.cmi: buffer.cmi genlex.cmi: stream.cmi -moreLabels.cmi: hashtbl.cmi +moreLabels.cmi: hashtbl.cmi map.cmi set.cmi parsing.cmi: lexing.cmi obj.cmi printf.cmi: buffer.cmi arg.cmo: array.cmi list.cmi printf.cmi string.cmi sys.cmi arg.cmi arg.cmx: array.cmx list.cmx printf.cmx string.cmx sys.cmx arg.cmi -array.cmo: array.cmi -array.cmx: array.cmi arrayLabels.cmo: array.cmi arrayLabels.cmi arrayLabels.cmx: array.cmx arrayLabels.cmi +array.cmo: array.cmi +array.cmx: array.cmi buffer.cmo: string.cmi sys.cmi buffer.cmi buffer.cmx: string.cmx sys.cmx buffer.cmi callback.cmo: obj.cmi callback.cmi callback.cmx: obj.cmx callback.cmi char.cmo: char.cmi char.cmx: char.cmi +complex.cmo: complex.cmi +complex.cmx: complex.cmi digest.cmo: string.cmi digest.cmi digest.cmx: string.cmx digest.cmi filename.cmo: buffer.cmi string.cmi sys.cmi filename.cmi filename.cmx: buffer.cmx string.cmx sys.cmx filename.cmi -format.cmo: buffer.cmi obj.cmi string.cmi format.cmi -format.cmx: buffer.cmx obj.cmx string.cmx format.cmi +format.cmo: buffer.cmi obj.cmi printf.cmi string.cmi format.cmi +format.cmx: buffer.cmx obj.cmx printf.cmx string.cmx format.cmi gc.cmo: printf.cmi sys.cmi gc.cmi gc.cmx: printf.cmx sys.cmx gc.cmi genlex.cmo: char.cmi hashtbl.cmi list.cmi stream.cmi string.cmi genlex.cmi @@ -35,10 +37,10 @@ lazy.cmo: lazy.cmi lazy.cmx: lazy.cmi lexing.cmo: string.cmi lexing.cmi lexing.cmx: string.cmx lexing.cmi -list.cmo: array.cmi list.cmi -list.cmx: array.cmx list.cmi listLabels.cmo: list.cmi listLabels.cmi listLabels.cmx: list.cmx listLabels.cmi +list.cmo: array.cmi list.cmi +list.cmx: array.cmx list.cmi map.cmo: map.cmi map.cmx: map.cmi marshal.cmo: string.cmi marshal.cmi @@ -59,8 +61,8 @@ pervasives.cmo: pervasives.cmi pervasives.cmx: pervasives.cmi printexc.cmo: obj.cmi printf.cmi string.cmi sys.cmi printexc.cmi printexc.cmx: obj.cmx printf.cmx string.cmx sys.cmx printexc.cmi -printf.cmo: buffer.cmi obj.cmi string.cmi printf.cmi -printf.cmx: buffer.cmx obj.cmx string.cmx printf.cmi +printf.cmo: buffer.cmi list.cmi obj.cmi string.cmi printf.cmi +printf.cmx: buffer.cmx list.cmx obj.cmx string.cmx printf.cmi queue.cmo: queue.cmi queue.cmx: queue.cmi random.cmo: array.cmi char.cmi digest.cmi string.cmi random.cmi @@ -75,10 +77,10 @@ stdLabels.cmo: arrayLabels.cmi listLabels.cmi stringLabels.cmi stdLabels.cmi stdLabels.cmx: arrayLabels.cmx listLabels.cmx stringLabels.cmx stdLabels.cmi stream.cmo: list.cmi obj.cmi string.cmi stream.cmi stream.cmx: list.cmx obj.cmx string.cmx stream.cmi -string.cmo: char.cmi list.cmi string.cmi -string.cmx: char.cmx list.cmx string.cmi stringLabels.cmo: string.cmi stringLabels.cmi stringLabels.cmx: string.cmx stringLabels.cmi +string.cmo: char.cmi list.cmi string.cmi +string.cmx: char.cmx list.cmx string.cmi sys.cmo: sys.cmi sys.cmx: sys.cmi weak.cmo: obj.cmi weak.cmi diff --git a/stdlib/Makefile b/stdlib/Makefile index e3b648c04..724aaabf8 100644 --- a/stdlib/Makefile +++ b/stdlib/Makefile @@ -30,7 +30,7 @@ BASIC=pervasives.cmo array.cmo list.cmo char.cmo string.cmo sys.cmo \ set.cmo map.cmo stack.cmo queue.cmo stream.cmo \ buffer.cmo printf.cmo format.cmo arg.cmo printexc.cmo gc.cmo \ digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo \ - lazy.cmo filename.cmo int32.cmo int64.cmo nativeint.cmo + lazy.cmo filename.cmo int32.cmo int64.cmo nativeint.cmo complex.cmo LABELLED=arrayLabels.ml listLabels.ml stringLabels.ml moreLabels.ml OBJS=$(BASIC) labelled.cmo stdLabels.cmo diff --git a/stdlib/Makefile.Mac b/stdlib/Makefile.Mac index f8e60ae72..45bd2326c 100644 --- a/stdlib/Makefile.Mac +++ b/stdlib/Makefile.Mac @@ -24,7 +24,7 @@ OBJS = pervasives.cmo array.cmo list.cmo char.cmo string.cmo sys.cmo ¶ set.cmo map.cmo stack.cmo queue.cmo stream.cmo ¶ buffer.cmo printf.cmo format.cmo arg.cmo printexc.cmo gc.cmo ¶ digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo ¶ - lazy.cmo filename.cmo int32.cmo int64.cmo nativeint.cmo + lazy.cmo filename.cmo int32.cmo int64.cmo nativeint.cmo complex.cmo all Ä stdlib.cma std_exit.cmo camlheader camlheader_ur diff --git a/stdlib/Makefile.nt b/stdlib/Makefile.nt index 630804d11..c16e0657f 100644 --- a/stdlib/Makefile.nt +++ b/stdlib/Makefile.nt @@ -28,7 +28,7 @@ BASIC=pervasives.cmo array.cmo list.cmo char.cmo string.cmo sys.cmo \ set.cmo map.cmo stack.cmo queue.cmo stream.cmo \ buffer.cmo printf.cmo format.cmo arg.cmo printexc.cmo gc.cmo \ digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo \ - lazy.cmo filename.cmo int32.cmo int64.cmo nativeint.cmo + lazy.cmo filename.cmo int32.cmo int64.cmo nativeint.cmo complex.cmo LABELLED=arrayLabels.ml listLabels.ml stringLabels.ml moreLabels.ml OBJS=$(BASIC) labelled.cmo stdLabels.cmo diff --git a/stdlib/complex.ml b/stdlib/complex.ml new file mode 100644 index 000000000..7c9f20410 --- /dev/null +++ b/stdlib/complex.ml @@ -0,0 +1,80 @@ +(***********************************************************************) +(* *) +(* Objective Caml *) +(* *) +(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) +(* *) +(* Copyright 2002 Institut National de Recherche en Informatique et *) +(* en Automatique. All rights reserved. This file is distributed *) +(* under the terms of the GNU Library General Public License, with *) +(* the special exception on linking described in file ../LICENSE. *) +(* *) +(***********************************************************************) + +(* $Id$ *) + +(* Complex numbers *) + +type t = { re: float; im: float } + +let zero = { re = 0.0; im = 0.0 } +let one = { re = 1.0; im = 0.0 } +let i = { re = 0.0; im = 1.0 } + +let add x y = { re = x.re +. y.re; im = x.im +. y.im } + +let sub x y = { re = x.re -. y.re; im = x.im -. y.im } + +let neg x = { re = -. x.re; im = -. x.im } + +let conj x = { re = x.re; im = -. x.im } + +let mul x y = { re = x.re *. y.re -. x.im *. y.im; + im = x.re *. y.im +. x.im *. y.re } + +let inv x = + (* Watch out for overflow in computing re^2 + im^2 *) + if abs_float x.re >= abs_float x.im then begin + let q = x.im /. x.re in + let d = 1.0 +. q *. q in + { re = (1.0 /. d) /. x.re; im = -. (q /. d) /. x.re } + end else begin + let q = x.re /. x.im in + let d = 1.0 +. q *. q in + { re = (q /. d) /. x.im; im = (-1.0 /. d) /. x.im } + end + +let div x y = mul x (inv y) + +let norm2 x = x.re *. x.re +. x.im *. x.im + +let norm x = + (* Watch out for overflow in computing re^2 + im^2 *) + let r = abs_float x.re and i = abs_float x.im in + if r >= i then + let q = i /. r in r *. sqrt(1.0 +. q *. q) + else + let q = r /. i in i *. sqrt(1.0 +. q *. q) + +let arg x = atan2 x.im x.re + +let polar n a = { re = cos a *. n; im = sin a *. n } + +let sqrt x = + (* Avoid cancellation in computing norm x + x.re + when x.re < 0 and x.im is small *) + if x.re >= 0.0 then begin + let r = sqrt(0.5 *. norm x +. 0.5 *. x.re) in + { re = r; im = if r = 0.0 then 0.0 else 0.5 *. x.im /. r } + end else begin + let s = sqrt(0.5 *. norm x -. 0.5 *. x.re) in + { re = if s = 0.0 then 0.0 else 0.5 *. abs_float x.im /. s; + im = if x.im >= 0.0 then s else -. s } + end + +let exp x = + let e = exp x.re in { re = e *. cos x.im; im = e *. sin x.im } + +let log x = { re = log (norm x); im = atan2 x.im x.re } + +let pow x y = exp (mul y (log x)) diff --git a/stdlib/complex.mli b/stdlib/complex.mli new file mode 100644 index 000000000..72e974a2f --- /dev/null +++ b/stdlib/complex.mli @@ -0,0 +1,85 @@ +(***********************************************************************) +(* *) +(* Objective Caml *) +(* *) +(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) +(* *) +(* Copyright 2002 Institut National de Recherche en Informatique et *) +(* en Automatique. All rights reserved. This file is distributed *) +(* under the terms of the GNU Library General Public License, with *) +(* the special exception on linking described in file ../LICENSE. *) +(* *) +(***********************************************************************) + +(* $Id$ *) + +(** Complex numbers. + + This module provides arithmetic operations on complex numbers. + Complex numbers are represented by their real and imaginary parts + (cartesian representation). Each part is represented by a + double-precision floating-point number (type [float]). *) + +type t = { re: float; im: float } +(** The type of complex numbers. [re] is the real part and [im] the + imaginary part. *) + +val zero: t +(** The complex number [0]. *) + +val one: t +(** The complex number [1]. *) + +val i: t +(** The complex number [i]. *) + +val neg: t -> t +(** Unary negation. *) + +val conj: t -> t +(** Conjugate: given the complex [x + i.y], returns [x - i.y]. *) + +val add: t -> t -> t +(** Addition *) + +val sub: t -> t -> t +(** Subtraction *) + +val mul: t -> t -> t +(** Multiplication *) + +val inv: t -> t +(** Multiplicative inverse ([1/z]). *) + +val div: t -> t -> t +(** Division *) + +val sqrt: t -> t +(** Square root. The result always lies within the semispace [real >= 0]. + This function has a discontinuity along the negative real axis. *) + +val norm2: t -> float +(** Norm squared: given [x + i.y], returns [x^2 + y^2]. *) + +val norm: t -> float +(** Norm: given [x + i.y], returns [sqrt(x^2 + y^2)]. *) + +val arg: t -> float +(** Argument. The argument of a complex number is the angle + in the complex plane between the positive real axis and a line + passing through zero and the number. This angle ranges from + [-pi] to [pi]. This function has a discontinuity along the + negative real axis. *) + +val polar: float -> float -> t +(** [polar norm arg] returns the complex having norm [norm] + and argument [arg]. *) + +val exp: t -> t +(** Exponentiation. [exp z] returns [e] to the [z] power. *) + +val log: t -> t +(** Natural logarithm (in base [e]). *) + +val pow: t -> t -> t +(** Power function. [pow z1 z2] returns [z1] to the [z2] power. *) |