mixed-types-num-0.1.0.0: 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

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

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 -> t1 -> t1 Source #

Instances

CanMulAsymmetric Double Double Source # 

Associated Types

type MulType Double Double :: * Source #

CanMulAsymmetric Double Int Source # 

Associated Types

type MulType Double Int :: * Source #

CanMulAsymmetric Double Integer Source # 

Associated Types

type MulType Double Integer :: * Source #

CanMulAsymmetric Double Rational Source # 

Associated Types

type MulType Double Rational :: * Source #

CanMulAsymmetric Int Double Source # 

Associated Types

type MulType Int Double :: * Source #

CanMulAsymmetric Int Int Source # 

Associated Types

type MulType Int Int :: * Source #

Methods

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

CanMulAsymmetric Int Integer Source # 

Associated Types

type MulType Int Integer :: * Source #

CanMulAsymmetric Int Rational Source # 

Associated Types

type MulType Int Rational :: * Source #

CanMulAsymmetric Integer Double Source # 

Associated Types

type MulType Integer Double :: * Source #

CanMulAsymmetric Integer Int Source # 

Associated Types

type MulType Integer Int :: * Source #

CanMulAsymmetric Integer Integer Source # 

Associated Types

type MulType Integer Integer :: * Source #

CanMulAsymmetric Integer Rational Source # 

Associated Types

type MulType Integer Rational :: * Source #

CanMulAsymmetric Rational Double Source # 

Associated Types

type MulType Rational Double :: * Source #

CanMulAsymmetric Rational Int Source # 

Associated Types

type MulType Rational Int :: * Source #

CanMulAsymmetric Rational Integer Source # 

Associated Types

type MulType Rational Integer :: * Source #

CanMulAsymmetric Rational Rational Source # 
CanMulAsymmetric a b => CanMulAsymmetric [a] [b] Source # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

mul :: Maybe a -> Maybe b -> MulType (Maybe a) (Maybe 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 :: (CanMulX t1 t2, CanMulX t1 t3, CanMulX t2 t3, CanMulX t1 (MulType t2 t3), CanMulX (MulType t1 t2) t3, HasEqCertainly (MulType t1 (MulType t2 t3)) (MulType (MulType t1 t2) t3), CanAdd t2 t3, CanMulX t1 (AddType t2 t3), CanAddX (MulType t1 t2) (MulType t1 t3), HasEqCertainly (MulType t1 (AddType t2 t3)) (AddType (MulType t1 t2) (MulType t1 t3)), ConvertibleExactly Integer t2) => T t1 -> T t2 -> T t3 -> Spec Source #

HSpec properties that each implementation of CanMul should satisfy.

specCanMulNotMixed :: (CanMulX t t, CanMulX t (MulType t t), HasEqCertainly (MulType (MulType t t) t) (MulType t (MulType t t)), CanAdd t t, CanMulX t (AddType t t), CanAddX (MulType t t) (MulType t t), HasEqCertainly (MulType t (AddType t t)) (AddType (MulType t t) (MulType t t)), ConvertibleExactly Integer t) => T t -> Spec Source #

HSpec properties that each implementation of CanMul should satisfy.

specCanMulSameType :: (ConvertibleExactly Integer t, Show t, HasEqCertainly t t, CanMulSameType t) => T t -> Spec Source #

HSpec properties that each implementation of CanMulSameType should satisfy.

type CanMulX t1 t2 = (CanMul t1 t2, Show t1, Arbitrary t1, Show t2, Arbitrary t2, Show (MulType t1 t2), HasEqCertainly t1 (MulType t1 t2), HasEqCertainly t2 (MulType t1 t2), HasEqCertainly (MulType t1 t2) (MulType t1 t2), HasOrderCertainly t1 (MulType t1 t2), HasOrderCertainly t2 (MulType t1 t2), HasOrderCertainly (MulType t1 t2) (MulType t1 t2)) Source #

Compound type constraint useful for test definition.

Exponentiation

class CanPow t1 t2 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 ^.

Associated Types

type PowType t1 t2 Source #

Methods

pow :: t1 -> t2 -> PowType t1 t2 Source #

pow :: (PowType t1 t2 ~ t1, Num t1, Integral t2) => t1 -> t2 -> t1 Source #

Instances

CanPow Double Int Source # 

Associated Types

type PowType Double Int :: * Source #

CanPow Double Integer Source # 

Associated Types

type PowType Double Integer :: * Source #

CanPow Int Int Source # 

Associated Types

type PowType Int Int :: * Source #

Methods

pow :: Int -> Int -> PowType Int Int Source #

CanPow Int Integer Source # 

Associated Types

type PowType Int Integer :: * Source #

CanPow Integer Int Source # 

Associated Types

type PowType Integer Int :: * Source #

CanPow Integer Integer Source # 

Associated Types

type PowType Integer Integer :: * Source #

CanPow Rational Int Source # 

Associated Types

type PowType Rational Int :: * Source #

CanPow Rational Integer Source # 

Associated Types

type PowType Rational Integer :: * Source #

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

Associated Types

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

Methods

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

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

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

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

A synonym of ^

(**) :: CanPow t1 t2 => t1 -> t2 -> PowType t1 t2 Source #

A synonym of ^

Tests

specCanPow :: (CanPowX t1 t2, HasEqCertainly t1 (PowType t1 t2), ConvertibleExactly Integer t1, ConvertibleExactly Integer t2, CanTestPosNeg t2, CanAdd t2 Integer, CanMulX t1 (PowType t1 t2), CanPowX t1 (AddType t2 Integer), HasEqCertainly (MulType t1 (PowType t1 t2)) (PowType t1 (AddType t2 Integer))) => T t1 -> T t2 -> Spec Source #

HSpec properties that each implementation of CanPow should satisfy.

type CanPowX t1 t2 = (CanPow t1 t2, Show t1, Arbitrary t1, Show t2, Arbitrary t2, Show (PowType t1 t2)) Source #

Compound type constraint useful for test definition.