mixed-types-num-0.3.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.MinMaxAbs

Contents

Description

 

Synopsis

Minimum and maximum

class CanMinMaxAsymmetric t1 t2 where Source #

A replacement for Prelude's min and max. If t1 = t2 and Ord t1, then one can use the default implementation to mirror Prelude's min and max.

Associated Types

type MinMaxType t1 t2 Source #

Methods

min :: t1 -> t2 -> MinMaxType t1 t2 Source #

max :: t1 -> t2 -> MinMaxType t1 t2 Source #

min :: (MinMaxType t1 t2 ~ t1, t1 ~ t2, Ord t1) => t1 -> t2 -> MinMaxType t1 t2 Source #

max :: (MinMaxType t1 t2 ~ t1, t1 ~ t2, Ord t1) => t1 -> t2 -> MinMaxType t1 t2 Source #

Instances

CanMinMaxAsymmetric Double Double Source # 
CanMinMaxAsymmetric Int Int Source # 

Associated Types

type MinMaxType Int Int :: * Source #

CanMinMaxAsymmetric Int Integer Source # 
CanMinMaxAsymmetric Int Rational Source # 
CanMinMaxAsymmetric Integer Int Source # 
CanMinMaxAsymmetric Integer Integer Source # 
CanMinMaxAsymmetric Integer Rational Source # 
CanMinMaxAsymmetric Rational Int Source # 
CanMinMaxAsymmetric Rational Integer Source # 
CanMinMaxAsymmetric Rational Rational Source # 
(CanMinMaxAsymmetric Double b0, CanEnsureCE es0 b0, CanEnsureCE es0 (MinMaxType Double b0), SuitableForCE es0) => CanMinMaxAsymmetric Double (CollectErrors es0 b0) Source # 

Associated Types

type MinMaxType Double (CollectErrors es0 b0) :: * Source #

(CanMinMaxAsymmetric Int b0, CanEnsureCE es0 b0, CanEnsureCE es0 (MinMaxType Int b0), SuitableForCE es0) => CanMinMaxAsymmetric Int (CollectErrors es0 b0) Source # 

Associated Types

type MinMaxType Int (CollectErrors es0 b0) :: * Source #

Methods

min :: Int -> CollectErrors es0 b0 -> MinMaxType Int (CollectErrors es0 b0) Source #

max :: Int -> CollectErrors es0 b0 -> MinMaxType Int (CollectErrors es0 b0) Source #

(CanMinMaxAsymmetric Integer b0, CanEnsureCE es0 b0, CanEnsureCE es0 (MinMaxType Integer b0), SuitableForCE es0) => CanMinMaxAsymmetric Integer (CollectErrors es0 b0) Source # 

Associated Types

type MinMaxType Integer (CollectErrors es0 b0) :: * Source #

(CanMinMaxAsymmetric Rational b0, CanEnsureCE es0 b0, CanEnsureCE es0 (MinMaxType Rational b0), SuitableForCE es0) => CanMinMaxAsymmetric Rational (CollectErrors es0 b0) Source # 

Associated Types

type MinMaxType Rational (CollectErrors es0 b0) :: * Source #

CanMinMaxAsymmetric a b => CanMinMaxAsymmetric [a] [b] Source # 

Associated Types

type MinMaxType [a] [b] :: * Source #

Methods

min :: [a] -> [b] -> MinMaxType [a] [b] Source #

max :: [a] -> [b] -> MinMaxType [a] [b] Source #

CanMinMaxAsymmetric a b => CanMinMaxAsymmetric (Maybe a) (Maybe b) Source # 

Associated Types

type MinMaxType (Maybe a) (Maybe b) :: * Source #

Methods

min :: Maybe a -> Maybe b -> MinMaxType (Maybe a) (Maybe b) Source #

max :: Maybe a -> Maybe b -> MinMaxType (Maybe a) (Maybe b) Source #

(CanMinMaxAsymmetric a0 Double, CanEnsureCE es0 a0, CanEnsureCE es0 (MinMaxType a0 Double), SuitableForCE es0) => CanMinMaxAsymmetric (CollectErrors es0 a0) Double Source # 

Associated Types

type MinMaxType (CollectErrors es0 a0) Double :: * Source #

(CanMinMaxAsymmetric a0 Rational, CanEnsureCE es0 a0, CanEnsureCE es0 (MinMaxType a0 Rational), SuitableForCE es0) => CanMinMaxAsymmetric (CollectErrors es0 a0) Rational Source # 

Associated Types

type MinMaxType (CollectErrors es0 a0) Rational :: * Source #

(CanMinMaxAsymmetric a0 Int, CanEnsureCE es0 a0, CanEnsureCE es0 (MinMaxType a0 Int), SuitableForCE es0) => CanMinMaxAsymmetric (CollectErrors es0 a0) Int Source # 

Associated Types

type MinMaxType (CollectErrors es0 a0) Int :: * Source #

Methods

min :: CollectErrors es0 a0 -> Int -> MinMaxType (CollectErrors es0 a0) Int Source #

max :: CollectErrors es0 a0 -> Int -> MinMaxType (CollectErrors es0 a0) Int Source #

(CanMinMaxAsymmetric a0 Integer, CanEnsureCE es0 a0, CanEnsureCE es0 (MinMaxType a0 Integer), SuitableForCE es0) => CanMinMaxAsymmetric (CollectErrors es0 a0) Integer Source # 

Associated Types

type MinMaxType (CollectErrors es0 a0) Integer :: * Source #

(CanMinMaxAsymmetric a b, CanEnsureCE es a, CanEnsureCE es b, CanEnsureCE es (MinMaxType a b), SuitableForCE es) => CanMinMaxAsymmetric (CollectErrors es a) (CollectErrors es b) Source # 

Associated Types

type MinMaxType (CollectErrors es a) (CollectErrors es b) :: * Source #

type CanMinMaxThis t1 t2 = (CanMinMax t1 t2, MinMaxType t1 t2 ~ t1) Source #

Tests

Absolute value

class CanAbs t where Source #

A replacement for Prelude's abs. If Num t, then one can use the default implementation to mirror Prelude's abs.

Associated Types

type AbsType t Source #

Methods

abs :: t -> AbsType t Source #

abs :: (AbsType t ~ t, Num t) => t -> AbsType t Source #

Instances

CanAbs Double Source # 

Associated Types

type AbsType Double :: * Source #

CanAbs Int Source # 

Associated Types

type AbsType Int :: * Source #

Methods

abs :: Int -> AbsType Int Source #

CanAbs Integer Source # 

Associated Types

type AbsType Integer :: * Source #

CanAbs Rational Source # 

Associated Types

type AbsType Rational :: * Source #

(CanAbs a, CanEnsureCE es a, CanEnsureCE es (AbsType a), SuitableForCE es) => CanAbs (CollectErrors es a) Source # 

Associated Types

type AbsType (CollectErrors es a) :: * Source #

Methods

abs :: CollectErrors es a -> AbsType (CollectErrors es a) Source #

type CanAbsSameType t = (CanAbs t, AbsType t ~ t) Source #

Tests

specCanNegNum :: (CanNegX t, CanNegX (NegType t), HasEqCertainly t (NegType (NegType t)), ConvertibleExactly Integer t, HasEqCertainly t t, HasEqCertainly t (NegType t), CanTestPosNeg t, CanTestPosNeg (NegType t)) => T t -> Spec Source #

HSpec properties that each numeric implementation of CanNeg should satisfy.

specCanAbs :: (CanAbsX t, CanAbsX (AbsType t)) => T t -> Spec Source #

HSpec properties that each implementation of CanAbs should satisfy.

Orphan instances

CanNeg Double Source # 

Associated Types

type NegType Double :: * Source #

CanNeg Int Source # 

Associated Types

type NegType Int :: * Source #

Methods

negate :: Int -> NegType Int Source #

CanNeg Integer Source # 

Associated Types

type NegType Integer :: * Source #

CanNeg Rational Source # 

Associated Types

type NegType Rational :: * Source #