mixed-types-num-0.5.8.0: 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.AddSub

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

Minimal complete definition

Nothing

Associated Types

type AddType t1 t2 Source #

type AddType t1 t2 = t1

Methods

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

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

Instances

Instances details
CanAddAsymmetric Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Double Double Source #

CanAddAsymmetric Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Double Int Source #

CanAddAsymmetric Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Double Integer Source #

CanAddAsymmetric Double Rational Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Double Rational Source #

CanAddAsymmetric Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Int Double Source #

CanAddAsymmetric Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Int Int Source #

Methods

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

CanAddAsymmetric Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Int Integer Source #

CanAddAsymmetric Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Int Rational Source #

CanAddAsymmetric Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Integer Double Source #

CanAddAsymmetric Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Integer Int Source #

CanAddAsymmetric Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Integer Integer Source #

CanAddAsymmetric Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Integer Rational Source #

CanAddAsymmetric Rational Double Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Rational Double Source #

CanAddAsymmetric Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Rational Int Source #

CanAddAsymmetric Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Rational Integer Source #

CanAddAsymmetric Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Rational Rational Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type AddType Double (Complex b) Source #

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type AddType Int (Complex b) Source #

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type AddType Integer (Complex b) Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type AddType Rational (Complex b) Source #

(CanAddAsymmetric Double b, CanBeErrors es) => CanAddAsymmetric Double (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Double (CollectErrors es b) Source #

(CanAddAsymmetric Int b, CanBeErrors es) => CanAddAsymmetric Int (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Int (CollectErrors es b) Source #

Methods

add :: Int -> CollectErrors es b -> AddType Int (CollectErrors es b) Source #

(CanAddAsymmetric Integer b, CanBeErrors es) => CanAddAsymmetric Integer (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Integer (CollectErrors es b) Source #

(CanAddAsymmetric Rational b, CanBeErrors es) => CanAddAsymmetric Rational (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType Rational (CollectErrors es b) Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type AddType (Complex a) Integer Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type AddType (Complex a) Int Source #

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type AddType (Complex a) Rational Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type AddType (Complex a) Double Source #

Methods

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

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

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType [a] [b] Source #

Methods

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

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

Defined in Numeric.MixedTypes.AddSub

Associated Types

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

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

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

Methods

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

(CanAddAsymmetric a Integer, CanBeErrors es) => CanAddAsymmetric (CollectErrors es a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType (CollectErrors es a) Integer Source #

(CanAddAsymmetric a Int, CanBeErrors es) => CanAddAsymmetric (CollectErrors es a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType (CollectErrors es a) Int Source #

Methods

add :: CollectErrors es a -> Int -> AddType (CollectErrors es a) Int Source #

(CanAddAsymmetric a Rational, CanBeErrors es) => CanAddAsymmetric (CollectErrors es a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType (CollectErrors es a) Rational Source #

(CanAddAsymmetric a Double, CanBeErrors es) => CanAddAsymmetric (CollectErrors es a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType (CollectErrors es a) Double Source #

(CanAddAsymmetric a b, CanBeErrors es) => CanAddAsymmetric (CollectErrors es a) (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type AddType (CollectErrors es a) (CollectErrors es b) Source #

Methods

add :: CollectErrors es a -> CollectErrors es b -> AddType (CollectErrors es a) (CollectErrors es 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 :: _ => T t1 -> T t2 -> T t3 -> Spec Source #

HSpec properties that each implementation of CanAdd should satisfy.

specCanAddNotMixed :: _ => 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.

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

Minimal complete definition

Nothing

Associated Types

type SubType t1 t2 Source #

type SubType t1 t2 = AddType t1 (NegType t2)

Methods

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

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

Instances

Instances details
CanSub Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Double Double Source #

CanSub Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Double Int Source #

CanSub Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Double Integer Source #

CanSub Double Rational Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Double Rational Source #

CanSub Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Int Double Source #

CanSub Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Int Int Source #

Methods

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

CanSub Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Int Integer Source #

CanSub Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Int Rational Source #

CanSub Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Integer Double Source #

CanSub Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Integer Int Source #

CanSub Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Integer Integer Source #

CanSub Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Integer Rational Source #

CanSub Rational Double Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Rational Double Source #

CanSub Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Rational Int Source #

CanSub Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Rational Integer Source #

CanSub Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Rational Rational Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type SubType Double (Complex b) Source #

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type SubType Int (Complex b) Source #

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type SubType Integer (Complex b) Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type SubType Rational (Complex b) Source #

(CanSub Double b, CanBeErrors es) => CanSub Double (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Double (CollectErrors es b) Source #

(CanSub Int b, CanBeErrors es) => CanSub Int (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Int (CollectErrors es b) Source #

Methods

sub :: Int -> CollectErrors es b -> SubType Int (CollectErrors es b) Source #

(CanSub Integer b, CanBeErrors es) => CanSub Integer (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Integer (CollectErrors es b) Source #

(CanSub Rational b, CanBeErrors es) => CanSub Rational (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType Rational (CollectErrors es b) Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type SubType (Complex a) Integer Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type SubType (Complex a) Int Source #

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type SubType (Complex a) Rational Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type SubType (Complex a) Double Source #

Methods

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

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

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType [a] [b] Source #

Methods

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

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

Defined in Numeric.MixedTypes.AddSub

Associated Types

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

Methods

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

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

Methods

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

(CanSub a Integer, CanBeErrors es) => CanSub (CollectErrors es a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType (CollectErrors es a) Integer Source #

(CanSub a Int, CanBeErrors es) => CanSub (CollectErrors es a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType (CollectErrors es a) Int Source #

Methods

sub :: CollectErrors es a -> Int -> SubType (CollectErrors es a) Int Source #

(CanSub a Rational, CanBeErrors es) => CanSub (CollectErrors es a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType (CollectErrors es a) Rational Source #

(CanSub a Double, CanBeErrors es) => CanSub (CollectErrors es a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType (CollectErrors es a) Double Source #

(CanSub a b, CanBeErrors es) => CanSub (CollectErrors es a) (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.AddSub

Associated Types

type SubType (CollectErrors es a) (CollectErrors es b) Source #

Methods

sub :: CollectErrors es a -> CollectErrors es b -> SubType (CollectErrors es a) (CollectErrors es 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 :: _ => T t1 -> T t2 -> Spec Source #

HSpec properties that each implementation of CanSub should satisfy.

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

HSpec properties that each implementation of CanSub should satisfy.