mixed-types-num-0.3.1.5: 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 #

Minimal complete definition

Nothing

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 # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Double Double :: Type Source #

HasOrderAsymmetric Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Double Int :: Type Source #

HasOrderAsymmetric Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Double Integer :: Type Source #

HasOrderAsymmetric Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Int Double :: Type Source #

HasOrderAsymmetric Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Int Int :: Type Source #

HasOrderAsymmetric Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Int Integer :: Type Source #

HasOrderAsymmetric Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Int Rational :: Type Source #

HasOrderAsymmetric Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Integer Double :: Type Source #

HasOrderAsymmetric Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Integer Int :: Type Source #

HasOrderAsymmetric Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Integer Integer :: Type Source #

HasOrderAsymmetric Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Integer Rational :: Type Source #

HasOrderAsymmetric Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Rational Int :: Type Source #

HasOrderAsymmetric Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Rational Integer :: Type Source #

HasOrderAsymmetric Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Rational Rational :: Type Source #

HasOrderAsymmetric () () Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType () () :: Type Source #

Methods

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

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

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

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

(HasOrderAsymmetric Double b, CanEnsureCE es b, CanEnsureCE es (OrderCompareType Double b), IsBool (EnsureCE es (OrderCompareType Double b)), SuitableForCE es) => HasOrderAsymmetric Double (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Double (CollectErrors es b) :: Type Source #

(HasOrderAsymmetric Int b, CanEnsureCE es b, CanEnsureCE es (OrderCompareType Int b), IsBool (EnsureCE es (OrderCompareType Int b)), SuitableForCE es) => HasOrderAsymmetric Int (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Int (CollectErrors es b) :: Type Source #

(HasOrderAsymmetric Integer b, CanEnsureCE es b, CanEnsureCE es (OrderCompareType Integer b), IsBool (EnsureCE es (OrderCompareType Integer b)), SuitableForCE es) => HasOrderAsymmetric Integer (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Integer (CollectErrors es b) :: Type Source #

(HasOrderAsymmetric Rational b, CanEnsureCE es b, CanEnsureCE es (OrderCompareType Rational b), IsBool (EnsureCE es (OrderCompareType Rational b)), SuitableForCE es) => HasOrderAsymmetric Rational (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType Rational (CollectErrors es b) :: Type Source #

(HasOrderAsymmetric a Integer, CanEnsureCE es a, CanEnsureCE es (OrderCompareType a Integer), IsBool (EnsureCE es (OrderCompareType a Integer)), SuitableForCE es) => HasOrderAsymmetric (CollectErrors es a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType (CollectErrors es a) Integer :: Type Source #

(HasOrderAsymmetric a Int, CanEnsureCE es a, CanEnsureCE es (OrderCompareType a Int), IsBool (EnsureCE es (OrderCompareType a Int)), SuitableForCE es) => HasOrderAsymmetric (CollectErrors es a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType (CollectErrors es a) Int :: Type Source #

(HasOrderAsymmetric a Rational, CanEnsureCE es a, CanEnsureCE es (OrderCompareType a Rational), IsBool (EnsureCE es (OrderCompareType a Rational)), SuitableForCE es) => HasOrderAsymmetric (CollectErrors es a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType (CollectErrors es a) Rational :: Type Source #

(HasOrderAsymmetric a Double, CanEnsureCE es a, CanEnsureCE es (OrderCompareType a Double), IsBool (EnsureCE es (OrderCompareType a Double)), SuitableForCE es) => HasOrderAsymmetric (CollectErrors es a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType (CollectErrors es a) Double :: Type 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 # 
Instance details

Defined in Numeric.MixedTypes.Ord

Associated Types

type OrderCompareType (CollectErrors es a) (CollectErrors es b) :: Type 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 #

Minimal complete definition

Nothing

Instances
CanTestPosNeg Double Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

CanTestPosNeg Int Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

CanTestPosNeg Integer Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

CanTestPosNeg Rational Source # 
Instance details

Defined in Numeric.MixedTypes.Ord

(CanTestPosNeg t, SuitableForCE es) => CanTestPosNeg (CollectErrors es t) Source # 
Instance details

Defined in Numeric.MixedTypes.Ord