Did you know ... Search Documentation:
Pack ct_fft -- prolog/complex.pl
PublicShow source

This is module to calculate imaginary number.

The imaginary unit is represented by i.

author
- PiotrLi
license
- GPL
 set_default_is(F, A, B) is det
Set function for iis/2 if you don't want use is/2.

Example:

?- [user].
|: my_the_best_is(A,B):-
|: var(A),
|: nonvar(B),
|: A is B,
|: format('~w is ~w\n',[A,B]).
|: ^D% user://1 compiled 0.00 sec, 1 clauses
true.

?- set_default_is(my_the_best_is(A,B),A,B).
true.

?- X iis 3+i*5+15.
3 is 3
15 is 15
18 is 3+15
5 is 5+0
X = 18+5*i.

?- X iis 15**(3*i).
8.12415060330663 is log(15**3)
X = exp(i*8.12415060330663).
 iis(-Number, ++Expr) is det
It is is/2 witch imaginary number.
abs(+Z)
Return modulus of Z.
phase(+Z)
Return phase of Z, normalized to be between -pi and pi.
real(+Z)
Return real part of Z.
imaginary(+Z)
Return imaginary part of Z.
conjugate(+Z)
Return the conjugate of Z.
reciprocal(+Z)
Return the reciprocal of Z.
exp(+Z)
Return the complex exponential of Z.
sin(+Z)
Return the complex sine of Z.
cos(+Z)
Return the complex cosine of Z.
tan(+Z)
Return the complex tangent of Z.

Examples:

?- X iis i*i.
X = -1.

?- X iis 5*i*6*7.
X = 210*i.

?- X iis 5*i+3.
X = 3+5*i.

?- X iis phase(2+3*i).
X = 0.982793723247329.

?- X iis abs(5+10*i).
X = 11.180339887498949.

?- X iis conjugate(1+5*i).
X = 1-5*i.

?- X iis imaginary(5+2*i).
X = 2.

?- X iis imaginary(sqrt(2)*exp(45*pi/180*i)).
X = 1.0.

?- X iis 6*i*5/(i*2*5).
X = 3.
 c_equals(@Term1, @Term2) is det
It is for (iis)/2, like (=:=)/2 for (is)/2.
 complex_canonical(+Complex, -Real:number, -Imaginary:number) is semidet
Get real and imaginary from complex number and test if complex_number(Complex) in the same time.
 is_canonical(+Z, -Real:number, -Imaginary:number) is semidet
Get real and imaginary from complex number and test if Complex is in canonical in the same time.
 complex_exponential(+Complex, -Abs:number, -Phase:number) is semidet
Get abs and phase from complex number and test if complex_number(Complex) in the same time
 is_exponential(+Complex, -Abs:number, -Phase:number) is semidet
Get abs and phase from complex number and test if Complex is in exponential or trigonometric in the same time.
 complex_number(@Complex) is semidet
True if Term currently is a complex number in a form like:
  • canonical
    4, i, -1, 2*i, 3+2*i, 8-4*i, 3+ -2*i
  • exponential
    12*exp(i*5), exp(i*12)
  • trigonometric
    10*(cos(3)+i*sin(3)), cos(4)+i*sin(4)