mixed-types-num-0.5.12: Alternative Prelude with numeric and logic expressions typed bottom-up
Copyright(c) Michal Konecny
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Numeric.MixedTypes.MinMaxAbs

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 #

type MinMaxType t1 t2 = t1

Methods

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

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

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

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

Instances

Instances details
CanMinMaxAsymmetric Rational Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Rational Rational Source #

CanMinMaxAsymmetric Rational Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Rational Integer Source #

CanMinMaxAsymmetric Rational Double Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Rational Double Source #

CanMinMaxAsymmetric Rational Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Rational Int Source #

CanMinMaxAsymmetric Integer Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Integer Rational Source #

CanMinMaxAsymmetric Integer Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Integer Integer Source #

CanMinMaxAsymmetric Integer Double Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Integer Double Source #

CanMinMaxAsymmetric Integer Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Integer Int Source #

CanMinMaxAsymmetric Double Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Double Rational Source #

CanMinMaxAsymmetric Double Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Double Integer Source #

CanMinMaxAsymmetric Double Double Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Double Double Source #

CanMinMaxAsymmetric Double Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Double Int Source #

CanMinMaxAsymmetric Int Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Int Rational Source #

CanMinMaxAsymmetric Int Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Int Integer Source #

CanMinMaxAsymmetric Int Double Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Int Double Source #

CanMinMaxAsymmetric Int Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Int Int Source #

(CanMinMaxAsymmetric Rational b, CanBeErrors es) => CanMinMaxAsymmetric Rational (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Rational (CollectErrors es b) Source #

(CanMinMaxAsymmetric Integer b, CanBeErrors es) => CanMinMaxAsymmetric Integer (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Integer (CollectErrors es b) Source #

(CanMinMaxAsymmetric Double b, CanBeErrors es) => CanMinMaxAsymmetric Double (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Double (CollectErrors es b) Source #

(CanMinMaxAsymmetric Int b, CanBeErrors es) => CanMinMaxAsymmetric Int (CollectErrors es b) Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType Int (CollectErrors es 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) 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 b => CanMinMaxAsymmetric [a] [b] Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType [a] [b] Source #

Methods

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

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

(CanMinMaxAsymmetric a Rational, CanBeErrors es) => CanMinMaxAsymmetric (CollectErrors es a) Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType (CollectErrors es a) Rational Source #

(CanMinMaxAsymmetric a Integer, CanBeErrors es) => CanMinMaxAsymmetric (CollectErrors es a) Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType (CollectErrors es a) Integer Source #

(CanMinMaxAsymmetric a Double, CanBeErrors es) => CanMinMaxAsymmetric (CollectErrors es a) Double Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType (CollectErrors es a) Double Source #

(CanMinMaxAsymmetric a Int, CanBeErrors es) => CanMinMaxAsymmetric (CollectErrors es a) Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type MinMaxType (CollectErrors es a) Int Source #

(CanMinMaxAsymmetric a b, CanBeErrors 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) Source #

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

Tests

specCanMinMax :: _ => T t1 -> T t2 -> T t3 -> Spec Source #

HSpec properties that each implementation of CanMinMax should satisfy.

specCanMinMaxNotMixed :: _ => T t -> Spec Source #

HSpec properties that each implementation of CanMinMax should satisfy.

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 #

type AbsType t = t

Methods

abs :: t -> AbsType t Source #

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

Instances

Instances details
CanAbs Rational Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type AbsType Rational Source #

CanAbs Integer Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type AbsType Integer Source #

CanAbs Double Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type AbsType Double Source #

CanAbs Int Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

Associated Types

type AbsType Int Source #

Methods

abs :: Int -> AbsType Int 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) Source #

Methods

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

(CanAbs a, CanBeErrors es) => CanAbs (CollectErrors es a) Source # 
Instance details

Defined in Numeric.MixedTypes.MinMaxAbs

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 :: _ => T t -> Spec Source #

HSpec properties that each numeric implementation of CanNeg should satisfy.

specCanAbs :: _ => T t -> Spec Source #

HSpec properties that each implementation of CanAbs should satisfy.

Orphan instances

CanNeg Rational Source # 
Instance details

Associated Types

type NegType Rational Source #

CanNeg Integer Source # 
Instance details

Associated Types

type NegType Integer Source #

CanNeg Double Source # 
Instance details

Associated Types

type NegType Double Source #

CanNeg Int Source # 
Instance details

Associated Types

type NegType Int Source #

Methods

negate :: Int -> NegType Int Source #