Sys.Signals module for a Variant type of signals (and a set_signal function that...
[ocaml.git] / stdlib / complex.mli
blob3c3b361d27e4547dca2cf1c415596c2cecadf40a
1 (***********************************************************************)
2 (* *)
3 (* Objective Caml *)
4 (* *)
5 (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
6 (* *)
7 (* Copyright 2002 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 (***********************************************************************)
14 (* $Id$ *)
16 (** Complex numbers.
18 This module provides arithmetic operations on complex numbers.
19 Complex numbers are represented by their real and imaginary parts
20 (cartesian representation). Each part is represented by a
21 double-precision floating-point number (type [float]). *)
23 type t = { re: float; im: float }
24 (** The type of complex numbers. [re] is the real part and [im] the
25 imaginary part. *)
27 val zero: t
28 (** The complex number [0]. *)
30 val one: t
31 (** The complex number [1]. *)
33 val i: t
34 (** The complex number [i]. *)
36 val neg: t -> t
37 (** Unary negation. *)
39 val conj: t -> t
40 (** Conjugate: given the complex [x + i.y], returns [x - i.y]. *)
42 val add: t -> t -> t
43 (** Addition *)
45 val sub: t -> t -> t
46 (** Subtraction *)
48 val mul: t -> t -> t
49 (** Multiplication *)
51 val inv: t -> t
52 (** Multiplicative inverse ([1/z]). *)
54 val div: t -> t -> t
55 (** Division *)
57 val sqrt: t -> t
58 (** Square root. The result [x + i.y] is such that [x > 0] or
59 [x = 0] and [y >= 0].
60 This function has a discontinuity along the negative real axis. *)
62 val norm2: t -> float
63 (** Norm squared: given [x + i.y], returns [x^2 + y^2]. *)
65 val norm: t -> float
66 (** Norm: given [x + i.y], returns [sqrt(x^2 + y^2)]. *)
68 val arg: t -> float
69 (** Argument. The argument of a complex number is the angle
70 in the complex plane between the positive real axis and a line
71 passing through zero and the number. This angle ranges from
72 [-pi] to [pi]. This function has a discontinuity along the
73 negative real axis. *)
75 val polar: float -> float -> t
76 (** [polar norm arg] returns the complex having norm [norm]
77 and argument [arg]. *)
79 val exp: t -> t
80 (** Exponentiation. [exp z] returns [e] to the [z] power. *)
82 val log: t -> t
83 (** Natural logarithm (in base [e]). *)
85 val pow: t -> t -> t
86 (** Power function. [pow z1 z2] returns [z1] to the [z2] power. *)