mixed-types-num-0.1.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 -> Bool 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 -> Bool 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 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

specHasOrder :: (HasOrderX t1 t1, HasOrderX t1 t2, HasOrderX t1 t3, HasOrderX t2 t3, CanAndOrX (OrderCompareType t1 t2) (OrderCompareType t2 t3)) => T t1 -> T t2 -> T t3 -> Spec Source #

HSpec properties that each implementation of HasOrder should satisfy.

specHasOrderNotMixed :: (HasOrderX t t, CanAndOrX (OrderCompareType t t) (OrderCompareType t t)) => T t -> Spec Source #

HSpec properties that each implementation of HasOrder should satisfy.

type HasOrderX t1 t2 = (HasOrderCertainly t1 t2, Show t1, Arbitrary t1, Show t2, Arbitrary t2) Source #

Compound type constraint useful for test definition.

Specific comparisons