numeric-prelude-0.4.3.1: An experimental alternative hierarchy of numeric type classes

Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainernumericprelude@henning-thielemann.de
Stabilityprovisional
Portabilityportable (?)
Safe HaskellNone
LanguageHaskell98

Number.Complex

Contents

Description

Complex numbers.

Synopsis

Cartesian form

data T a Source #

Complex numbers are an algebraic type.

Instances
Functor T Source # 
Instance details

Defined in Number.Complex

Methods

fmap :: (a -> b) -> T a -> T b #

(<$) :: a -> T b -> T a #

C T Source # 
Instance details

Defined in Number.Complex

Methods

zero :: C a => T a Source #

(<+>) :: C a => T a -> T a -> T a Source #

(*>) :: C a => a -> T a -> T a Source #

C a b => C a (T b) Source #

The '(*>)' method can't replace scale because it requires the Algebra.Module constraint

Instance details

Defined in Number.Complex

Methods

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

C a b => C a (T b) Source # 
Instance details

Defined in Number.Complex

(Show v, C v, C v, C a v) => C a (T v) Source # 
Instance details

Defined in Number.Complex

Methods

toScalar :: T v -> a Source #

toMaybeScalar :: T v -> Maybe a Source #

fromScalar :: a -> T v Source #

(C a, C a v) => C a (T v) Source # 
Instance details

Defined in Number.Complex

Methods

norm :: T v -> a Source #

(Ord a, C a v) => C a (T v) Source # 
Instance details

Defined in Number.Complex

Methods

norm :: T v -> a Source #

(C a, Sqr a b) => C a (T b) Source # 
Instance details

Defined in Number.Complex

Methods

norm :: T b -> a Source #

Sqr a b => Sqr a (T b) Source # 
Instance details

Defined in Number.Complex

Methods

normSqr :: T b -> a Source #

Eq a => Eq (T a) Source # 
Instance details

Defined in Number.Complex

Methods

(==) :: T a -> T a -> Bool #

(/=) :: T a -> T a -> Bool #

(Floating a, Eq a) => Fractional (T a) Source # 
Instance details

Defined in Number.Complex

Methods

(/) :: T a -> T a -> T a #

recip :: T a -> T a #

fromRational :: Rational -> T a #

(Floating a, Eq a) => Num (T a) Source # 
Instance details

Defined in Number.Complex

Methods

(+) :: T a -> T a -> T a #

(-) :: T a -> T a -> T a #

(*) :: T a -> T a -> T a #

negate :: T a -> T a #

abs :: T a -> T a #

signum :: T a -> T a #

fromInteger :: Integer -> T a #

Read a => Read (T a) Source # 
Instance details

Defined in Number.Complex

Methods

readsPrec :: Int -> ReadS (T a) #

readList :: ReadS [T a] #

readPrec :: ReadPrec (T a) #

readListPrec :: ReadPrec [T a] #

Show a => Show (T a) Source # 
Instance details

Defined in Number.Complex

Methods

showsPrec :: Int -> T a -> ShowS #

show :: T a -> String #

showList :: [T a] -> ShowS #

Arbitrary a => Arbitrary (T a) Source # 
Instance details

Defined in Number.Complex

Methods

arbitrary :: Gen (T a) #

shrink :: T a -> [T a] #

Storable a => Storable (T a) Source # 
Instance details

Defined in Number.Complex

Methods

sizeOf :: T a -> Int #

alignment :: T a -> Int #

peekElemOff :: Ptr (T a) -> Int -> IO (T a) #

pokeElemOff :: Ptr (T a) -> Int -> T a -> IO () #

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

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

peek :: Ptr (T a) -> IO (T a) #

poke :: Ptr (T a) -> T a -> IO () #

C a => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

compare :: T a -> T a -> Ordering Source #

C a => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

zero :: T a Source #

(+) :: T a -> T a -> T a Source #

(-) :: T a -> T a -> T a Source #

negate :: T a -> T a Source #

C a => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

isZero :: T a -> Bool Source #

C a => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

(*) :: T a -> T a -> T a Source #

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

C a => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

div :: T a -> T a -> T a Source #

mod :: T a -> T a -> T a Source #

divMod :: T a -> T a -> (T a, T a) Source #

(Ord a, C a) => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

isUnit :: T a -> Bool Source #

stdAssociate :: T a -> T a Source #

stdUnit :: T a -> T a Source #

stdUnitInv :: T a -> T a Source #

(Ord a, C a, C a) => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

extendedGCD :: T a -> T a -> (T a, (T a, T a)) Source #

gcd :: T a -> T a -> T a Source #

lcm :: T a -> T a -> T a Source #

(C a, C a, C a) => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

abs :: T a -> T a Source #

signum :: T a -> T a Source #

C a => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

(/) :: T a -> T a -> T a Source #

recip :: T a -> T a Source #

fromRational' :: Rational -> T a Source #

(^-) :: T a -> Integer -> T a Source #

(C a, C a, Power a) => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

sqrt :: T a -> T a Source #

root :: Integer -> T a -> T a Source #

(^/) :: T a -> Rational -> T a Source #

(C a, C a, C a, Power a) => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

pi :: T a Source #

exp :: T a -> T a Source #

log :: T a -> T a Source #

logBase :: T a -> T a -> T a Source #

(**) :: T a -> T a -> T a Source #

sin :: T a -> T a Source #

cos :: T a -> T a Source #

tan :: T a -> T a Source #

asin :: T a -> T a Source #

acos :: T a -> T a Source #

atan :: T a -> T a Source #

sinh :: T a -> T a Source #

cosh :: T a -> T a Source #

tanh :: T a -> T a Source #

asinh :: T a -> T a Source #

acosh :: T a -> T a Source #

atanh :: T a -> T a Source #

fromReal :: C a => a -> T a Source #

(+:) :: a -> a -> T a infix 6 Source #

Construct a complex number from real and imaginary part.

(-:) :: C a => a -> a -> T a Source #

Construct a complex number with negated imaginary part.

scale :: C a => a -> T a -> T a Source #

Scale a complex number by a real number.

exp :: C a => T a -> T a Source #

Exponential of a complex number with minimal type class constraints.

quarterLeft :: C a => T a -> T a Source #

Turn the point one quarter to the right.

quarterRight :: C a => T a -> T a Source #

Turn the point one quarter to the right.

Polar form

fromPolar :: C a => a -> a -> T a Source #

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

cis :: C a => a -> T a Source #

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

signum :: (C a, C a) => T a -> T a Source #

Scale a complex number to magnitude 1.

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.

signumNorm :: (C a, C a a, C a) => T a -> T a Source #

toPolar :: (C a, C a) => T a -> (a, a) Source #

The function toPolar 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 :: C a => T a -> a Source #

magnitudeSqr :: C a => T a -> a Source #

phase :: (C a, C a) => T 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 :: C a => T a -> T a Source #

The conjugate of a complex number.

Properties

propPolar :: (C a, C a) => T a -> Bool Source #

Auxiliary classes

class C a => Power a where Source #

We like to build the Complex Algebraic instance on top of the Algebraic instance of the scalar type. This poses no problem to sqrt. However, root requires computing the complex argument which is a transcendent operation. In order to keep the type class dependencies clean for more sophisticated algebraic number types, we introduce a type class which actually performs the radix operation.

Minimal complete definition

power

Methods

power :: Rational -> T a -> T a Source #

Instances
Power Double Source # 
Instance details

Defined in Number.Complex

Methods

power :: Rational -> T Double -> T Double Source #

Power Float Source # 
Instance details

Defined in Number.Complex

Methods

power :: Rational -> T Float -> T Float Source #

Power T Source # 
Instance details

Defined in Number.Positional.Check

Methods

power :: Rational -> T0 T -> T0 T Source #

defltPow :: (C a, C a) => Rational -> T a -> T a Source #