mixed-types-num-0.5.11: Alternative Prelude with numeric and logic expressions typed bottom-up
Copyright(c) Michal Konecny
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Numeric.MixedTypes.Mul

Description

 
Synopsis

Multiplication

type CanMul t1 t2 = (CanMulAsymmetric t1 t2, CanMulAsymmetric t2 t1, MulType t1 t2 ~ MulType t2 t1) Source #

class CanMulAsymmetric t1 t2 where Source #

A replacement for Prelude's *. If t1 = t2 and Num t1, then one can use the default implementation to mirror Prelude's *.

Minimal complete definition

Nothing

Associated Types

type MulType t1 t2 Source #

type MulType t1 t2 = t1

Methods

mul :: t1 -> t2 -> MulType t1 t2 Source #

default mul :: (MulType t1 t2 ~ t1, t1 ~ t2, Num t1) => t1 -> t2 -> MulType t1 t2 Source #

Instances

Instances details
CanMulAsymmetric Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Double Double Source #

CanMulAsymmetric Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Double Int Source #

CanMulAsymmetric Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Double Integer Source #

CanMulAsymmetric Double Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Double Rational Source #

CanMulAsymmetric Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Int Double Source #

CanMulAsymmetric Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Int Int Source #

Methods

mul :: Int -> Int -> MulType Int Int Source #

CanMulAsymmetric Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Int Integer Source #

CanMulAsymmetric Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Int Rational Source #

CanMulAsymmetric Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Integer Double Source #

CanMulAsymmetric Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Integer Int Source #

CanMulAsymmetric Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Integer Integer Source #

CanMulAsymmetric Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Integer Rational Source #

CanMulAsymmetric Rational Double Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Rational Double Source #

CanMulAsymmetric Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Rational Int Source #

CanMulAsymmetric Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Rational Integer Source #

CanMulAsymmetric Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Rational Rational Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type MulType Double (Complex b) Source #

Methods

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

(CanMulAsymmetric Double b, CanGiveUpIfVeryInaccurate (MulType Double b)) => CanMulAsymmetric Double (CN b) Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Double (CN b) Source #

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type MulType Int (Complex b) Source #

Methods

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

(CanMulAsymmetric Int b, CanGiveUpIfVeryInaccurate (MulType Int b)) => CanMulAsymmetric Int (CN b) Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Int (CN b) Source #

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type MulType Integer (Complex b) Source #

(CanMulAsymmetric Integer b, CanGiveUpIfVeryInaccurate (MulType Integer b)) => CanMulAsymmetric Integer (CN b) Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Integer (CN b) Source #

Methods

mul :: Integer -> CN b -> MulType Integer (CN b) Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type MulType Rational (Complex b) Source #

(CanMulAsymmetric Rational b, CanGiveUpIfVeryInaccurate (MulType Rational b)) => CanMulAsymmetric Rational (CN b) Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType Rational (CN b) Source #

Methods

mul :: Rational -> CN b -> MulType Rational (CN b) Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type MulType (Complex a) Integer Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type MulType (Complex a) Int Source #

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type MulType (Complex a) Rational Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type MulType (Complex a) Double Source #

Methods

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

(CanMulAsymmetric a Integer, CanGiveUpIfVeryInaccurate (MulType a Integer)) => CanMulAsymmetric (CN a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType (CN a) Integer Source #

Methods

mul :: CN a -> Integer -> MulType (CN a) Integer Source #

(CanMulAsymmetric a Int, CanGiveUpIfVeryInaccurate (MulType a Int)) => CanMulAsymmetric (CN a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType (CN a) Int Source #

Methods

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

(CanMulAsymmetric a Rational, CanGiveUpIfVeryInaccurate (MulType a Rational)) => CanMulAsymmetric (CN a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType (CN a) Rational Source #

Methods

mul :: CN a -> Rational -> MulType (CN a) Rational Source #

(CanMulAsymmetric a Double, CanGiveUpIfVeryInaccurate (MulType a Double)) => CanMulAsymmetric (CN a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType (CN a) Double Source #

Methods

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

CanMulAsymmetric a b => CanMulAsymmetric [a] [b] Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType [a] [b] Source #

Methods

mul :: [a] -> [b] -> MulType [a] [b] Source #

CanMulAsymmetric a b => CanMulAsymmetric (Maybe a) (Maybe b) Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType (Maybe a) (Maybe b) Source #

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

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

Methods

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

(CanMulAsymmetric a b, CanGiveUpIfVeryInaccurate (MulType a b)) => CanMulAsymmetric (CN a) (CN b) Source # 
Instance details

Defined in Numeric.MixedTypes.Mul

Associated Types

type MulType (CN a) (CN b) Source #

Methods

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

type CanMulBy t1 t2 = (CanMul t1 t2, MulType t1 t2 ~ t1) Source #

(*) :: CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2 infixl 7 Source #

Tests

specCanMul :: _ => T t1 -> T t2 -> T t3 -> Spec Source #

HSpec properties that each implementation of CanMul should satisfy.

specCanMulNotMixed :: _ => T t -> Spec Source #

HSpec properties that each implementation of CanMul should satisfy.

specCanMulSameType :: (Show t, ConvertibleExactly Integer t, CanTestCertainly (EqCompareType t t), HasEqAsymmetric t t, CanMulAsymmetric t t, MulType t t ~ t) => T t -> Spec Source #

HSpec properties that each implementation of CanMulSameType should satisfy.