mixed-types-num-0.4.0.1: Alternative Prelude with numeric and logic expressions typed bottom-up

Copyright(c) Michal Konecny
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Numeric.MixedTypes.Complex

Contents

Description

Instances for Data.Complex.

Documentation

tComplex :: T t -> T (Complex t) Source #

Orphan instances

ConvertibleExactly Int t => ConvertibleExactly Int (Complex t) Source # 
Instance details

ConvertibleExactly Integer t => ConvertibleExactly Integer (Complex t) Source # 
Instance details

ConvertibleExactly Rational t => ConvertibleExactly Rational (Complex t) Source # 
Instance details

HasEqAsymmetric Double b => HasEqAsymmetric Double (Complex b) Source # 
Instance details

Associated Types

type EqCompareType Double (Complex b) :: Type Source #

HasEqAsymmetric Int b => HasEqAsymmetric Int (Complex b) Source # 
Instance details

Associated Types

type EqCompareType Int (Complex b) :: Type Source #

HasEqAsymmetric Integer b => HasEqAsymmetric Integer (Complex b) Source # 
Instance details

Associated Types

type EqCompareType Integer (Complex b) :: Type Source #

HasEqAsymmetric Rational b => HasEqAsymmetric Rational (Complex b) Source # 
Instance details

Associated Types

type EqCompareType Rational (Complex b) :: Type Source #

CanSub Double b => CanSub Double (Complex b) Source # 
Instance details

Associated Types

type SubType Double (Complex b) :: Type Source #

Methods

sub :: Double -> Complex b -> SubType Double (Complex b) Source #

CanSub Int b => CanSub Int (Complex b) Source # 
Instance details

Associated Types

type SubType Int (Complex b) :: Type Source #

Methods

sub :: Int -> Complex b -> SubType Int (Complex b) Source #

CanSub Integer b => CanSub Integer (Complex b) Source # 
Instance details

Associated Types

type SubType Integer (Complex b) :: Type Source #

CanSub Rational b => CanSub Rational (Complex b) Source # 
Instance details

Associated Types

type SubType Rational (Complex b) :: Type Source #

CanAddAsymmetric Double b => CanAddAsymmetric Double (Complex b) Source # 
Instance details

Associated Types

type AddType Double (Complex b) :: Type Source #

Methods

add :: Double -> Complex b -> AddType Double (Complex b) Source #

CanAddAsymmetric Int b => CanAddAsymmetric Int (Complex b) Source # 
Instance details

Associated Types

type AddType Int (Complex b) :: Type Source #

Methods

add :: Int -> Complex b -> AddType Int (Complex b) Source #

CanAddAsymmetric Integer b => CanAddAsymmetric Integer (Complex b) Source # 
Instance details

Associated Types

type AddType Integer (Complex b) :: Type Source #

CanAddAsymmetric Rational b => CanAddAsymmetric Rational (Complex b) Source # 
Instance details

Associated Types

type AddType Rational (Complex b) :: Type Source #

CanMulAsymmetric Double b => CanMulAsymmetric Double (Complex b) Source # 
Instance details

Associated Types

type MulType Double (Complex b) :: Type Source #

Methods

mul :: Double -> Complex b -> MulType Double (Complex b) Source #

CanMulAsymmetric Int b => CanMulAsymmetric Int (Complex b) Source # 
Instance details

Associated Types

type MulType Int (Complex b) :: Type Source #

Methods

mul :: Int -> Complex b -> MulType Int (Complex b) Source #

CanMulAsymmetric Integer b => CanMulAsymmetric Integer (Complex b) Source # 
Instance details

Associated Types

type MulType Integer (Complex b) :: Type Source #

CanMulAsymmetric Rational b => CanMulAsymmetric Rational (Complex b) Source # 
Instance details

Associated Types

type MulType Rational (Complex b) :: Type Source #

(CanMulAsymmetric Double b, CanMulAsymmetric b b, CanAddSameType (MulType b b), CanDiv (MulType Double b) (MulType b b)) => CanDiv Double (Complex b) Source # 
Instance details

Associated Types

type DivTypeNoCN Double (Complex b) :: Type Source #

type DivType Double (Complex b) :: Type Source #

(CanMulAsymmetric Int b, CanMulAsymmetric b b, CanAddSameType (MulType b b), CanDiv (MulType Int b) (MulType b b)) => CanDiv Int (Complex b) Source # 
Instance details

Associated Types

type DivTypeNoCN Int (Complex b) :: Type Source #

type DivType Int (Complex b) :: Type Source #

(CanMulAsymmetric Integer b, CanMulAsymmetric b b, CanAddSameType (MulType b b), CanDiv (MulType Integer b) (MulType b b)) => CanDiv Integer (Complex b) Source # 
Instance details

Associated Types

type DivTypeNoCN Integer (Complex b) :: Type Source #

type DivType Integer (Complex b) :: Type Source #

(CanMulAsymmetric Rational b, CanMulAsymmetric b b, CanAddSameType (MulType b b), CanDiv (MulType Rational b) (MulType b b)) => CanDiv Rational (Complex b) Source # 
Instance details

Associated Types

type DivTypeNoCN Rational (Complex b) :: Type Source #

type DivType Rational (Complex b) :: Type Source #

CanNeg t => CanNeg (Complex t) Source # 
Instance details

Associated Types

type NegType (Complex t) :: Type Source #

Methods

negate :: Complex t -> NegType (Complex t) Source #

(CanTestInteger t, CanTestZero t) => CanTestInteger (Complex t) Source # 
Instance details

(CanMulAsymmetric t t, CanAddSameType (MulType t t), CanSqrt (MulType t t)) => CanAbs (Complex t) Source # 
Instance details

Associated Types

type AbsType (Complex t) :: Type Source #

Methods

abs :: Complex t -> AbsType (Complex t) Source #

(CanExp t, CanSinCos t, CanMulAsymmetric (ExpType t) (SinCosType t)) => CanExp (Complex t) Source # 
Instance details

Associated Types

type ExpType (Complex t) :: Type Source #

Methods

exp :: Complex t -> ExpType (Complex t) Source #

HasEqAsymmetric a Integer => HasEqAsymmetric (Complex a) Integer Source # 
Instance details

Associated Types

type EqCompareType (Complex a) Integer :: Type Source #

HasEqAsymmetric a Int => HasEqAsymmetric (Complex a) Int Source # 
Instance details

Associated Types

type EqCompareType (Complex a) Int :: Type Source #

HasEqAsymmetric a Rational => HasEqAsymmetric (Complex a) Rational Source # 
Instance details

Associated Types

type EqCompareType (Complex a) Rational :: Type Source #

HasEqAsymmetric a Double => HasEqAsymmetric (Complex a) Double Source # 
Instance details

Associated Types

type EqCompareType (Complex a) Double :: Type Source #

CanSub a Integer => CanSub (Complex a) Integer Source # 
Instance details

Associated Types

type SubType (Complex a) Integer :: Type Source #

CanSub a Int => CanSub (Complex a) Int Source # 
Instance details

Associated Types

type SubType (Complex a) Int :: Type Source #

Methods

sub :: Complex a -> Int -> SubType (Complex a) Int Source #

CanSub a Rational => CanSub (Complex a) Rational Source # 
Instance details

Associated Types

type SubType (Complex a) Rational :: Type Source #

CanSub a Double => CanSub (Complex a) Double Source # 
Instance details

Associated Types

type SubType (Complex a) Double :: Type Source #

Methods

sub :: Complex a -> Double -> SubType (Complex a) Double Source #

CanAddAsymmetric a Integer => CanAddAsymmetric (Complex a) Integer Source # 
Instance details

Associated Types

type AddType (Complex a) Integer :: Type Source #

CanAddAsymmetric a Int => CanAddAsymmetric (Complex a) Int Source # 
Instance details

Associated Types

type AddType (Complex a) Int :: Type Source #

Methods

add :: Complex a -> Int -> AddType (Complex a) Int Source #

CanAddAsymmetric a Rational => CanAddAsymmetric (Complex a) Rational Source # 
Instance details

Associated Types

type AddType (Complex a) Rational :: Type Source #

CanAddAsymmetric a Double => CanAddAsymmetric (Complex a) Double Source # 
Instance details

Associated Types

type AddType (Complex a) Double :: Type Source #

Methods

add :: Complex a -> Double -> AddType (Complex a) Double Source #

CanMulAsymmetric a Integer => CanMulAsymmetric (Complex a) Integer Source # 
Instance details

Associated Types

type MulType (Complex a) Integer :: Type Source #

CanMulAsymmetric a Int => CanMulAsymmetric (Complex a) Int Source # 
Instance details

Associated Types

type MulType (Complex a) Int :: Type Source #

Methods

mul :: Complex a -> Int -> MulType (Complex a) Int Source #

CanMulAsymmetric a Rational => CanMulAsymmetric (Complex a) Rational Source # 
Instance details

Associated Types

type MulType (Complex a) Rational :: Type Source #

CanMulAsymmetric a Double => CanMulAsymmetric (Complex a) Double Source # 
Instance details

Associated Types

type MulType (Complex a) Double :: Type Source #

Methods

mul :: Complex a -> Double -> MulType (Complex a) Double Source #

CanDiv a Integer => CanDiv (Complex a) Integer Source # 
Instance details

Associated Types

type DivTypeNoCN (Complex a) Integer :: Type Source #

type DivType (Complex a) Integer :: Type Source #

CanDiv a Int => CanDiv (Complex a) Int Source # 
Instance details

Associated Types

type DivTypeNoCN (Complex a) Int :: Type Source #

type DivType (Complex a) Int :: Type Source #

CanDiv a Rational => CanDiv (Complex a) Rational Source # 
Instance details

Associated Types

type DivTypeNoCN (Complex a) Rational :: Type Source #

type DivType (Complex a) Rational :: Type Source #

CanDiv a Double => CanDiv (Complex a) Double Source # 
Instance details

Associated Types

type DivTypeNoCN (Complex a) Double :: Type Source #

type DivType (Complex a) Double :: Type Source #

ConvertibleExactly t1 t2 => ConvertibleExactly (Complex t1) (Complex t2) Source # 
Instance details

HasEqAsymmetric a b => HasEqAsymmetric (Complex a) (Complex b) Source # 
Instance details

Associated Types

type EqCompareType (Complex a) (Complex b) :: Type Source #

CanSub a b => CanSub (Complex a) (Complex b) Source # 
Instance details

Associated Types

type SubType (Complex a) (Complex b) :: Type Source #

Methods

sub :: Complex a -> Complex b -> SubType (Complex a) (Complex b) Source #

CanAddAsymmetric a b => CanAddAsymmetric (Complex a) (Complex b) Source # 
Instance details

Associated Types

type AddType (Complex a) (Complex b) :: Type Source #

Methods

add :: Complex a -> Complex b -> AddType (Complex a) (Complex b) Source #

(CanMulAsymmetric a b, CanAddSameType (MulType a b), CanSubSameType (MulType a b)) => CanMulAsymmetric (Complex a) (Complex b) Source # 
Instance details

Associated Types

type MulType (Complex a) (Complex b) :: Type Source #

Methods

mul :: Complex a -> Complex b -> MulType (Complex a) (Complex b) Source #

(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) Source # 
Instance details

Associated Types

type DivTypeNoCN (Complex a) (Complex b) :: Type Source #

type DivType (Complex a) (Complex b) :: Type Source #