mixed-types-num-0.3.0.1: 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.Ord

Contents

Description

 

Synopsis

Comparisons in numeric order

class IsBool (OrderCompareType a b) => HasOrderAsymmetric a b where Source #

Associated Types

type OrderCompareType a b Source #

Methods

lessThan :: a -> b -> OrderCompareType a b Source #

lessThan :: (OrderCompareType a b ~ Bool, a ~ b, Ord a) => a -> b -> OrderCompareType a b Source #

greaterThan :: a -> b -> OrderCompareType a b Source #

greaterThan :: (HasOrder b a, OrderCompareType b a ~ OrderCompareType a b) => a -> b -> OrderCompareType a b Source #

leq :: a -> b -> OrderCompareType a b Source #

leq :: (OrderCompareType a b ~ Bool, a ~ b, Ord a) => a -> b -> OrderCompareType a b Source #

geq :: a -> b -> OrderCompareType a b Source #

geq :: (HasOrder b a, OrderCompareType b a ~ OrderCompareType a b) => a -> b -> OrderCompareType a b Source #

Instances

HasOrderAsymmetric Double Double Source # 
HasOrderAsymmetric Double Int Source # 
HasOrderAsymmetric Double Integer Source # 
HasOrderAsymmetric Int Double Source # 
HasOrderAsymmetric Int Int Source # 
HasOrderAsymmetric Int Integer Source # 
HasOrderAsymmetric Int Rational Source # 
HasOrderAsymmetric Integer Double Source # 
HasOrderAsymmetric Integer Int Source # 
HasOrderAsymmetric Integer Integer Source # 
HasOrderAsymmetric Integer Rational Source # 
HasOrderAsymmetric Rational Int Source # 
HasOrderAsymmetric Rational Integer Source # 
HasOrderAsymmetric Rational Rational Source # 
HasOrderAsymmetric () () Source # 

Associated Types

type OrderCompareType () () :: * Source #

Methods

lessThan :: () -> () -> OrderCompareType () () Source #

greaterThan :: () -> () -> OrderCompareType () () Source #

leq :: () -> () -> OrderCompareType () () Source #

geq :: () -> () -> OrderCompareType () () Source #

(HasOrderAsymmetric Double b0, CanEnsureCE es0 b0, CanEnsureCE es0 (OrderCompareType Double b0), IsBool (EnsureCE es0 (OrderCompareType Double b0)), SuitableForCE es0) => HasOrderAsymmetric Double (CollectErrors es0 b0) Source # 
(HasOrderAsymmetric Int b0, CanEnsureCE es0 b0, CanEnsureCE es0 (OrderCompareType Int b0), IsBool (EnsureCE es0 (OrderCompareType Int b0)), SuitableForCE es0) => HasOrderAsymmetric Int (CollectErrors es0 b0) Source # 
(HasOrderAsymmetric Integer b0, CanEnsureCE es0 b0, CanEnsureCE es0 (OrderCompareType Integer b0), IsBool (EnsureCE es0 (OrderCompareType Integer b0)), SuitableForCE es0) => HasOrderAsymmetric Integer (CollectErrors es0 b0) Source # 
(HasOrderAsymmetric Rational b0, CanEnsureCE es0 b0, CanEnsureCE es0 (OrderCompareType Rational b0), IsBool (EnsureCE es0 (OrderCompareType Rational b0)), SuitableForCE es0) => HasOrderAsymmetric Rational (CollectErrors es0 b0) Source # 
(HasOrderAsymmetric a0 Double, CanEnsureCE es0 a0, CanEnsureCE es0 (OrderCompareType a0 Double), IsBool (EnsureCE es0 (OrderCompareType a0 Double)), SuitableForCE es0) => HasOrderAsymmetric (CollectErrors es0 a0) Double Source # 
(HasOrderAsymmetric a0 Rational, CanEnsureCE es0 a0, CanEnsureCE es0 (OrderCompareType a0 Rational), IsBool (EnsureCE es0 (OrderCompareType a0 Rational)), SuitableForCE es0) => HasOrderAsymmetric (CollectErrors es0 a0) Rational Source # 
(HasOrderAsymmetric a0 Int, CanEnsureCE es0 a0, CanEnsureCE es0 (OrderCompareType a0 Int), IsBool (EnsureCE es0 (OrderCompareType a0 Int)), SuitableForCE es0) => HasOrderAsymmetric (CollectErrors es0 a0) Int Source # 
(HasOrderAsymmetric a0 Integer, CanEnsureCE es0 a0, CanEnsureCE es0 (OrderCompareType a0 Integer), IsBool (EnsureCE es0 (OrderCompareType a0 Integer)), SuitableForCE es0) => HasOrderAsymmetric (CollectErrors es0 a0) Integer Source # 
(HasOrderAsymmetric a b, CanEnsureCE es a, CanEnsureCE es b, CanEnsureCE es (OrderCompareType a b), IsBool (EnsureCE es (OrderCompareType a b)), SuitableForCE es) => HasOrderAsymmetric (CollectErrors es a) (CollectErrors es b) 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 #

(>=) :: HasOrderAsymmetric a b => a -> b -> OrderCompareType a b 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 #

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

Tests

specHasOrderNotMixed :: (Show t, Arbitrary t, CanTestCertainly (OrderCompareType t t), CanTestCertainly (AndOrType (OrderCompareType t t) (OrderCompareType t t)), HasOrderAsymmetric t t) => T t -> Spec Source #

HSpec properties that each implementation of HasOrder should satisfy.

Specific comparisons

class CanTestPosNeg t where Source #