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.Ring

Contents

Description

 
Synopsis

Ring

type CanAddSubMulBy t s = (CanAddThis t s, CanSubThis t s, CanSub s t, SubType s t ~ t, CanMulBy t s) Source #

class (RingPre t, CanEnsureCN t, RingPre (EnsureCN t)) => Ring t Source #

Instances
Ring Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Ring Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Ring (CN Integer) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Ring (CN Rational) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

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 #

Methods

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

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

Instances
CanMulAsymmetric Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Double Double :: Type Source #

CanMulAsymmetric Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Double Int :: Type Source #

CanMulAsymmetric Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Double Integer :: Type Source #

CanMulAsymmetric Double Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Double Rational :: Type Source #

CanMulAsymmetric Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Int Double :: Type Source #

CanMulAsymmetric Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Int Int :: Type Source #

Methods

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

CanMulAsymmetric Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Int Integer :: Type Source #

CanMulAsymmetric Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Int Rational :: Type Source #

CanMulAsymmetric Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Integer Double :: Type Source #

CanMulAsymmetric Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Integer Int :: Type Source #

CanMulAsymmetric Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Integer Integer :: Type Source #

CanMulAsymmetric Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Integer Rational :: Type Source #

CanMulAsymmetric Rational Double Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Rational Double :: Type Source #

CanMulAsymmetric Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Rational Int :: Type Source #

CanMulAsymmetric Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Rational Integer :: Type Source #

CanMulAsymmetric Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Rational Rational :: Type Source #

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

Defined in Numeric.MixedTypes.Complex

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

Defined in Numeric.MixedTypes.Complex

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

Defined in Numeric.MixedTypes.Complex

Associated Types

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

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

(CanMulAsymmetric Double b, CanEnsureCE es b, CanEnsureCE es (MulType Double b), SuitableForCE es) => CanMulAsymmetric Double (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Double (CollectErrors es b) :: Type Source #

(CanMulAsymmetric Int b, CanEnsureCE es b, CanEnsureCE es (MulType Int b), SuitableForCE es) => CanMulAsymmetric Int (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Int (CollectErrors es b) :: Type Source #

Methods

mul :: Int -> CollectErrors es b -> MulType Int (CollectErrors es b) Source #

(CanMulAsymmetric Integer b, CanEnsureCE es b, CanEnsureCE es (MulType Integer b), SuitableForCE es) => CanMulAsymmetric Integer (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Integer (CollectErrors es b) :: Type Source #

(CanMulAsymmetric Rational b, CanEnsureCE es b, CanEnsureCE es (MulType Rational b), SuitableForCE es) => CanMulAsymmetric Rational (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType Rational (CollectErrors es b) :: Type Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

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

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

Defined in Numeric.MixedTypes.Complex

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

Defined in Numeric.MixedTypes.Complex

Associated Types

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

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

Methods

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

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

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType [a] [b] :: Type Source #

Methods

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

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

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType (Maybe a) (Maybe b) :: Type 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) :: Type Source #

Methods

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

(CanMulAsymmetric a Integer, CanEnsureCE es a, CanEnsureCE es (MulType a Integer), SuitableForCE es) => CanMulAsymmetric (CollectErrors es a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType (CollectErrors es a) Integer :: Type Source #

(CanMulAsymmetric a Int, CanEnsureCE es a, CanEnsureCE es (MulType a Int), SuitableForCE es) => CanMulAsymmetric (CollectErrors es a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType (CollectErrors es a) Int :: Type Source #

Methods

mul :: CollectErrors es a -> Int -> MulType (CollectErrors es a) Int Source #

(CanMulAsymmetric a Rational, CanEnsureCE es a, CanEnsureCE es (MulType a Rational), SuitableForCE es) => CanMulAsymmetric (CollectErrors es a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType (CollectErrors es a) Rational :: Type Source #

(CanMulAsymmetric a Double, CanEnsureCE es a, CanEnsureCE es (MulType a Double), SuitableForCE es) => CanMulAsymmetric (CollectErrors es a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType (CollectErrors es a) Double :: Type Source #

(CanMulAsymmetric a b, CanEnsureCE es a, CanEnsureCE es b, CanEnsureCE es (MulType a b), SuitableForCE es) => CanMulAsymmetric (CollectErrors es a) (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type MulType (CollectErrors es a) (CollectErrors es b) :: Type Source #

Methods

mul :: CollectErrors es a -> CollectErrors es b -> MulType (CollectErrors es a) (CollectErrors es 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 :: (Show t1, Show t2, Show t3, Show (MulType t1 t2), Show (MulType t2 t1), Show (MulType t1 (MulType t2 t3)), Show (MulType (MulType t1 t2) t3), Show (MulType t1 (AddType t2 t3)), Show (AddType (MulType t1 t2) (MulType t1 t3)), Arbitrary t1, Arbitrary t2, Arbitrary t3, ConvertibleExactly Integer t2, CanTestCertainly (EqCompareType (MulType t1 t2) t1), CanTestCertainly (EqCompareType (MulType t1 t2) (MulType t2 t1)), CanTestCertainly (EqCompareType (MulType t1 (MulType t2 t3)) (MulType (MulType t1 t2) t3)), CanTestCertainly (EqCompareType (MulType t1 (AddType t2 t3)) (AddType (MulType t1 t2) (MulType t1 t3))), HasEqAsymmetric (MulType t1 t2) t1, HasEqAsymmetric (MulType t1 t2) (MulType t2 t1), HasEqAsymmetric (MulType t1 (MulType t2 t3)) (MulType (MulType t1 t2) t3), HasEqAsymmetric (MulType t1 (AddType t2 t3)) (AddType (MulType t1 t2) (MulType t1 t3)), CanAddAsymmetric t2 t3, CanAddAsymmetric (MulType t1 t2) (MulType t1 t3), CanMulAsymmetric t1 t2, CanMulAsymmetric t1 t3, CanMulAsymmetric t1 (MulType t2 t3), CanMulAsymmetric t1 (AddType t2 t3), CanMulAsymmetric t2 t1, CanMulAsymmetric t2 t3, CanMulAsymmetric (MulType t1 t2) t3) => T t1 -> T t2 -> T t3 -> 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.

Exponentiation

class CanPow b e where Source #

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

Minimal complete definition

powNoCN

Associated Types

type PowTypeNoCN b e Source #

type PowType b e Source #

Instances
CanPow Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.Elementary

CanPow Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN Double Int :: Type Source #

type PowType Double Int :: Type Source #

CanPow Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

CanPow Double Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Elementary

CanPow Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.Elementary

Associated Types

type PowTypeNoCN Int Double :: Type Source #

type PowType Int Double :: Type Source #

CanPow Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN Int Int :: Type Source #

type PowType Int Int :: Type Source #

CanPow Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN Int Integer :: Type Source #

type PowType Int Integer :: Type Source #

CanPow Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.Elementary

CanPow Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN Integer Int :: Type Source #

type PowType Integer Int :: Type Source #

CanPow Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

CanPow Rational Double Source # 
Instance details

Defined in Numeric.MixedTypes.Elementary

CanPow Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN Rational Int :: Type Source #

type PowType Rational Int :: Type Source #

CanPow Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

(CanPow Double b, CanEnsureCE es b, CanEnsureCE es (PowType Double b), CanEnsureCE es (PowTypeNoCN Double b), SuitableForCE es) => CanPow Double (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN Double (CollectErrors es b) :: Type Source #

type PowType Double (CollectErrors es b) :: Type Source #

(CanPow Int b, CanEnsureCE es b, CanEnsureCE es (PowType Int b), CanEnsureCE es (PowTypeNoCN Int b), SuitableForCE es) => CanPow Int (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN Int (CollectErrors es b) :: Type Source #

type PowType Int (CollectErrors es b) :: Type Source #

(CanPow Integer b, CanEnsureCE es b, CanEnsureCE es (PowType Integer b), CanEnsureCE es (PowTypeNoCN Integer b), SuitableForCE es) => CanPow Integer (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN Integer (CollectErrors es b) :: Type Source #

type PowType Integer (CollectErrors es b) :: Type Source #

(CanPow Rational b, CanEnsureCE es b, CanEnsureCE es (PowType Rational b), CanEnsureCE es (PowTypeNoCN Rational b), SuitableForCE es) => CanPow Rational (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN Rational (CollectErrors es b) :: Type Source #

type PowType Rational (CollectErrors es b) :: Type Source #

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

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN (Maybe a) (Maybe b) :: Type Source #

type PowType (Maybe a) (Maybe b) :: Type Source #

Methods

powNoCN :: Maybe a -> Maybe b -> PowTypeNoCN (Maybe a) (Maybe b) Source #

pow :: Maybe a -> Maybe b -> PowType (Maybe a) (Maybe b) Source #

(CanPow a Integer, CanEnsureCE es a, CanEnsureCE es (PowType a Integer), CanEnsureCE es (PowTypeNoCN a Integer), SuitableForCE es) => CanPow (CollectErrors es a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN (CollectErrors es a) Integer :: Type Source #

type PowType (CollectErrors es a) Integer :: Type Source #

(CanPow a Int, CanEnsureCE es a, CanEnsureCE es (PowType a Int), CanEnsureCE es (PowTypeNoCN a Int), SuitableForCE es) => CanPow (CollectErrors es a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN (CollectErrors es a) Int :: Type Source #

type PowType (CollectErrors es a) Int :: Type Source #

(CanPow a Rational, CanEnsureCE es a, CanEnsureCE es (PowType a Rational), CanEnsureCE es (PowTypeNoCN a Rational), SuitableForCE es) => CanPow (CollectErrors es a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN (CollectErrors es a) Rational :: Type Source #

type PowType (CollectErrors es a) Rational :: Type Source #

(CanPow a Double, CanEnsureCE es a, CanEnsureCE es (PowType a Double), CanEnsureCE es (PowTypeNoCN a Double), SuitableForCE es) => CanPow (CollectErrors es a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN (CollectErrors es a) Double :: Type Source #

type PowType (CollectErrors es a) Double :: Type Source #

(CanPow a b, CanEnsureCE es a, CanEnsureCE es b, CanEnsureCE es (PowTypeNoCN a b), CanEnsureCE es (PowType a b), SuitableForCE es) => CanPow (CollectErrors es a) (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ring

Associated Types

type PowTypeNoCN (CollectErrors es a) (CollectErrors es b) :: Type Source #

type PowType (CollectErrors es a) (CollectErrors es b) :: Type Source #

type CanPowBy t1 t2 = (CanPow t1 t2, PowType t1 t2 ~ t1, PowTypeNoCN t1 t2 ~ t1) Source #

type CanPowCNBy t1 t2 = (CanPow t1 t2, PowType t1 t2 ~ EnsureCN t1, PowTypeNoCN t1 t2 ~ t1, CanEnsureCN t1, CanPow (EnsureCN t1) t2, PowType (EnsureCN t1) t2 ~ EnsureCN t1, PowTypeNoCN (EnsureCN t1) t2 ~ EnsureCN t1) Source #

(^) :: CanPow t1 t2 => t1 -> t2 -> PowType t1 t2 infixl 8 Source #

(^!) :: CanPow t1 t2 => t1 -> t2 -> PowTypeNoCN t1 t2 infixl 8 Source #

Like ^ but throwing an exception if the power is undefined.

powUsingMul :: (CanBeInteger e, CanMulSameType t) => t -> t -> e -> t Source #

Tests

specCanPow :: (Show t1, Show t2, Show (PowType t1 t2), Show (MulType t1 (PowType t1 t2)), Show (PowType t1 (AddType t2 Integer)), Arbitrary t1, Arbitrary t2, ConvertibleExactly Integer t1, ConvertibleExactly Integer t2, CanTestCertainly (EqCompareType (PowType t1 t2) t1), CanTestCertainly (EqCompareType (MulType t1 (PowType t1 t2)) (PowType t1 (AddType t2 Integer))), HasEqAsymmetric (PowType t1 t2) t1, HasEqAsymmetric (MulType t1 (PowType t1 t2)) (PowType t1 (AddType t2 Integer)), CanTestPosNeg t2, CanAddAsymmetric t2 Integer, CanPow t1 t2, CanPow t1 (AddType t2 Integer), CanMulAsymmetric t1 (PowType t1 t2)) => T t1 -> T t2 -> Spec Source #

HSpec properties that each implementation of CanPow should satisfy.