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

Description

 
Synopsis

Equality checks

type HasEq t1 t2 = (HasEqAsymmetric t1 t2, HasEqAsymmetric t2 t1, EqCompareType t1 t2 ~ EqCompareType t2 t1) Source #

class IsBool (EqCompareType a b) => HasEqAsymmetric a b where Source #

Minimal complete definition

Nothing

Associated Types

type EqCompareType a b Source #

type EqCompareType a b = Bool

Methods

equalTo :: a -> b -> EqCompareType a b Source #

default equalTo :: (EqCompareType a b ~ Bool, a ~ b, Eq a) => a -> b -> EqCompareType a b Source #

notEqualTo :: a -> b -> EqCompareType a b Source #

default notEqualTo :: CanNegSameType (EqCompareType a b) => a -> b -> EqCompareType a b Source #

Instances

Instances details
HasEqAsymmetric Bool Bool Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Bool Bool Source #

HasEqAsymmetric Char Char Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Char Char Source #

HasEqAsymmetric Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Double Double Source #

HasEqAsymmetric Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Double Int Source #

HasEqAsymmetric Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Double Integer Source #

HasEqAsymmetric Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Int Double Source #

HasEqAsymmetric Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Int Int Source #

HasEqAsymmetric Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Int Integer Source #

HasEqAsymmetric Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Int Rational Source #

HasEqAsymmetric Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Integer Double Source #

HasEqAsymmetric Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Integer Int Source #

HasEqAsymmetric Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Integer Integer Source #

HasEqAsymmetric Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Integer Rational Source #

HasEqAsymmetric Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Rational Int Source #

HasEqAsymmetric Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Rational Integer Source #

HasEqAsymmetric Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Rational Rational Source #

HasEqAsymmetric () () Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType () () Source #

Methods

equalTo :: () -> () -> EqCompareType () () Source #

notEqualTo :: () -> () -> EqCompareType () () Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type EqCompareType Double (Complex b) Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type EqCompareType Int (Complex b) Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type EqCompareType Integer (Complex b) Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type EqCompareType Rational (Complex b) Source #

(HasEqAsymmetric Bool b, CanBeErrors es, CanTestCertainly (EqCompareType Bool b)) => HasEqAsymmetric Bool (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Bool (CollectErrors es b) Source #

(HasEqAsymmetric Double b, CanBeErrors es, CanTestCertainly (EqCompareType Double b)) => HasEqAsymmetric Double (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Double (CollectErrors es b) Source #

(HasEqAsymmetric Int b, CanBeErrors es, CanTestCertainly (EqCompareType Int b)) => HasEqAsymmetric Int (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Int (CollectErrors es b) Source #

(HasEqAsymmetric Integer b, CanBeErrors es, CanTestCertainly (EqCompareType Integer b)) => HasEqAsymmetric Integer (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Integer (CollectErrors es b) Source #

(HasEqAsymmetric Rational b, CanBeErrors es, CanTestCertainly (EqCompareType Rational b)) => HasEqAsymmetric Rational (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType Rational (CollectErrors es b) Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type EqCompareType (Complex a) Integer Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type EqCompareType (Complex a) Int Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type EqCompareType (Complex a) Rational Source #

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

Defined in Numeric.MixedTypes.Complex

Associated Types

type EqCompareType (Complex a) Double Source #

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

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType [a] [b] Source #

Methods

equalTo :: [a] -> [b] -> EqCompareType [a] [b] Source #

notEqualTo :: [a] -> [b] -> EqCompareType [a] [b] Source #

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

Defined in Numeric.MixedTypes.Eq

Associated Types

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

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

Defined in Numeric.MixedTypes.Complex

Associated Types

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

(HasEqAsymmetric (Maybe Bool) b, CanBeErrors es, CanTestCertainly (EqCompareType (Maybe Bool) b)) => HasEqAsymmetric (Maybe Bool) (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (Maybe Bool) (CollectErrors es b) Source #

(HasEqAsymmetric a Bool, CanBeErrors es, CanTestCertainly (EqCompareType a Bool)) => HasEqAsymmetric (CollectErrors es a) Bool Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (CollectErrors es a) Bool Source #

(HasEqAsymmetric a Integer, CanBeErrors es, CanTestCertainly (EqCompareType a Integer)) => HasEqAsymmetric (CollectErrors es a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (CollectErrors es a) Integer Source #

(HasEqAsymmetric a Int, CanBeErrors es, CanTestCertainly (EqCompareType a Int)) => HasEqAsymmetric (CollectErrors es a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (CollectErrors es a) Int Source #

(HasEqAsymmetric a Rational, CanBeErrors es, CanTestCertainly (EqCompareType a Rational)) => HasEqAsymmetric (CollectErrors es a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (CollectErrors es a) Rational Source #

(HasEqAsymmetric a Double, CanBeErrors es, CanTestCertainly (EqCompareType a Double)) => HasEqAsymmetric (CollectErrors es a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (CollectErrors es a) Double Source #

(HasEqAsymmetric a (Maybe Bool), CanBeErrors es, CanTestCertainly (EqCompareType a (Maybe Bool))) => HasEqAsymmetric (CollectErrors es a) (Maybe Bool) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (CollectErrors es a) (Maybe Bool) Source #

(HasEqAsymmetric a1 b1, HasEqAsymmetric a2 b2, CanAndOrAsymmetric (EqCompareType a1 b1) (EqCompareType a2 b2), IsBool (AndOrType (EqCompareType a1 b1) (EqCompareType a2 b2))) => HasEqAsymmetric (a1, a2) (b1, b2) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (a1, a2) (b1, b2) Source #

Methods

equalTo :: (a1, a2) -> (b1, b2) -> EqCompareType (a1, a2) (b1, b2) Source #

notEqualTo :: (a1, a2) -> (b1, b2) -> EqCompareType (a1, a2) (b1, b2) Source #

(HasEqAsymmetric a b, CanBeErrors es, CanTestCertainly (EqCompareType a b)) => HasEqAsymmetric (CollectErrors es a) (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

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

HasEqAsymmetric ((a1, a2), a3) ((b1, b2), b3) => HasEqAsymmetric (a1, a2, a3) (b1, b2, b3) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (a1, a2, a3) (b1, b2, b3) Source #

Methods

equalTo :: (a1, a2, a3) -> (b1, b2, b3) -> EqCompareType (a1, a2, a3) (b1, b2, b3) Source #

notEqualTo :: (a1, a2, a3) -> (b1, b2, b3) -> EqCompareType (a1, a2, a3) (b1, b2, b3) Source #

HasEqAsymmetric ((a1, a2, a3), a4) ((b1, b2, b3), b4) => HasEqAsymmetric (a1, a2, a3, a4) (b1, b2, b3, b4) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (a1, a2, a3, a4) (b1, b2, b3, b4) Source #

Methods

equalTo :: (a1, a2, a3, a4) -> (b1, b2, b3, b4) -> EqCompareType (a1, a2, a3, a4) (b1, b2, b3, b4) Source #

notEqualTo :: (a1, a2, a3, a4) -> (b1, b2, b3, b4) -> EqCompareType (a1, a2, a3, a4) (b1, b2, b3, b4) Source #

HasEqAsymmetric ((a1, a2, a3, a4), a5) ((b1, b2, b3, b4), b5) => HasEqAsymmetric (a1, a2, a3, a4, a5) (b1, b2, b3, b4, b5) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Associated Types

type EqCompareType (a1, a2, a3, a4, a5) (b1, b2, b3, b4, b5) Source #

Methods

equalTo :: (a1, a2, a3, a4, a5) -> (b1, b2, b3, b4, b5) -> EqCompareType (a1, a2, a3, a4, a5) (b1, b2, b3, b4, b5) Source #

notEqualTo :: (a1, a2, a3, a4, a5) -> (b1, b2, b3, b4, b5) -> EqCompareType (a1, a2, a3, a4, a5) (b1, b2, b3, b4, b5) Source #

(==) :: HasEqAsymmetric a b => a -> b -> EqCompareType a b infix 4 Source #

(/=) :: HasEqAsymmetric a b => a -> b -> EqCompareType a b infix 4 Source #

(?==?) :: HasEqCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #

(!==!) :: HasEqCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #

(!/=!) :: HasEqCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #

Tests

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

HSpec properties that each implementation of HasEq should satisfy.

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

HSpec properties that each implementation of HasEq should satisfy.

specConversion :: (Arbitrary t1, Show t1, HasEqCertainly t1 t1) => T t1 -> T t2 -> (t1 -> t2) -> (t2 -> t1) -> Spec Source #

HSpec property of there-and-back conversion.

Specific comparisons

class CanTestValid t where Source #

Methods

isValid :: t -> Bool Source #

specResultIsValid1 :: (Arbitrary t1, Show t1, CanTestValid t1, CanTestValid t2) => (t1 -> t2) -> String -> T t1 -> Spec Source #

HSpec property checking the validity of unary operations' results.

specResultIsValid2 :: (Arbitrary t1, Show t1, Arbitrary t2, Show t2, CanTestValid t1, CanTestValid t2, CanTestValid t3) => (t1 -> t2 -> t3) -> String -> T t1 -> T t2 -> Spec Source #

HSpec properties that check validity of operations' results.

specResultIsValid1Pre :: (Arbitrary t1, Show t1, CanTestValid t1, CanTestValid t2) => (t1 -> Bool) -> (t1 -> t2) -> String -> T t1 -> Spec Source #

specResultIsValid2Pre :: (Arbitrary t1, Show t1, Arbitrary t2, Show t2, CanTestValid t1, CanTestValid t2, CanTestValid t3) => (t1 -> t2 -> Bool) -> (t1 -> t2 -> t3) -> String -> T t1 -> T t2 -> Spec Source #

class CanTestNaN t where Source #

Minimal complete definition

Nothing

Methods

isNaN :: t -> Bool Source #

default isNaN :: RealFloat t => t -> Bool Source #

Instances

Instances details
CanTestNaN Double Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Methods

isNaN :: Double -> Bool Source #

CanTestNaN Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Methods

isNaN :: Integer -> Bool Source #

CanTestNaN Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Methods

isNaN :: Rational -> Bool Source #

(CanTestNaN t, CanBeErrors es) => CanTestNaN (CollectErrors es t) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Methods

isNaN :: CollectErrors es t -> Bool Source #

class CanTestFinite t where Source #

Minimal complete definition

Nothing

Methods

isInfinite :: t -> Bool Source #

default isInfinite :: RealFloat t => t -> Bool Source #

isFinite :: t -> Bool Source #

default isFinite :: RealFloat t => t -> Bool Source #

Instances

Instances details
CanTestFinite Double Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

CanTestFinite Int Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

CanTestFinite Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

CanTestFinite Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

(CanTestFinite t, CanBeErrors es) => CanTestFinite (CollectErrors es t) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

class CanTestInteger t where Source #

Minimal complete definition

certainlyNotInteger, certainlyIntegerGetIt

Instances

Instances details
CanTestInteger Double Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

CanTestInteger Int Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

CanTestInteger Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

CanTestInteger Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

(CanTestInteger t, CanTestZero t) => CanTestInteger (Complex t) Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

(CanTestInteger t, CanBeErrors es) => CanTestInteger (CollectErrors es t) Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

specCanTestZero :: (CanTestZero t, ConvertibleExactly Integer t) => T t -> Spec Source #

HSpec properties that each implementation of CanTestZero should satisfy.

class CanPickNonZero t where Source #

Minimal complete definition

Nothing

Methods

pickNonZero :: [(t, s)] -> Maybe (t, s) Source #

Given a list [(a1,b1),(a2,b2),...] and assuming that at least one of a1,a2,... is non-zero, pick one of them and return the corresponding pair (ai,bi).

If none of a1,a2,... is zero, either throws an exception or loops forever.

The default implementation is based on a CanTestZero instance and is not parallel.

default pickNonZero :: (CanTestZero t, Show t) => [(t, s)] -> Maybe (t, s) Source #

Instances

Instances details
CanPickNonZero Int Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Methods

pickNonZero :: [(Int, s)] -> Maybe (Int, s) Source #

CanPickNonZero Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Methods

pickNonZero :: [(Integer, s)] -> Maybe (Integer, s) Source #

CanPickNonZero Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Eq

Methods

pickNonZero :: [(Rational, s)] -> Maybe (Rational, s) Source #

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

Defined in Numeric.MixedTypes.Eq

Methods

pickNonZero :: [(CollectErrors es a, s)] -> Maybe (CollectErrors es a, s) Source #

specCanPickNonZero :: (CanPickNonZero t, CanTestZero t, ConvertibleExactly Integer t, Show t, Arbitrary t) => T t -> Spec Source #

HSpec properties that each implementation of CanPickNonZero should satisfy.