{-# LANGUAGE DeriveDataTypeable #-}
{- |
Module      :  Fractal.RUFF.Types.Complex
Copyright   :  (c) Claude Heiland-Allen 2011
License     :  BSD3

Maintainer  :  claudiusmaximus@goto10.org
Stability   :  unstable
Portability :  portable

Complex numbers without the 'RealFloat' constraint.
-}

module Fractal.RUFF.Types.Complex
  ( Complex((:+)), cis, mkPolar
  , realPart, imagPart, conjugate
  , magnitude, phase, polar
  ) where

import Data.Data (Data)
import Data.Typeable (Typeable)

-- | Complex number type without the 'RealFloat' constraint.
data Complex r = !r :+ !r
  deriving (Read, Show, Eq, Ord, Data, Typeable)

instance Num r => Num (Complex r) where
  (x :+ y) + (u :+ v) = (x + u) :+ (y + v)
  (x :+ y) - (u :+ v) = (x - u) :+ (y - v)
  (x :+ y) * (u :+ v) = (x * u - y * v) :+ (x * v + y * u)
  negate (x :+ y) = negate x :+ negate y
  abs = error "Fractal.Types.Complex.Num.abs"
  signum = error "Fractal.Types.Complex.Num.signum"
  fromInteger n = fromInteger n :+ 0

instance Fractional r => Fractional (Complex r) where
  (x :+ y) / (u :+ v) = ((x * u + y * v) / d) :+ ((y * u - x * v) / d) where d = u * u + v * v
  fromRational r = fromRational r :+ 0

-- | Extract the real part.
realPart :: Complex r -> r
realPart (r :+ _) = r

-- | Extract the imaginary part.
imagPart :: Complex r -> r
imagPart (_ :+ i) = i

-- | Complex conjugate.
conjugate :: Num r => Complex r -> Complex r
conjugate (r :+ i) = r :+ negate i

-- | Complex phase.
phase :: (Ord r, Floating r) => Complex r -> r
phase (r :+ i)
  | r > 0 && i > 0 =      atan (    i /     r)
  | r > 0 && i < 0 =    - atan (abs i /     r)
  | r < 0 && i > 0 = pi - atan (    i / abs r)
  | r < 0 && i < 0 =      atan (abs i / abs r) - pi
  | i > 0          =      pi / 2
  | i < 0          =    - pi / 2
  | r < 0          =      pi
  | otherwise      =      0

-- | Complex magnitude.
magnitude :: Floating r => Complex r -> r
magnitude (r :+ i) = sqrt $ r * r + i * i

-- | Complex number with the given magnitude and phase.
mkPolar :: Floating r => r -> r -> Complex r
mkPolar r t = (r * cos t) :+ (r * sin t)

-- | Complex number with magnitude 1 and the given phase.
cis :: Floating r => r -> Complex r
cis t = cos t :+ sin t

-- | Convert to polar form.
polar :: (Ord r, Floating r) => Complex r -> (r, r)
polar z = (magnitude z, phase z)