base-4.20.0.0: Core data structures and operations
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Complex

Description

Complex numbers.

Synopsis

Rectangular form

data Complex a Source #

A data type representing complex numbers.

You can read about complex numbers on wikipedia.

In haskell, complex numbers are represented as a :+ b which can be thought of as representing \(a + bi\). 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. Apart from the loss of precision due to IEEE754 floating point numbers, it holds that z == abs z * signum z.

Note that Complex's instances inherit the deficiencies from the type parameter's. For example, Complex Float's Eq instance has similar problems to Float's.

As can be seen in the examples, the Foldable and Traversable instances traverse the real part first.

Examples

Expand
>>> (5.0 :+ 2.5) + 6.5
11.5 :+ 2.5
>>> abs (1.0 :+ 1.0) - sqrt 2.0
0.0 :+ 0.0
>>> abs (signum (4.0 :+ 3.0))
1.0 :+ 0.0
>>> foldr (:) [] (1 :+ 2)
[1,2]
>>> mapM print (1 :+ 2)
1
2

Constructors

!a :+ !a infix 6

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

Instances

Instances details
MonadZip Complex Source #

Since: base-4.15.0.0

Instance details

Defined in Data.Complex

Methods

mzip :: Complex a -> Complex b -> Complex (a, b) Source #

mzipWith :: (a -> b -> c) -> Complex a -> Complex b -> Complex c Source #

munzip :: Complex (a, b) -> (Complex a, Complex b) Source #

Foldable1 Complex Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => Complex m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> Complex a -> m Source #

foldMap1' :: Semigroup m => (a -> m) -> Complex a -> m Source #

toNonEmpty :: Complex a -> NonEmpty a Source #

maximum :: Ord a => Complex a -> a Source #

minimum :: Ord a => Complex a -> a Source #

head :: Complex a -> a Source #

last :: Complex a -> a Source #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Complex a -> b Source #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Complex a -> b Source #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Complex a -> b Source #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Complex a -> b Source #

Eq1 Complex Source #
>>> eq1 (1 :+ 2) (1 :+ 2)
True
>>> eq1 (1 :+ 2) (1 :+ 3)
False

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Complex a -> Complex b -> Bool Source #

Read1 Complex Source #
>>> readPrec_to_S readPrec1 0 "(2 % 3) :+ (3 % 4)" :: [(Complex Rational, String)]
[(2 % 3 :+ 3 % 4,"")]

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Show1 Complex Source #
>>> showsPrec1 0 (2 :+ 3) ""
"2 :+ 3"

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Complex a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Complex a] -> ShowS Source #

Applicative Complex Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

pure :: a -> Complex a Source #

(<*>) :: Complex (a -> b) -> Complex a -> Complex b Source #

liftA2 :: (a -> b -> c) -> Complex a -> Complex b -> Complex c Source #

(*>) :: Complex a -> Complex b -> Complex b Source #

(<*) :: Complex a -> Complex b -> Complex a Source #

Functor Complex Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

fmap :: (a -> b) -> Complex a -> Complex b Source #

(<$) :: a -> Complex b -> Complex a Source #

Monad Complex Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

(>>=) :: Complex a -> (a -> Complex b) -> Complex b Source #

(>>) :: Complex a -> Complex b -> Complex b Source #

return :: a -> Complex a Source #

MonadFix Complex Source #

Since: base-4.15.0.0

Instance details

Defined in Data.Complex

Methods

mfix :: (a -> Complex a) -> Complex a Source #

Foldable Complex Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

fold :: Monoid m => Complex m -> m Source #

foldMap :: Monoid m => (a -> m) -> Complex a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Complex a -> m Source #

foldr :: (a -> b -> b) -> b -> Complex a -> b Source #

foldr' :: (a -> b -> b) -> b -> Complex a -> b Source #

foldl :: (b -> a -> b) -> b -> Complex a -> b Source #

foldl' :: (b -> a -> b) -> b -> Complex a -> b Source #

foldr1 :: (a -> a -> a) -> Complex a -> a Source #

foldl1 :: (a -> a -> a) -> Complex a -> a Source #

toList :: Complex a -> [a] Source #

null :: Complex a -> Bool Source #

length :: Complex a -> Int Source #

elem :: Eq a => a -> Complex a -> Bool Source #

maximum :: Ord a => Complex a -> a Source #

minimum :: Ord a => Complex a -> a Source #

sum :: Num a => Complex a -> a Source #

product :: Num a => Complex a -> a Source #

Traversable Complex Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

traverse :: Applicative f => (a -> f b) -> Complex a -> f (Complex b) Source #

sequenceA :: Applicative f => Complex (f a) -> f (Complex a) Source #

mapM :: Monad m => (a -> m b) -> Complex a -> m (Complex b) Source #

sequence :: Monad m => Complex (m a) -> m (Complex a) Source #

Generic1 Complex Source # 
Instance details

Defined in Data.Complex

Associated Types

type Rep1 Complex

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Data a => Data (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Complex a -> c (Complex a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Complex a) Source #

toConstr :: Complex a -> Constr Source #

dataTypeOf :: Complex a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Complex a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Complex a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Complex a -> Complex a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Complex a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Complex a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Complex a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Complex a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Complex a -> m (Complex a) Source #

RealFloat a => Floating (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Storable a => Storable (Complex a) Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Complex

Methods

sizeOf :: Complex a -> Int Source #

alignment :: Complex a -> Int Source #

peekElemOff :: Ptr (Complex a) -> Int -> IO (Complex a) Source #

pokeElemOff :: Ptr (Complex a) -> Int -> Complex a -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (Complex a) Source #

pokeByteOff :: Ptr b -> Int -> Complex a -> IO () Source #

peek :: Ptr (Complex a) -> IO (Complex a) Source #

poke :: Ptr (Complex a) -> Complex a -> IO () Source #

Generic (Complex a) Source # 
Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a)

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

from :: Complex a -> Rep (Complex a) x Source #

to :: Rep (Complex a) x -> Complex a Source #

RealFloat a => Num (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Read a => Read (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

RealFloat a => Fractional (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Show a => Show (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Eq a => Eq (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

(==) :: Complex a -> Complex a -> Bool Source #

(/=) :: Complex a -> Complex a -> Bool Source #

type Rep1 Complex Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

type Rep (Complex a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

realPart :: Complex a -> a Source #

Extracts the real part of a complex number.

Examples

Expand
>>> realPart (5.0 :+ 3.0)
5.0
>>> realPart ((5.0 :+ 3.0) * (2.0 :+ 3.0))
1.0

imagPart :: Complex a -> a Source #

Extracts the imaginary part of a complex number.

Examples

Expand
>>> imagPart (5.0 :+ 3.0)
3.0
>>> imagPart ((5.0 :+ 3.0) * (2.0 :+ 3.0))
21.0

Polar form

mkPolar :: Floating a => a -> a -> Complex a Source #

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

Examples

Expand
>>> mkPolar 1 (pi / 4)
0.7071067811865476 :+ 0.7071067811865475
>>> mkPolar 1 0
1.0 :+ 0.0

cis :: Floating a => a -> Complex a Source #

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

cis = mkPolar 1

Examples

Expand
>>> cis 0
1.0 :+ 0.0

The following examples are not perfectly zero due to IEEE 754

>>> cis pi
(-1.0) :+ 1.2246467991473532e-16
>>> cis (4 * pi) - cis (2 * pi)
0.0 :+ (-2.4492935982947064e-16)

polar :: RealFloat a => Complex a -> (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.

polar z = (magnitude z, phase z)

Examples

Expand
>>> polar (1.0 :+ 1.0)
(1.4142135623730951,0.7853981633974483)
>>> polar ((-1.0) :+ 0.0)
(1.0,3.141592653589793)
>>> polar (0.0 :+ 0.0)
(0.0,0.0)

magnitude :: RealFloat a => Complex a -> a Source #

The non-negative magnitude of a complex number.

Examples

Expand
>>> magnitude (1.0 :+ 1.0)
1.4142135623730951
>>> magnitude (1.0 + 0.0)
1.0
>>> magnitude (0.0 :+ (-5.0))
5.0

phase :: RealFloat a => Complex a -> a Source #

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

Examples

Expand
>>> phase (0.5 :+ 0.5) / pi
0.25
>>> phase (0 :+ 4) / pi
0.5

Conjugate

conjugate :: Num a => Complex a -> Complex a Source #

The conjugate of a complex number.

conjugate (conjugate x) = x

Examples

Expand
>>> conjugate (3.0 :+ 3.0)
3.0 :+ (-3.0)
>>> conjugate ((3.0 :+ 3.0) * (2.0 :+ 2.0))
0.0 :+ (-12.0)