accelerate-0.15.0.0: An embedded language for accelerated array processing

Safe HaskellNone
LanguageHaskell98

Data.Array.Accelerate.Data.Complex

Contents

Synopsis

Rectangular from

data Complex a :: * -> *

Complex numbers are an algebraic type.

For a complex number z, abs z is a number with the magnitude of z, but oriented in the positive real direction, whereas signum z has the phase of z, but unit magnitude.

Constructors

!a :+ !a infix 6

forms a complex number from its real and imaginary rectangular components.

Instances

Elt a => Unlift Exp (Complex (Exp a)) 
(Lift Exp a, Elt (Plain a)) => Lift Exp (Complex a) 
(RealFloat a, Unbox a) => MVector MVector (Complex a) 
(RealFloat a, Unbox a) => Vector Vector (Complex a) 
Eq a => Eq (Complex a) 
RealFloat a => Floating (Complex a) 
(Elt a, IsFloating a, RealFloat a) => Floating (Exp (Complex a)) 
RealFloat a => Fractional (Complex a) 
(Elt a, IsFloating a) => Fractional (Exp (Complex a)) 
Data a => Data (Complex a) 
RealFloat a => Num (Complex a) 
(Elt a, IsFloating a) => Num (Exp (Complex a)) 
Read a => Read (Complex a) 
Show a => Show (Complex a) 
Elt a => Elt (Complex a) 
(RealFloat a, Unbox a) => Unbox (Complex a) 
Typeable (* -> *) Complex 
data MVector s (Complex a) = MV_Complex (MVector s (a, a)) 
type Plain (Complex a) = Complex (Plain a) 
data Vector (Complex a) = V_Complex (Vector (a, a)) 

real :: Elt a => Exp (Complex a) -> Exp a Source

Return the real part of a complex number

imag :: Elt a => Exp (Complex a) -> Exp a Source

Return the imaginary part of a complex number

Polar form

mkPolar :: (Elt a, IsFloating a) => Exp a -> Exp a -> Exp (Complex a) Source

Form a complex number from polar components of magnitude and phase.

cis :: (Elt a, IsFloating a) => Exp a -> Exp (Complex a) Source

cis t is a complex value with magnitude 1 and phase t (modulo 2*pi).

polar :: (Elt a, IsFloating a) => Exp (Complex a) -> Exp (a, a) Source

The function polar takes a complex number and returns a (magnitude, phase) pair in canonical form: the magnitude is non-negative, and the phase in the range (-pi, pi]; if the magnitude is zero, then so is the phase.

magnitude :: (Elt a, IsFloating a) => Exp (Complex a) -> Exp a Source

The non-negative magnitude of a complex number

phase :: (Elt a, IsFloating a) => Exp (Complex a) -> Exp a Source

The phase of a complex number, in the range (-pi, pi]. If the magnitude is zero, then so is the phase.

Conjugate

conjugate :: (Elt a, IsNum a) => Exp (Complex a) -> Exp (Complex a) Source

Return the complex conjugate of a complex number, defined as

conjugate(Z) = X - iY