base-4.14.1.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

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.

The Foldable and Traversable instances traverse the real part first.

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

Constructors

!a :+ !a infix 6

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

Instances

Instances details
Monad Complex #

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 #

Functor Complex #

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 #

Applicative Complex #

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 #

Foldable Complex #

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 #

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 #

Eq a => Eq (Complex a) #

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

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

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

RealFloat a => Floating (Complex a) #

Since: base-2.1

Instance details

Defined in Data.Complex

RealFloat a => Fractional (Complex a) #

Since: base-2.1

Instance details

Defined in Data.Complex

Data a => Data (Complex a) #

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 => Num (Complex a) #

Since: base-2.1

Instance details

Defined in Data.Complex

Read a => Read (Complex a) #

Since: base-2.1

Instance details

Defined in Data.Complex

Show a => Show (Complex a) #

Since: base-2.1

Instance details

Defined in Data.Complex

Generic (Complex a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a) :: Type -> Type Source #

Methods

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

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

Storable a => Storable (Complex a) #

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 #

Generic1 Complex #

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Associated Types

type Rep1 Complex :: k -> Type Source #

Methods

from1 :: forall (a :: k). Complex a -> Rep1 Complex a Source #

to1 :: forall (a :: k). Rep1 Complex a -> Complex a Source #

type Rep (Complex a) # 
Instance details

Defined in Data.Complex

type Rep1 Complex # 
Instance details

Defined in Data.Complex

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.