Copyright | (c) Michal Konecny |
---|---|
License | BSD3 |
Maintainer | mikkonecny@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type HasOrder t1 t2 = (HasOrderAsymmetric t1 t2, HasOrderAsymmetric t2 t1, OrderCompareType t1 t2 ~ OrderCompareType t2 t1)
- class IsBool (OrderCompareType a b) => HasOrderAsymmetric a b where
- type OrderCompareType a b
- lessThan :: a -> b -> OrderCompareType a b
- greaterThan :: a -> b -> OrderCompareType a b
- leq :: a -> b -> OrderCompareType a b
- geq :: a -> b -> OrderCompareType a b
- (>) :: HasOrderAsymmetric a b => a -> b -> OrderCompareType a b
- (<) :: HasOrderAsymmetric a b => a -> b -> OrderCompareType a b
- (<=) :: HasOrderAsymmetric a b => a -> b -> OrderCompareType a b
- (>=) :: HasOrderAsymmetric a b => a -> b -> OrderCompareType a b
- type HasOrderCertainlyAsymmetric t1 t2 = (HasOrderAsymmetric t1 t2, CanTestCertainly (OrderCompareType t1 t2))
- type HasOrderCertainly t1 t2 = (HasOrder t1 t2, CanTestCertainly (OrderCompareType t1 t2))
- (?<=?) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool
- (?<?) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool
- (?>=?) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool
- (?>?) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool
- (!<=!) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool
- (!<!) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool
- (!>=!) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool
- (!>!) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool
- specHasOrder :: _ => T t1 -> T t2 -> T t3 -> Spec
- specHasOrderNotMixed :: _ => T t -> Spec
- class CanTestPosNeg t where
- isCertainlyPositive :: t -> Bool
- isCertainlyNonNegative :: t -> Bool
- isCertainlyNegative :: t -> Bool
- isCertainlyNonPositive :: t -> Bool
Comparisons in numeric order
type HasOrder t1 t2 = (HasOrderAsymmetric t1 t2, HasOrderAsymmetric t2 t1, OrderCompareType t1 t2 ~ OrderCompareType t2 t1) Source #
class IsBool (OrderCompareType a b) => HasOrderAsymmetric a b where Source #
Nothing
type OrderCompareType a b Source #
type OrderCompareType a b = Bool
lessThan :: a -> b -> OrderCompareType a b Source #
default lessThan :: (OrderCompareType a b ~ Bool, a ~ b, Ord a) => a -> b -> OrderCompareType a b Source #
greaterThan :: a -> b -> OrderCompareType a b Source #
default greaterThan :: (HasOrder b a, OrderCompareType b a ~ OrderCompareType a b) => a -> b -> OrderCompareType a b Source #
leq :: a -> b -> OrderCompareType a b Source #
default leq :: (OrderCompareType a b ~ Bool, a ~ b, Ord a) => a -> b -> OrderCompareType a b Source #
geq :: a -> b -> OrderCompareType a b Source #
default geq :: (HasOrder b a, OrderCompareType b a ~ OrderCompareType a b) => a -> b -> OrderCompareType a b Source #
Instances
(>) :: HasOrderAsymmetric a b => a -> b -> OrderCompareType a b infix 4 Source #
(<) :: HasOrderAsymmetric a b => a -> b -> OrderCompareType a b infix 4 Source #
(<=) :: HasOrderAsymmetric a b => a -> b -> OrderCompareType a b infix 4 Source #
(>=) :: HasOrderAsymmetric a b => a -> b -> OrderCompareType a b infix 4 Source #
type HasOrderCertainlyAsymmetric t1 t2 = (HasOrderAsymmetric t1 t2, CanTestCertainly (OrderCompareType t1 t2)) Source #
type HasOrderCertainly t1 t2 = (HasOrder t1 t2, CanTestCertainly (OrderCompareType t1 t2)) Source #
(?<=?) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #
(?<?) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #
(?>=?) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #
(?>?) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #
(!<=!) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #
(!<!) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #
(!>=!) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #
(!>!) :: HasOrderCertainlyAsymmetric a b => a -> b -> Bool infix 4 Source #
Tests
specHasOrder :: _ => T t1 -> T t2 -> T t3 -> Spec Source #
HSpec properties that each implementation of HasOrder
should satisfy.
specHasOrderNotMixed :: _ => T t -> Spec Source #
HSpec properties that each implementation of HasOrder
should satisfy.
Specific comparisons
class CanTestPosNeg t where Source #
Nothing
isCertainlyPositive :: t -> Bool Source #
default isCertainlyPositive :: HasOrderCertainly t Integer => t -> Bool Source #
isCertainlyNonNegative :: t -> Bool Source #
default isCertainlyNonNegative :: HasOrderCertainly t Integer => t -> Bool Source #
isCertainlyNegative :: t -> Bool Source #
default isCertainlyNegative :: HasOrderCertainly t Integer => t -> Bool Source #
isCertainlyNonPositive :: t -> Bool Source #
default isCertainlyNonPositive :: HasOrderCertainly t Integer => t -> Bool Source #