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 |
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
Complex numbers are an algebraic type.
For a complex number z
,
is a number with the magnitude of abs
zz
,
but oriented in the positive real direction, whereas
has the phase of signum
zz
, 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.
!a :+ !a infix 6 | forms a complex number from its real and imaginary rectangular components. |
Instances
MonadFix Complex # | Since: base-4.15.0.0 |
MonadZip Complex # | Since: base-4.15.0.0 |
Foldable Complex # | Since: base-4.9.0.0 |
Defined in Data.Complex 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 # | |
Eq1 Complex # |
Since: base-4.16.0.0 |
Read1 Complex # |
Since: base-4.16.0.0 |
Defined in Data.Functor.Classes 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 # | |
Show1 Complex # |
Since: base-4.16.0.0 |
Traversable Complex # | Since: base-4.9.0.0 |
Defined in Data.Complex | |
Applicative Complex # | Since: base-4.9.0.0 |
Functor Complex # | Since: base-4.9.0.0 |
Monad Complex # | Since: base-4.9.0.0 |
Generic1 Complex # | |
Data a => Data (Complex a) # | Since: base-2.1 |
Defined in Data.Complex 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 # | |
Storable a => Storable (Complex a) # | Since: base-4.8.0.0 |
Defined in Data.Complex 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 # | |
RealFloat a => Floating (Complex a) # | Since: base-2.1 |
Defined in Data.Complex 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 # | |
Generic (Complex a) # | |
RealFloat a => Num (Complex a) # | Since: base-2.1 |
Defined in Data.Complex (+) :: 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 # | |
Read a => Read (Complex a) # | Since: base-2.1 |
RealFloat a => Fractional (Complex a) # | Since: base-2.1 |
Show a => Show (Complex a) # | Since: base-2.1 |
Eq a => Eq (Complex a) # | Since: base-2.1 |
type Rep1 Complex # | Since: base-4.9.0.0 |
Defined in Data.Complex type Rep1 Complex = D1 ('MetaData "Complex" "Data.Complex" "base" 'False) (C1 ('MetaCons ":+" ('InfixI 'NotAssociative 6) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1)) | |
type Rep (Complex a) # | Since: base-4.9.0.0 |
Defined in Data.Complex type Rep (Complex a) = D1 ('MetaData "Complex" "Data.Complex" "base" 'False) (C1 ('MetaCons ":+" ('InfixI 'NotAssociative 6) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))) |
Polar form
mkPolar :: Floating a => a -> a -> Complex a Source #
Form a complex number from polar components of magnitude and phase.