| Copyright | (c) Michal Konecny |
|---|---|
| License | BSD3 |
| Maintainer | [email protected] |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Numeric.MixedTypes.Eq
Description
Synopsis
- type HasEq t1 t2 = (HasEqAsymmetric t1 t2, HasEqAsymmetric t2 t1, EqCompareType t1 t2 ~ EqCompareType t2 t1)
- class IsBool (EqCompareType a b) => HasEqAsymmetric a b where
- type EqCompareType a b
- equalTo :: a -> b -> EqCompareType a b
- notEqualTo :: a -> b -> EqCompareType a b
- (==) :: HasEqAsymmetric a b => a -> b -> EqCompareType a b
- (/=) :: HasEqAsymmetric a b => a -> b -> EqCompareType a b
- type HasEqCertainly t1 t2 = (HasEq t1 t2, CanTestCertainly (EqCompareType t1 t2))
- type HasEqCertainlyAsymmetric t1 t2 = (HasEqAsymmetric t1 t2, CanTestCertainly (EqCompareType t1 t2))
- notCertainlyDifferentFrom :: HasEqCertainlyAsymmetric a b => a -> b -> Bool
- certainlyEqualTo :: HasEqCertainlyAsymmetric a b => a -> b -> Bool
- certainlyNotEqualTo :: HasEqCertainlyAsymmetric a b => a -> b -> Bool
- (?==?) :: HasEqCertainlyAsymmetric a b => a -> b -> Bool
- (!==!) :: HasEqCertainlyAsymmetric a b => a -> b -> Bool
- (!/=!) :: HasEqCertainlyAsymmetric a b => a -> b -> Bool
- specHasEq :: _ => T t1 -> T t2 -> T t3 -> Spec
- specHasEqNotMixed :: _ => T t -> Spec
- specConversion :: (Arbitrary t1, Show t1, HasEqCertainly t1 t1) => T t1 -> T t2 -> (t1 -> t2) -> (t2 -> t1) -> Spec
- class CanTestNaN t where
- class CanTestFinite t where
- isInfinite :: t -> Bool
- isFinite :: t -> Bool
- class CanTestInteger t where
- certainlyNotInteger :: t -> Bool
- certainlyInteger :: t -> Bool
- certainlyIntegerGetIt :: t -> Maybe Integer
- class CanTestZero t where
- isCertainlyZero :: t -> Bool
- isCertainlyNonZero :: t -> Bool
- specCanTestZero :: (CanTestZero t, ConvertibleExactly Integer t) => T t -> Spec
- class CanPickNonZero t where
- pickNonZero :: [(t, s)] -> Maybe (t, s)
- specCanPickNonZero :: (CanPickNonZero t, CanTestZero t, ConvertibleExactly Integer t, Show t, Arbitrary t) => T t -> Spec
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
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
(==) :: HasEqAsymmetric a b => a -> b -> EqCompareType a b infix 4 Source #
(/=) :: HasEqAsymmetric a b => a -> b -> EqCompareType a b infix 4 Source #
type HasEqCertainly t1 t2 = (HasEq t1 t2, CanTestCertainly (EqCompareType t1 t2)) Source #
type HasEqCertainlyAsymmetric t1 t2 = (HasEqAsymmetric t1 t2, CanTestCertainly (EqCompareType t1 t2)) Source #
notCertainlyDifferentFrom :: HasEqCertainlyAsymmetric a b => a -> b -> Bool Source #
certainlyEqualTo :: HasEqCertainlyAsymmetric a b => a -> b -> Bool Source #
certainlyNotEqualTo :: HasEqCertainlyAsymmetric a b => a -> b -> Bool 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 CanTestNaN t where Source #
Minimal complete definition
Nothing
Instances
| CanTestNaN Double Source # | |
| CanTestNaN Integer Source # | |
| CanTestNaN Rational Source # | |
| (CanTestNaN t, CanBeErrors es) => CanTestNaN (CollectErrors es t) Source # | |
Defined in Numeric.MixedTypes.Eq Methods isNaN :: CollectErrors es t -> Bool Source # | |
class CanTestFinite t where Source #
Minimal complete definition
Nothing
Instances
| CanTestFinite Double Source # | |
| CanTestFinite Int Source # | |
| CanTestFinite Integer Source # | |
| CanTestFinite Rational Source # | |
| (CanTestFinite t, CanBeErrors es) => CanTestFinite (CollectErrors es t) Source # | |
Defined in Numeric.MixedTypes.Eq Methods isInfinite :: CollectErrors es t -> Bool Source # isFinite :: CollectErrors es t -> Bool Source # | |
class CanTestInteger t where Source #
Minimal complete definition
Methods
certainlyNotInteger :: t -> Bool Source #
certainlyInteger :: t -> Bool Source #
certainlyIntegerGetIt :: t -> Maybe Integer Source #
Instances
| CanTestInteger Double Source # | |
Defined in Numeric.MixedTypes.Eq | |
| CanTestInteger Int Source # | |
Defined in Numeric.MixedTypes.Eq | |
| CanTestInteger Integer Source # | |
Defined in Numeric.MixedTypes.Eq | |
| CanTestInteger Rational Source # | |
Defined in Numeric.MixedTypes.Eq | |
| (CanTestInteger t, CanTestZero t) => CanTestInteger (Complex t) Source # | |
Defined in Numeric.MixedTypes.Complex | |
| (CanTestInteger t, CanBeErrors es) => CanTestInteger (CollectErrors es t) Source # | |
Defined in Numeric.MixedTypes.Eq Methods certainlyNotInteger :: CollectErrors es t -> Bool Source # certainlyInteger :: CollectErrors es t -> Bool Source # certainlyIntegerGetIt :: CollectErrors es t -> Maybe Integer Source # | |
class CanTestZero t where Source #
Minimal complete definition
Nothing
Methods
isCertainlyZero :: t -> Bool Source #
default isCertainlyZero :: HasEqCertainly t Integer => t -> Bool Source #
isCertainlyNonZero :: t -> Bool Source #
default isCertainlyNonZero :: HasEqCertainly t Integer => t -> Bool Source #
Instances
| CanTestZero Double Source # | |
Defined in Numeric.MixedTypes.Eq | |
| CanTestZero Int Source # | |
Defined in Numeric.MixedTypes.Eq | |
| CanTestZero Integer Source # | |
Defined in Numeric.MixedTypes.Eq | |
| CanTestZero Rational Source # | |
Defined in Numeric.MixedTypes.Eq | |
| (CanTestZero t, CanBeErrors es) => CanTestZero (CollectErrors es t) Source # | |
Defined in Numeric.MixedTypes.Eq Methods isCertainlyZero :: CollectErrors es t -> Bool Source # isCertainlyNonZero :: CollectErrors es t -> Bool Source # | |
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
| CanPickNonZero Int Source # | |
Defined in Numeric.MixedTypes.Eq | |
| CanPickNonZero Integer Source # | |
Defined in Numeric.MixedTypes.Eq | |
| CanPickNonZero Rational Source # | |
Defined in Numeric.MixedTypes.Eq | |
| (CanPickNonZero a, CanBeErrors es) => CanPickNonZero (CollectErrors es a) Source # | |
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.