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

Minimal complete definition

Nothing

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

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Double Double :: Type Source #

CanMinMaxAsymmetric Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Int Int :: Type Source #

CanMinMaxAsymmetric Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Int Integer :: Type Source #

CanMinMaxAsymmetric Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Int Rational :: Type Source #

CanMinMaxAsymmetric Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Integer Int :: Type Source #

CanMinMaxAsymmetric Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Integer Integer :: Type Source #

CanMinMaxAsymmetric Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Integer Rational :: Type Source #

CanMinMaxAsymmetric Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Rational Int :: Type Source #

CanMinMaxAsymmetric Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Rational Integer :: Type Source #

CanMinMaxAsymmetric Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Rational Rational :: Type Source #

(CanMinMaxAsymmetric Double b, CanEnsureCE es b, CanEnsureCE es (MinMaxType Double b), SuitableForCE es) => CanMinMaxAsymmetric Double (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

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

(CanMinMaxAsymmetric Int b, CanEnsureCE es b, CanEnsureCE es (MinMaxType Int b), SuitableForCE es) => CanMinMaxAsymmetric Int (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

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

(CanMinMaxAsymmetric Integer b, CanEnsureCE es b, CanEnsureCE es (MinMaxType Integer b), SuitableForCE es) => CanMinMaxAsymmetric Integer (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

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

(CanMinMaxAsymmetric Rational b, CanEnsureCE es b, CanEnsureCE es (MinMaxType Rational b), SuitableForCE es) => CanMinMaxAsymmetric Rational (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

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

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

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType [a] [b] :: Type 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 # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType (Maybe a) (Maybe b) :: Type 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 a Integer, CanEnsureCE es a, CanEnsureCE es (MinMaxType a Integer), SuitableForCE es) => CanMinMaxAsymmetric (CollectErrors es a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

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

(CanMinMaxAsymmetric a Int, CanEnsureCE es a, CanEnsureCE es (MinMaxType a Int), SuitableForCE es) => CanMinMaxAsymmetric (CollectErrors es a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

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

(CanMinMaxAsymmetric a Rational, CanEnsureCE es a, CanEnsureCE es (MinMaxType a Rational), SuitableForCE es) => CanMinMaxAsymmetric (CollectErrors es a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

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

(CanMinMaxAsymmetric a Double, CanEnsureCE es a, CanEnsureCE es (MinMaxType a Double), SuitableForCE es) => CanMinMaxAsymmetric (CollectErrors es a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

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

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

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

Minimal complete definition

Nothing

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

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type AbsType Double :: Type Source #

CanAbs Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type AbsType Int :: Type Source #

Methods

abs :: Int -> AbsType Int Source #

CanAbs Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type AbsType Integer :: Type Source #

CanAbs Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type AbsType Rational :: Type Source #

(CanMulAsymmetric t t, CanAddSameType (MulType t t), CanSqrt (MulType t t)) => CanAbs (Complex t) Source # 
Instance details

Defined in Numeric.MixedTypes.Complex

Associated Types

type AbsType (Complex t) :: Type Source #

Methods

abs :: Complex t -> AbsType (Complex t) Source #

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

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type AbsType (CollectErrors es a) :: Type 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), CanTestFinite 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), CanTestFinite t) => T t -> Spec Source #

HSpec properties that each implementation of CanAbs should satisfy.

Orphan instances

CanNeg Double Source # 
Instance details

Associated Types

type NegType Double :: Type Source #

CanNeg Int Source # 
Instance details

Associated Types

type NegType Int :: Type Source #

Methods

negate :: Int -> NegType Int Source #

CanNeg Integer Source # 
Instance details

Associated Types

type NegType Integer :: Type Source #

CanNeg Rational Source # 
Instance details

Associated Types

type NegType Rational :: Type Source #