{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

-- | Complex numbers.
module NumHask.Data.Complex
  ( Complex (..),
    (+:),
    realPart,
    imagPart,
  )
where

import Data.Data (Data)
import GHC.Generics
import NumHask.Algebra.Additive
import NumHask.Algebra.Field
import NumHask.Algebra.Lattice
import NumHask.Algebra.Metric
import NumHask.Algebra.Multiplicative
import NumHask.Algebra.Ring
import NumHask.Data.Integral
import Prelude hiding
  ( Num (..),
    atan,
    atan2,
    ceiling,
    cos,
    exp,
    floor,
    fromIntegral,
    log,
    negate,
    pi,
    properFraction,
    recip,
    round,
    sin,
    sqrt,
    truncate,
    (/),
  )

-- | The underlying representation is a newtype-wrapped tuple, compared with the base datatype. This was chosen to facilitate the use of DerivingVia.
newtype Complex a = Complex {forall a. Complex a -> (a, a)
complexPair :: (a, a)}
  deriving stock
    ( Complex a -> Complex a -> Bool
(Complex a -> Complex a -> Bool)
-> (Complex a -> Complex a -> Bool) -> Eq (Complex a)
forall a. Eq a => Complex a -> Complex a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Complex a -> Complex a -> Bool
== :: Complex a -> Complex a -> Bool
$c/= :: forall a. Eq a => Complex a -> Complex a -> Bool
/= :: Complex a -> Complex a -> Bool
Eq,
      Int -> Complex a -> ShowS
[Complex a] -> ShowS
Complex a -> String
(Int -> Complex a -> ShowS)
-> (Complex a -> String)
-> ([Complex a] -> ShowS)
-> Show (Complex a)
forall a. Show a => Int -> Complex a -> ShowS
forall a. Show a => [Complex a] -> ShowS
forall a. Show a => Complex a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Complex a -> ShowS
showsPrec :: Int -> Complex a -> ShowS
$cshow :: forall a. Show a => Complex a -> String
show :: Complex a -> String
$cshowList :: forall a. Show a => [Complex a] -> ShowS
showList :: [Complex a] -> ShowS
Show,
      ReadPrec [Complex a]
ReadPrec (Complex a)
Int -> ReadS (Complex a)
ReadS [Complex a]
(Int -> ReadS (Complex a))
-> ReadS [Complex a]
-> ReadPrec (Complex a)
-> ReadPrec [Complex a]
-> Read (Complex a)
forall a. Read a => ReadPrec [Complex a]
forall a. Read a => ReadPrec (Complex a)
forall a. Read a => Int -> ReadS (Complex a)
forall a. Read a => ReadS [Complex a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall a. Read a => Int -> ReadS (Complex a)
readsPrec :: Int -> ReadS (Complex a)
$creadList :: forall a. Read a => ReadS [Complex a]
readList :: ReadS [Complex a]
$creadPrec :: forall a. Read a => ReadPrec (Complex a)
readPrec :: ReadPrec (Complex a)
$creadListPrec :: forall a. Read a => ReadPrec [Complex a]
readListPrec :: ReadPrec [Complex a]
Read,
      Typeable (Complex a)
Typeable (Complex a) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Complex a -> c (Complex a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (Complex a))
-> (Complex a -> Constr)
-> (Complex a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (Complex a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (Complex a)))
-> ((forall b. Data b => b -> b) -> Complex a -> Complex a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Complex a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Complex a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Complex a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Complex a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Complex a -> m (Complex a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Complex a -> m (Complex a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Complex a -> m (Complex a))
-> Data (Complex a)
Complex a -> Constr
Complex a -> DataType
(forall b. Data b => b -> b) -> Complex a -> Complex a
forall a. Data a => Typeable (Complex a)
forall a. Data a => Complex a -> Constr
forall a. Data a => Complex a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> Complex a -> Complex a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Complex a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> Complex a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Complex a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Complex a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Complex a -> m (Complex a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Complex a -> m (Complex a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Complex a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Complex a -> c (Complex a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Complex a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Complex a))
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Complex a -> u
forall u. (forall d. Data d => d -> u) -> Complex a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Complex a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Complex a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Complex a -> m (Complex a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Complex a -> m (Complex a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Complex a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Complex a -> c (Complex a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Complex a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Complex a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Complex a -> c (Complex a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Complex a -> c (Complex a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Complex a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Complex a)
$ctoConstr :: forall a. Data a => Complex a -> Constr
toConstr :: Complex a -> Constr
$cdataTypeOf :: forall a. Data a => Complex a -> DataType
dataTypeOf :: Complex a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Complex a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Complex a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Complex a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Complex a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Complex a -> Complex a
gmapT :: (forall b. Data b => b -> b) -> Complex a -> Complex a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Complex a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Complex a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Complex a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Complex a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> Complex a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Complex a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Complex a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Complex a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Complex a -> m (Complex a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Complex a -> m (Complex a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Complex a -> m (Complex a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Complex a -> m (Complex a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Complex a -> m (Complex a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Complex a -> m (Complex a)
Data,
      (forall x. Complex a -> Rep (Complex a) x)
-> (forall x. Rep (Complex a) x -> Complex a)
-> Generic (Complex a)
forall x. Rep (Complex a) x -> Complex a
forall x. Complex a -> Rep (Complex a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Complex a) x -> Complex a
forall a x. Complex a -> Rep (Complex a) x
$cfrom :: forall a x. Complex a -> Rep (Complex a) x
from :: forall x. Complex a -> Rep (Complex a) x
$cto :: forall a x. Rep (Complex a) x -> Complex a
to :: forall x. Rep (Complex a) x -> Complex a
Generic,
      (forall a b. (a -> b) -> Complex a -> Complex b)
-> (forall a b. a -> Complex b -> Complex a) -> Functor Complex
forall a b. a -> Complex b -> Complex a
forall a b. (a -> b) -> Complex a -> Complex b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Complex a -> Complex b
fmap :: forall a b. (a -> b) -> Complex a -> Complex b
$c<$ :: forall a b. a -> Complex b -> Complex a
<$ :: forall a b. a -> Complex b -> Complex a
Functor
    )
  deriving
    ( Complex a
Complex a -> Complex a -> Complex a
(Complex a -> Complex a -> Complex a)
-> Complex a -> Additive (Complex a)
forall a. Additive a => Complex a
forall a. Additive a => Complex a -> Complex a -> Complex a
forall a. (a -> a -> a) -> a -> Additive a
$c+ :: forall a. Additive a => Complex a -> Complex a -> Complex a
+ :: Complex a -> Complex a -> Complex a
$czero :: forall a. Additive a => Complex a
zero :: Complex a
Additive,
      Additive (Complex a)
Additive (Complex a) =>
(Complex a -> Complex a)
-> (Complex a -> Complex a -> Complex a) -> Subtractive (Complex a)
Complex a -> Complex a
Complex a -> Complex a -> Complex a
forall a. Subtractive a => Additive (Complex a)
forall a. Subtractive a => Complex a -> Complex a
forall a. Subtractive a => Complex a -> Complex a -> Complex a
forall a. Additive a => (a -> a) -> (a -> a -> a) -> Subtractive a
$cnegate :: forall a. Subtractive a => Complex a -> Complex a
negate :: Complex a -> Complex a
$c- :: forall a. Subtractive a => Complex a -> Complex a -> Complex a
- :: Complex a -> Complex a -> Complex a
Subtractive,
      Distributive (Mag (Complex a))
Distributive (Mag (Complex a)) =>
(Complex a -> Mag (Complex a))
-> (Complex a -> Base (Complex a)) -> Basis (Complex a)
Complex a -> Mag (Complex a)
Complex a -> Base (Complex a)
forall a.
Distributive (Mag a) =>
(a -> Mag a) -> (a -> Base a) -> Basis a
forall a. (ExpField a, Eq a) => Distributive (Mag (Complex a))
forall a. (ExpField a, Eq a) => Complex a -> Mag (Complex a)
forall a. (ExpField a, Eq a) => Complex a -> Base (Complex a)
$cmagnitude :: forall a. (ExpField a, Eq a) => Complex a -> Mag (Complex a)
magnitude :: Complex a -> Mag (Complex a)
$cbasis :: forall a. (ExpField a, Eq a) => Complex a -> Base (Complex a)
basis :: Complex a -> Base (Complex a)
Basis,
      Distributive (Dir (Complex a))
Distributive (Complex a)
(Distributive (Complex a), Distributive (Dir (Complex a))) =>
(Complex a -> Dir (Complex a))
-> (Dir (Complex a) -> Complex a) -> Direction (Complex a)
Dir (Complex a) -> Complex a
Complex a -> Dir (Complex a)
forall coord.
(Distributive coord, Distributive (Dir coord)) =>
(coord -> Dir coord) -> (Dir coord -> coord) -> Direction coord
forall a. TrigField a => Distributive (Dir (Complex a))
forall a. TrigField a => Distributive (Complex a)
forall a. TrigField a => Dir (Complex a) -> Complex a
forall a. TrigField a => Complex a -> Dir (Complex a)
$cangle :: forall a. TrigField a => Complex a -> Dir (Complex a)
angle :: Complex a -> Dir (Complex a)
$cray :: forall a. TrigField a => Dir (Complex a) -> Complex a
ray :: Dir (Complex a) -> Complex a
Direction,
      Eq (Complex a)
Additive (Complex a)
Complex a
(Eq (Complex a), Additive (Complex a)) =>
Complex a -> Epsilon (Complex a)
forall a. (Eq a, Additive a) => a -> Epsilon a
forall a. Epsilon a => Eq (Complex a)
forall a. Epsilon a => Additive (Complex a)
forall a. Epsilon a => Complex a
$cepsilon :: forall a. Epsilon a => Complex a
epsilon :: Complex a
Epsilon,
      Eq (Complex a)
Eq (Complex a) =>
(Complex a -> Complex a -> Complex a)
-> JoinSemiLattice (Complex a)
Complex a -> Complex a -> Complex a
forall a. Eq a => (a -> a -> a) -> JoinSemiLattice a
forall a. JoinSemiLattice a => Eq (Complex a)
forall a. JoinSemiLattice a => Complex a -> Complex a -> Complex a
$c\/ :: forall a. JoinSemiLattice a => Complex a -> Complex a -> Complex a
\/ :: Complex a -> Complex a -> Complex a
JoinSemiLattice,
      Eq (Complex a)
Eq (Complex a) =>
(Complex a -> Complex a -> Complex a)
-> MeetSemiLattice (Complex a)
Complex a -> Complex a -> Complex a
forall a. Eq a => (a -> a -> a) -> MeetSemiLattice a
forall a. MeetSemiLattice a => Eq (Complex a)
forall a. MeetSemiLattice a => Complex a -> Complex a -> Complex a
$c/\ :: forall a. MeetSemiLattice a => Complex a -> Complex a -> Complex a
/\ :: Complex a -> Complex a -> Complex a
MeetSemiLattice,
      JoinSemiLattice (Complex a)
Complex a
JoinSemiLattice (Complex a) =>
Complex a -> BoundedJoinSemiLattice (Complex a)
forall a. BoundedJoinSemiLattice a => JoinSemiLattice (Complex a)
forall a. BoundedJoinSemiLattice a => Complex a
forall a. JoinSemiLattice a => a -> BoundedJoinSemiLattice a
$cbottom :: forall a. BoundedJoinSemiLattice a => Complex a
bottom :: Complex a
BoundedJoinSemiLattice,
      MeetSemiLattice (Complex a)
Complex a
MeetSemiLattice (Complex a) =>
Complex a -> BoundedMeetSemiLattice (Complex a)
forall a. BoundedMeetSemiLattice a => MeetSemiLattice (Complex a)
forall a. BoundedMeetSemiLattice a => Complex a
forall a. MeetSemiLattice a => a -> BoundedMeetSemiLattice a
$ctop :: forall a. BoundedMeetSemiLattice a => Complex a
top :: Complex a
BoundedMeetSemiLattice,
      Field (Complex a)
Field (Complex a) =>
(Complex a -> Complex a)
-> (Complex a -> Complex a)
-> (Complex a -> Complex a -> Complex a)
-> (Complex a -> Complex a -> Complex a)
-> (Complex a -> Complex a)
-> ExpField (Complex a)
Complex a -> Complex a
Complex a -> Complex a -> Complex a
forall a. (Ord a, TrigField a, ExpField a) => Field (Complex a)
forall a.
(Ord a, TrigField a, ExpField a) =>
Complex a -> Complex a
forall a.
(Ord a, TrigField a, ExpField a) =>
Complex a -> Complex a -> Complex a
forall a.
Field a =>
(a -> a)
-> (a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> ExpField a
$cexp :: forall a.
(Ord a, TrigField a, ExpField a) =>
Complex a -> Complex a
exp :: Complex a -> Complex a
$clog :: forall a.
(Ord a, TrigField a, ExpField a) =>
Complex a -> Complex a
log :: Complex a -> Complex a
$c** :: forall a.
(Ord a, TrigField a, ExpField a) =>
Complex a -> Complex a -> Complex a
** :: Complex a -> Complex a -> Complex a
$clogBase :: forall a.
(Ord a, TrigField a, ExpField a) =>
Complex a -> Complex a -> Complex a
logBase :: Complex a -> Complex a -> Complex a
$csqrt :: forall a.
(Ord a, TrigField a, ExpField a) =>
Complex a -> Complex a
sqrt :: Complex a -> Complex a
ExpField
    )
    via (EuclideanPair a)

infixl 6 +:

-- | Complex number constructor.
(+:) :: a -> a -> Complex a
+: :: forall a. a -> a -> Complex a
(+:) a
r a
i = (a, a) -> Complex a
forall a. (a, a) -> Complex a
Complex (a
r, a
i)

-- | Extracts the real part of a complex number.
realPart :: Complex a -> a
realPart :: forall a. Complex a -> a
realPart (Complex (a
x, a
_)) = a
x

-- | Extracts the imaginary part of a complex number.
imagPart :: Complex a -> a
imagPart :: forall a. Complex a -> a
imagPart (Complex (a
_, a
y)) = a
y

instance
  (Subtractive a, Multiplicative a) =>
  Multiplicative (Complex a)
  where
  (Complex (a
r, a
i)) * :: Complex a -> Complex a -> Complex a
* (Complex (a
r', a
i')) =
    (a, a) -> Complex a
forall a. (a, a) -> Complex a
Complex (a
r a -> a -> a
forall a. Multiplicative a => a -> a -> a
* a
r' a -> a -> a
forall a. Subtractive a => a -> a -> a
- a
i a -> a -> a
forall a. Multiplicative a => a -> a -> a
* a
i', a
i a -> a -> a
forall a. Multiplicative a => a -> a -> a
* a
r' a -> a -> a
forall a. Additive a => a -> a -> a
+ a
i' a -> a -> a
forall a. Multiplicative a => a -> a -> a
* a
r)
  one :: Complex a
one = a
forall a. Multiplicative a => a
one a -> a -> Complex a
forall a. a -> a -> Complex a
+: a
forall a. Additive a => a
zero

instance
  (Subtractive a, Divisive a) =>
  Divisive (Complex a)
  where
  recip :: Complex a -> Complex a
recip (Complex (a
r, a
i)) = (a
r a -> a -> a
forall a. Multiplicative a => a -> a -> a
* a
d) a -> a -> Complex a
forall a. a -> a -> Complex a
+: (a -> a
forall a. Subtractive a => a -> a
negate a
i a -> a -> a
forall a. Multiplicative a => a -> a -> a
* a
d)
    where
      d :: a
d = a -> a
forall a. Divisive a => a -> a
recip ((a
r a -> a -> a
forall a. Multiplicative a => a -> a -> a
* a
r) a -> a -> a
forall a. Additive a => a -> a -> a
+ (a
i a -> a -> a
forall a. Multiplicative a => a -> a -> a
* a
i))

instance
  (Additive a, FromIntegral a b) =>
  FromIntegral (Complex a) b
  where
  fromIntegral :: b -> Complex a
fromIntegral b
x = b -> a
forall a b. FromIntegral a b => b -> a
fromIntegral b
x a -> a -> Complex a
forall a. a -> a -> Complex a
+: a
forall a. Additive a => a
zero

instance (Distributive a, Subtractive a) => InvolutiveRing (Complex a) where
  adj :: Complex a -> Complex a
adj (Complex (a
r, a
i)) = a
r a -> a -> Complex a
forall a. a -> a -> Complex a
+: a -> a
forall a. Subtractive a => a -> a
negate a
i

-- Can't use DerivingVia due to extra Whole constraints
instance (Subtractive a, QuotientField a) => QuotientField (Complex a) where
  type Whole (Complex a) = Complex (Whole a)

  properFraction :: Complex a -> (Whole (Complex a), Complex a)
properFraction (Complex (a
x, a
y)) =
    ((Whole a, Whole a) -> Complex (Whole a)
forall a. (a, a) -> Complex a
Complex (Whole a
xwhole, Whole a
ywhole), (a, a) -> Complex a
forall a. (a, a) -> Complex a
Complex (a
xfrac, a
yfrac))
    where
      (Whole a
xwhole, a
xfrac) = a -> (Whole a, a)
forall a. QuotientField a => a -> (Whole a, a)
properFraction a
x
      (Whole a
ywhole, a
yfrac) = a -> (Whole a, a)
forall a. QuotientField a => a -> (Whole a, a)
properFraction a
y

  round :: Complex a -> Whole (Complex a)
round (Complex (a
x, a
y)) = (Whole a, Whole a) -> Complex (Whole a)
forall a. (a, a) -> Complex a
Complex (a -> Whole a
forall a. QuotientField a => a -> Whole a
round a
x, a -> Whole a
forall a. QuotientField a => a -> Whole a
round a
y)
  ceiling :: Complex a -> Whole (Complex a)
ceiling (Complex (a
x, a
y)) = (Whole a, Whole a) -> Complex (Whole a)
forall a. (a, a) -> Complex a
Complex (a -> Whole a
forall a. QuotientField a => a -> Whole a
ceiling a
x, a -> Whole a
forall a. QuotientField a => a -> Whole a
ceiling a
y)
  floor :: Complex a -> Whole (Complex a)
floor (Complex (a
x, a
y)) = (Whole a, Whole a) -> Complex (Whole a)
forall a. (a, a) -> Complex a
Complex (a -> Whole a
forall a. QuotientField a => a -> Whole a
floor a
x, a -> Whole a
forall a. QuotientField a => a -> Whole a
floor a
y)
  truncate :: Complex a -> Whole (Complex a)
truncate (Complex (a
x, a
y)) = (Whole a, Whole a) -> Complex (Whole a)
forall a. (a, a) -> Complex a
Complex (a -> Whole a
forall a. QuotientField a => a -> Whole a
truncate a
x, a -> Whole a
forall a. QuotientField a => a -> Whole a
truncate a
y)