Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Data.Complex
Contents
Description
Complex numbers.
Synopsis
- data Complex a = !a :+ !a
- realPart :: Complex a -> a
- imagPart :: Complex a -> a
- mkPolar :: Floating a => a -> a -> Complex a
- cis :: Floating a => a -> Complex a
- polar :: RealFloat a => Complex a -> (a, a)
- magnitude :: RealFloat a => Complex a -> a
- phase :: RealFloat a => Complex a -> a
- conjugate :: Num a => Complex a -> Complex a
Rectangular form
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
,
is a number with the abs
zmagnitude
of z
,
but oriented in the positive real direction, whereas
has the signum
zphase
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
Instances
Instances details
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 (1 :+ 2) (1 :+ 2)
True
>>>
eq1 (1 :+ 2) (1 :+ 3)
False
Since: base-4.16.0.0
>>>
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
Methods
liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Complex a) Source #
liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Complex a] Source #
liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Complex a) Source #
liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Complex a] Source #
Instance details
Defined in Data.Complex
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 #
Instance details
Defined in Data.Complex
Instance details
Defined in Data.Complex
Associated Types
Instance details
Defined in Data.Complex
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 #
Since: base-2.1
Instance details
Defined in Data.Complex
Methods
exp :: Complex a -> Complex a Source #
log :: Complex a -> Complex a Source #
sqrt :: Complex a -> Complex a Source #
(**) :: Complex a -> Complex a -> Complex a Source #
logBase :: Complex a -> Complex a -> Complex a Source #
sin :: Complex a -> Complex a Source #
cos :: Complex a -> Complex a Source #
tan :: Complex a -> Complex a Source #
asin :: Complex a -> Complex a Source #
acos :: Complex a -> Complex a Source #
atan :: Complex a -> Complex a Source #
sinh :: Complex a -> Complex a Source #
cosh :: Complex a -> Complex a Source #
tanh :: Complex a -> Complex a Source #
asinh :: Complex a -> Complex a Source #
acosh :: Complex a -> Complex a Source #
atanh :: Complex a -> Complex a Source #
log1p :: Complex a -> Complex a Source #
expm1 :: Complex a -> 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 #
Instance details
Defined in Data.Complex
Associated Types
Instance details
Defined in Data.Complex
Since: base-2.1
Instance details
Defined in Data.Complex
Methods
(+) :: Complex a -> Complex a -> Complex a Source #
(-) :: Complex a -> Complex a -> Complex a Source #
(*) :: Complex a -> Complex a -> Complex a Source #
negate :: Complex a -> Complex a Source #
abs :: Complex a -> Complex a Source #
signum :: Complex a -> Complex a Source #
fromInteger :: Integer -> Complex a Source #
Since: base-2.1
Instance details
Defined in Data.Complex
Since: base-2.1
Instance details
Defined in Data.Complex
Since: base-2.1
Instance details
Defined in Data.Complex
Since: base-2.1
Instance details
Defined in Data.Complex
Since: base-4.9.0.0
Instance details
Defined in Data.Complex
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
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 (-
;
if the pi
, pi
]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