base-4.8.2.0: Basic libraries

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

Contents

Description

Complex numbers.

Synopsis

Rectangular form

data Complex a Source

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

Eq a => Eq (Complex a) Source 

Methods

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

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

RealFloat a => Floating (Complex a) Source 
RealFloat a => Fractional (Complex a) Source 
Data a => Data (Complex a) Source 

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 :: (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 => Num (Complex a) Source 
Read a => Read (Complex a) Source 
Show a => Show (Complex a) Source 
Storable a => Storable (Complex a) Source 

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

realPart :: Complex a -> a Source

Extracts the real part of a complex number.

imagPart :: Complex a -> a Source

Extracts the imaginary part of a complex number.

Polar form

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

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

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

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

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 nonnegative, and the phase in the range (-pi, pi]; if the magnitude is zero, then so is the phase.

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

The nonnegative magnitude of a complex number.

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.

Conjugate

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

The conjugate of a complex number.