{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Numeric.MixedTypes.Complex
(
tComplex
)
where
import Numeric.MixedTypes.PreludeHiding
import Utils.TH.DeclForTypes
import Data.Complex
import Numeric.MixedTypes.Literals
import Numeric.MixedTypes.Bool
import Numeric.MixedTypes.Eq
import Numeric.MixedTypes.MinMaxAbs
import Numeric.MixedTypes.AddSub
import Numeric.MixedTypes.Ring
import Numeric.MixedTypes.Div
import Numeric.MixedTypes.Elementary
tComplex :: T t -> T (Complex t)
tComplex :: T t -> T (Complex t)
tComplex (T String
tName) = String -> T (Complex t)
forall t. String -> T t
T (String
"(Complex " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
tName String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
instance (ConvertibleExactly Integer t) => (ConvertibleExactly Integer (Complex t))
where
safeConvertExactly :: Integer -> ConvertResult (Complex t)
safeConvertExactly Integer
n =
do
t
nT <- Integer -> ConvertResult t
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> ConvertResult t2
safeConvertExactly Integer
n
t
zT <- Integer -> ConvertResult t
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> ConvertResult t2
safeConvertExactly Integer
0
Complex t -> ConvertResult (Complex t)
forall (m :: * -> *) a. Monad m => a -> m a
return (Complex t -> ConvertResult (Complex t))
-> Complex t -> ConvertResult (Complex t)
forall a b. (a -> b) -> a -> b
$ t
nT t -> t -> Complex t
forall a. a -> a -> Complex a
:+ t
zT
instance (ConvertibleExactly Int t) => (ConvertibleExactly Int (Complex t))
where
safeConvertExactly :: Int -> ConvertResult (Complex t)
safeConvertExactly Int
n =
do
t
nT <- Int -> ConvertResult t
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> ConvertResult t2
safeConvertExactly Int
n
t
zT <- Int -> ConvertResult t
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> ConvertResult t2
safeConvertExactly (Integer -> Int
forall t. CanBeInt t => t -> Int
int Integer
0)
Complex t -> ConvertResult (Complex t)
forall (m :: * -> *) a. Monad m => a -> m a
return (Complex t -> ConvertResult (Complex t))
-> Complex t -> ConvertResult (Complex t)
forall a b. (a -> b) -> a -> b
$ t
nT t -> t -> Complex t
forall a. a -> a -> Complex a
:+ t
zT
instance (ConvertibleExactly Rational t) => (ConvertibleExactly Rational (Complex t))
where
safeConvertExactly :: Rational -> ConvertResult (Complex t)
safeConvertExactly Rational
r =
do
t
rT <- Rational -> ConvertResult t
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> ConvertResult t2
safeConvertExactly Rational
r
t
zT <- Rational -> ConvertResult t
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> ConvertResult t2
safeConvertExactly Rational
0.0
Complex t -> ConvertResult (Complex t)
forall (m :: * -> *) a. Monad m => a -> m a
return (Complex t -> ConvertResult (Complex t))
-> Complex t -> ConvertResult (Complex t)
forall a b. (a -> b) -> a -> b
$ t
rT t -> t -> Complex t
forall a. a -> a -> Complex a
:+ t
zT
instance (ConvertibleExactly t1 t2) => (ConvertibleExactly (Complex t1) (Complex t2))
where
safeConvertExactly :: Complex t1 -> ConvertResult (Complex t2)
safeConvertExactly (t1
a1 :+ t1
i1) =
do
t2
a2 <- t1 -> ConvertResult t2
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> ConvertResult t2
safeConvertExactly t1
a1
t2
i2 <- t1 -> ConvertResult t2
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> ConvertResult t2
safeConvertExactly t1
i1
Complex t2 -> ConvertResult (Complex t2)
forall (m :: * -> *) a. Monad m => a -> m a
return (Complex t2 -> ConvertResult (Complex t2))
-> Complex t2 -> ConvertResult (Complex t2)
forall a b. (a -> b) -> a -> b
$ t2
a2 t2 -> t2 -> Complex t2
forall a. a -> a -> Complex a
:+ t2
i2
instance (HasEqAsymmetric a b) => HasEqAsymmetric (Complex a) (Complex b) where
type EqCompareType (Complex a) (Complex b) = EqCompareType a b
equalTo :: Complex a -> Complex b -> EqCompareType (Complex a) (Complex b)
equalTo (a
a1 :+ a
i1) (b
a2 :+ b
i2) = (a
a1 a -> b -> EqCompareType a b
forall a b. HasEqAsymmetric a b => a -> b -> EqCompareType a b
== b
a2) EqCompareType a b
-> EqCompareType a b
-> AndOrType (EqCompareType a b) (EqCompareType a b)
forall a b. CanAndOrAsymmetric a b => a -> b -> AndOrType a b
&& (a
i1 a -> b -> EqCompareType a b
forall a b. HasEqAsymmetric a b => a -> b -> EqCompareType a b
== b
i2)
instance (CanTestInteger t, CanTestZero t) => CanTestInteger (Complex t) where
certainlyNotInteger :: Complex t -> Bool
certainlyNotInteger (t
a :+ t
i) =
t -> Bool
forall t. CanTestInteger t => t -> Bool
certainlyNotInteger t
a Bool -> Bool -> AndOrType Bool Bool
forall a b. CanAndOrAsymmetric a b => a -> b -> AndOrType a b
|| t -> Bool
forall t. CanTestZero t => t -> Bool
isCertainlyNonZero t
i
certainlyIntegerGetIt :: Complex t -> Maybe Integer
certainlyIntegerGetIt (t
a :+ t
i) =
case (t -> Maybe Integer
forall t. CanTestInteger t => t -> Maybe Integer
certainlyIntegerGetIt t
a, t -> Maybe Integer
forall t. CanTestInteger t => t -> Maybe Integer
certainlyIntegerGetIt t
i) of
(Just Integer
aN, Just Integer
iN) | Integer
iN Integer -> Integer -> EqCompareType Integer Integer
forall a b. HasEqAsymmetric a b => a -> b -> EqCompareType a b
== Integer
0 -> Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
aN
(Maybe Integer, Maybe Integer)
_ -> Maybe Integer
forall a. Maybe a
Nothing
instance CanNeg t => CanNeg (Complex t) where
type NegType (Complex t) = Complex (NegType t)
negate :: Complex t -> NegType (Complex t)
negate (t
a :+ t
i) = (t -> NegType t
forall t. CanNeg t => t -> NegType t
negate t
a) NegType t -> NegType t -> Complex (NegType t)
forall a. a -> a -> Complex a
:+ (t -> NegType t
forall t. CanNeg t => t -> NegType t
negate t
i)
instance (CanAddAsymmetric a b) => CanAddAsymmetric (Complex a) (Complex b) where
type AddType (Complex a) (Complex b) = Complex (AddType a b)
add :: Complex a -> Complex b -> AddType (Complex a) (Complex b)
add (a
a1 :+ a
i1) (b
a2 :+ b
i2) = (a
a1 a -> b -> AddType a b
forall t1 t2. CanAddAsymmetric t1 t2 => t1 -> t2 -> AddType t1 t2
+ b
a2) AddType a b -> AddType a b -> Complex (AddType a b)
forall a. a -> a -> Complex a
:+ (a
i1 a -> b -> AddType a b
forall t1 t2. CanAddAsymmetric t1 t2 => t1 -> t2 -> AddType t1 t2
+ b
i2)
instance (CanSub a b) => CanSub (Complex a) (Complex b) where
type SubType (Complex a) (Complex b) = Complex (SubType a b)
sub :: Complex a -> Complex b -> SubType (Complex a) (Complex b)
sub (a
a1 :+ a
i1) (b
a2 :+ b
i2) = (a
a1 a -> b -> SubType a b
forall t1 t2. CanSub t1 t2 => t1 -> t2 -> SubType t1 t2
- b
a2) SubType a b -> SubType a b -> Complex (SubType a b)
forall a. a -> a -> Complex a
:+ (a
i1 a -> b -> SubType a b
forall t1 t2. CanSub t1 t2 => t1 -> t2 -> SubType t1 t2
- b
i2)
instance
(CanMulAsymmetric a b
, CanAddSameType (MulType a b), CanSubSameType (MulType a b))
=>
CanMulAsymmetric (Complex a) (Complex b)
where
type MulType (Complex a) (Complex b) = Complex (MulType a b)
mul :: Complex a -> Complex b -> MulType (Complex a) (Complex b)
mul (a
a1 :+ a
i1) (b
a2 :+ b
i2) =
(a
a1a -> b -> MulType a b
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*b
a2 MulType a b -> MulType a b -> SubType (MulType a b) (MulType a b)
forall t1 t2. CanSub t1 t2 => t1 -> t2 -> SubType t1 t2
- a
i1a -> b -> MulType a b
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*b
i2) MulType a b -> MulType a b -> Complex (MulType a b)
forall a. a -> a -> Complex a
:+ (a
a1a -> b -> MulType a b
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*b
i2 MulType a b -> MulType a b -> AddType (MulType a b) (MulType a b)
forall t1 t2. CanAddAsymmetric t1 t2 => t1 -> t2 -> AddType t1 t2
+ a
i1a -> b -> MulType a b
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*b
a2)
instance
(CanMulAsymmetric a b
, CanAddSameType (MulType a b), CanSubSameType (MulType a b)
, CanMulAsymmetric b b, CanAddSameType (MulType b b)
, CanDiv (MulType a b) (MulType b b))
=>
CanDiv (Complex a) (Complex b)
where
type DivType (Complex a) (Complex b) = Complex (DivType (MulType a b) (MulType b b))
divide :: Complex a -> Complex b -> DivType (Complex a) (Complex b)
divide (a
a1 :+ a
i1) (b
a2 :+ b
i2) =
let d :: AddType (MulType b b) (MulType b b)
d = b
a2b -> b -> MulType b b
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*b
a2 MulType b b -> MulType b b -> AddType (MulType b b) (MulType b b)
forall t1 t2. CanAddAsymmetric t1 t2 => t1 -> t2 -> AddType t1 t2
+ b
i2b -> b -> MulType b b
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*b
i2 in
((a
a1a -> b -> MulType a b
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*b
a2 MulType a b -> MulType a b -> AddType (MulType a b) (MulType a b)
forall t1 t2. CanAddAsymmetric t1 t2 => t1 -> t2 -> AddType t1 t2
+ a
i1a -> b -> MulType a b
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*b
i2)MulType a b -> MulType b b -> DivType (MulType a b) (MulType b b)
forall t1 t2. CanDiv t1 t2 => t1 -> t2 -> DivType t1 t2
/AddType (MulType b b) (MulType b b)
MulType b b
d) DivType (MulType a b) (MulType b b)
-> DivType (MulType a b) (MulType b b)
-> Complex (DivType (MulType a b) (MulType b b))
forall a. a -> a -> Complex a
:+ ((a
i1a -> b -> MulType a b
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*b
a2MulType a b -> MulType a b -> SubType (MulType a b) (MulType a b)
forall t1 t2. CanSub t1 t2 => t1 -> t2 -> SubType t1 t2
-a
a1a -> b -> MulType a b
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*b
i2)MulType a b -> MulType b b -> DivType (MulType a b) (MulType b b)
forall t1 t2. CanDiv t1 t2 => t1 -> t2 -> DivType t1 t2
/AddType (MulType b b) (MulType b b)
MulType b b
d)
instance
(CanMulAsymmetric t t
, CanAddSameType (MulType t t)
, CanSqrt (MulType t t))
=>
CanAbs (Complex t)
where
type AbsType (Complex t) = SqrtType (MulType t t)
abs :: Complex t -> AbsType (Complex t)
abs (t
a :+ t
i) = MulType t t -> SqrtType (MulType t t)
forall t. CanSqrt t => t -> SqrtType t
sqrt (t
at -> t -> MulType t t
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*t
a MulType t t -> MulType t t -> AddType (MulType t t) (MulType t t)
forall t1 t2. CanAddAsymmetric t1 t2 => t1 -> t2 -> AddType t1 t2
+ t
it -> t -> MulType t t
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
*t
i)
instance
(CanExp t
, CanSinCos t
, CanMulAsymmetric (ExpType t) (SinCosType t))
=>
CanExp (Complex t)
where
type ExpType (Complex t) = Complex (MulType (ExpType t) (SinCosType t))
exp :: Complex t -> ExpType (Complex t)
exp (t
a :+ t
i) =
let ea :: ExpType t
ea = t -> ExpType t
forall t. CanExp t => t -> ExpType t
exp t
a in
(ExpType t
ea ExpType t -> SinCosType t -> MulType (ExpType t) (SinCosType t)
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
* t -> SinCosType t
forall t. CanSinCos t => t -> SinCosType t
cos t
i) MulType (ExpType t) (SinCosType t)
-> MulType (ExpType t) (SinCosType t)
-> Complex (MulType (ExpType t) (SinCosType t))
forall a. a -> a -> Complex a
:+ (ExpType t
ea ExpType t -> SinCosType t -> MulType (ExpType t) (SinCosType t)
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
* t -> SinCosType t
forall t. CanSinCos t => t -> SinCosType t
sin t
i)
$(declForTypes
[[t| Integer |], [t| Int |], [t| Rational |], [t| Double |]]
(\ t -> [d|
instance (HasEqAsymmetric $t b) => HasEqAsymmetric $t (Complex b) where
type EqCompareType $t (Complex b) = EqCompareType $t b
equalTo n (a2 :+ i2) = (n == a2) && (convertExactlyTargetSample n 0 == i2)
instance (HasEqAsymmetric a $t) => HasEqAsymmetric (Complex a) $t where
type EqCompareType (Complex a) $t = EqCompareType a $t
equalTo (a1 :+ i1) n = (a1 == n) && (i1 == convertExactlyTargetSample n 0)
instance (CanAddAsymmetric $t b) => CanAddAsymmetric $t (Complex b) where
type AddType $t (Complex b) = Complex (AddType $t b)
add n (a2 :+ i2) = (n + a2) :+ (convertExactlyTargetSample n 0 + i2)
instance (CanAddAsymmetric a $t) => CanAddAsymmetric (Complex a) $t where
type AddType (Complex a) $t = Complex (AddType a $t)
add (a1 :+ i1) n = (a1 + n) :+ (i1 + (convertExactlyTargetSample n 0))
instance (CanSub $t b) => CanSub $t (Complex b) where
type SubType $t (Complex b) = Complex (SubType $t b)
sub n (a2 :+ i2) = (n - a2) :+ (convertExactlyTargetSample n 0 - i2)
instance (CanSub a $t) => CanSub (Complex a) $t where
type SubType (Complex a) $t = Complex (SubType a $t)
sub (a1 :+ i1) n = (a1 - n) :+ (i1 - (convertExactlyTargetSample n 0))
instance
(CanMulAsymmetric $t b) => CanMulAsymmetric $t (Complex b)
where
type MulType $t (Complex b) = Complex (MulType $t b)
mul n (a2 :+ i2) = (n*a2) :+ (n*i2)
instance
(CanMulAsymmetric a $t) => CanMulAsymmetric (Complex a) $t
where
type MulType (Complex a) $t = Complex (MulType a $t)
mul (a1 :+ i1) n = (a1*n) :+ (i1*n)
instance
(CanMulAsymmetric $t b
, CanMulAsymmetric b b, CanAddSameType (MulType b b)
, CanDiv (MulType $t b) (MulType b b))
=>
CanDiv $t (Complex b)
where
type DivType $t (Complex b) = Complex (DivType (MulType $t b) (MulType b b))
divide n (a2 :+ i2) =
let d = a2*a2 + i2*i2 in
((n*a2)/d) :+ (((-n)*i2)/d)
instance
(CanDiv a $t) => CanDiv (Complex a) $t
where
type DivType (Complex a) $t = Complex (DivType a $t)
divide (a1 :+ i1) n = (a1/n) :+ (i1/n)
|]))