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

Contents

Description

 

Synopsis

Addition

type CanAdd t1 t2 = (CanAddAsymmetric t1 t2, CanAddAsymmetric t2 t1, AddType t1 t2 ~ AddType t2 t1) Source #

class CanAddAsymmetric 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 AddType t1 t2 Source #

Methods

add :: t1 -> t2 -> AddType t1 t2 Source #

add :: (AddType t1 t2 ~ t1, t1 ~ t2, Num t1) => t1 -> t1 -> t1 Source #

Instances

CanAddAsymmetric Double Double Source # 

Associated Types

type AddType Double Double :: * Source #

CanAddAsymmetric Double Int Source # 

Associated Types

type AddType Double Int :: * Source #

CanAddAsymmetric Double Integer Source # 

Associated Types

type AddType Double Integer :: * Source #

CanAddAsymmetric Double Rational Source # 

Associated Types

type AddType Double Rational :: * Source #

CanAddAsymmetric Int Double Source # 

Associated Types

type AddType Int Double :: * Source #

CanAddAsymmetric Int Int Source # 

Associated Types

type AddType Int Int :: * Source #

Methods

add :: Int -> Int -> AddType Int Int Source #

CanAddAsymmetric Int Integer Source # 

Associated Types

type AddType Int Integer :: * Source #

CanAddAsymmetric Int Rational Source # 

Associated Types

type AddType Int Rational :: * Source #

CanAddAsymmetric Integer Double Source # 

Associated Types

type AddType Integer Double :: * Source #

CanAddAsymmetric Integer Int Source # 

Associated Types

type AddType Integer Int :: * Source #

CanAddAsymmetric Integer Integer Source # 

Associated Types

type AddType Integer Integer :: * Source #

CanAddAsymmetric Integer Rational Source # 

Associated Types

type AddType Integer Rational :: * Source #

CanAddAsymmetric Rational Double Source # 

Associated Types

type AddType Rational Double :: * Source #

CanAddAsymmetric Rational Int Source # 

Associated Types

type AddType Rational Int :: * Source #

CanAddAsymmetric Rational Integer Source # 

Associated Types

type AddType Rational Integer :: * Source #

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

Associated Types

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

Methods

add :: [a] -> [b] -> AddType [a] [b] Source #

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

Associated Types

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

Methods

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

type CanAddThis t1 t2 = (CanAdd t1 t2, AddType t1 t2 ~ t1) Source #

(+) :: CanAddAsymmetric t1 t2 => t1 -> t2 -> AddType t1 t2 infixl 6 Source #

Tests

specCanAdd :: (CanAddXX t1 t1, CanAddXX t1 t2, CanAddXX t1 t3, CanAddXX t2 t3, CanAddXX t1 (AddType t2 t3), CanAddXX (AddType t1 t2) t3, ConvertibleExactly Integer t1, CanTestPosNeg t1, HasEqCertainly (AddType t1 (AddType t2 t3)) (AddType (AddType t1 t2) t3)) => T t1 -> T t2 -> T t3 -> Spec Source #

HSpec properties that each implementation of CanAdd should satisfy.

specCanAddNotMixed :: (CanAddXX t t, CanAddXX t (AddType t t), ConvertibleExactly Integer t, CanTestPosNeg t) => T t -> Spec Source #

HSpec properties that each implementation of CanAdd should satisfy.

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

HSpec properties that each implementation of CanAddSameType should satisfy.

type CanAddX t1 t2 = (CanAdd t1 t2, Show t1, Arbitrary t1, Show t2, Arbitrary t2, Show (AddType t1 t2), HasEqCertainly t1 (AddType t1 t2), HasEqCertainly t2 (AddType t1 t2), HasEqCertainly (AddType t1 t2) (AddType t1 t2), HasOrderCertainly t1 (AddType t1 t2), HasOrderCertainly t2 (AddType t1 t2), HasOrderCertainly (AddType t1 t2) (AddType t1 t2)) Source #

Compound type constraint useful for test definition.

type CanAddXX t1 t2 = (CanAddX t1 t2, HasEqCertainly (AddType t1 t2) (AddType t2 t1)) Source #

Compound type constraint useful for test definition.

Subtraction

class CanSub t1 t2 where Source #

A replacement for Prelude's binary -.

If CanNeg t2 and CanAdd t1 (NegType t2), then one can use the default implementation via a-b = a + (-b).

Associated Types

type SubType t1 t2 Source #

Methods

sub :: t1 -> t2 -> SubType t1 t2 Source #

sub :: (SubType t1 t2 ~ AddType t1 (NegType t2), CanNeg t2, CanAdd t1 (NegType t2)) => t1 -> t2 -> SubType t1 t2 Source #

Instances

CanSub Double Double Source # 

Associated Types

type SubType Double Double :: * Source #

CanSub Double Int Source # 

Associated Types

type SubType Double Int :: * Source #

CanSub Double Integer Source # 

Associated Types

type SubType Double Integer :: * Source #

CanSub Double Rational Source # 

Associated Types

type SubType Double Rational :: * Source #

CanSub Int Double Source # 

Associated Types

type SubType Int Double :: * Source #

CanSub Int Int Source # 

Associated Types

type SubType Int Int :: * Source #

Methods

sub :: Int -> Int -> SubType Int Int Source #

CanSub Int Integer Source # 

Associated Types

type SubType Int Integer :: * Source #

CanSub Int Rational Source # 

Associated Types

type SubType Int Rational :: * Source #

CanSub Integer Double Source # 

Associated Types

type SubType Integer Double :: * Source #

CanSub Integer Int Source # 

Associated Types

type SubType Integer Int :: * Source #

CanSub Integer Integer Source # 

Associated Types

type SubType Integer Integer :: * Source #

CanSub Integer Rational Source # 

Associated Types

type SubType Integer Rational :: * Source #

CanSub Rational Double Source # 

Associated Types

type SubType Rational Double :: * Source #

CanSub Rational Int Source # 

Associated Types

type SubType Rational Int :: * Source #

CanSub Rational Integer Source # 

Associated Types

type SubType Rational Integer :: * Source #

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

Associated Types

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

Methods

sub :: [a] -> [b] -> SubType [a] [b] Source #

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

Associated Types

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

Methods

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

type CanSubThis t1 t2 = (CanSub t1 t2, SubType t1 t2 ~ t1) Source #

(-) :: CanSub t1 t2 => t1 -> t2 -> SubType t1 t2 infixl 6 Source #

Tests

specCanSub :: (CanSubX t1 t1, CanSubX t1 t2, CanNeg t2, CanAdd t1 (NegType t2), HasEqCertainly (SubType t1 t2) (AddType t1 (NegType t2)), Show (AddType t1 (NegType t2)), ConvertibleExactly Integer t1) => T t1 -> T t2 -> Spec Source #

HSpec properties that each implementation of CanSub should satisfy.

specCanSubNotMixed :: (CanSubX t t, CanSubX t (SubType t t), CanNeg t, CanAdd t (NegType t), Show (AddType t (NegType t)), HasEqCertainly (SubType t t) (AddType t (NegType t)), ConvertibleExactly Integer t) => T t -> Spec Source #

HSpec properties that each implementation of CanSub should satisfy.

type CanSubX t1 t2 = (CanSub t1 t2, HasEqCertainly t1 (SubType t1 t2), CanAddXX t1 t2, Show (SubType t1 t2)) Source #

Compound type constraint useful for test definition.