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

Contents

Description

 

Synopsis

Square root

class CanSqrt t where Source #

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

Associated Types

type SqrtType t Source #

Methods

sqrt :: t -> SqrtType t Source #

sqrt :: (SqrtType t ~ t, Floating t) => t -> SqrtType t Source #

Instances

CanSqrt Double Source # 

Associated Types

type SqrtType Double :: * Source #

(CanSqrt a, CanEnsureCE es a, CanEnsureCE es (SqrtType a), SuitableForCE es) => CanSqrt (CollectErrors es a) Source # 

Associated Types

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

Methods

sqrt :: CollectErrors es a -> SqrtType (CollectErrors es a) Source #

Exp

class CanExp t where Source #

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

Associated Types

type ExpType t Source #

Methods

exp :: t -> ExpType t Source #

exp :: (ExpType t ~ t, Floating t) => t -> ExpType t Source #

Instances

CanExp Double Source # 

Associated Types

type ExpType Double :: * Source #

(CanExp a, CanEnsureCE es a, CanEnsureCE es (ExpType a), SuitableForCE es) => CanExp (CollectErrors es a) Source # 

Associated Types

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

Methods

exp :: CollectErrors es a -> ExpType (CollectErrors es a) Source #

type CanExpSameType t = (CanExp t, ExpType t ~ t) Source #

Log

class CanLog t where Source #

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

Associated Types

type LogType t Source #

Methods

log :: t -> LogType t Source #

log :: (LogType t ~ t, Floating t) => t -> LogType t Source #

Instances

CanLog Double Source # 

Associated Types

type LogType Double :: * Source #

(CanLog a, CanEnsureCE es a, CanEnsureCE es (LogType a), SuitableForCE es) => CanLog (CollectErrors es a) Source # 

Associated Types

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

Methods

log :: CollectErrors es a -> LogType (CollectErrors es a) Source #

type CanLogSameType t = (CanLog t, LogType t ~ t) Source #

Sine and cosine

class CanSinCos t where Source #

A replacement for Prelude's cos and sin. If Floating t, then one can use the default implementation to mirror Prelude's sin, cos.

Associated Types

type SinCosType t Source #

Methods

cos :: t -> SinCosType t Source #

cos :: (SinCosType t ~ t, Floating t) => t -> SinCosType t Source #

sin :: t -> SinCosType t Source #

sin :: (SinCosType t ~ t, Floating t) => t -> SinCosType t Source #

specCanSinCosReal :: (Show t, Show (SinCosType t), Show (AddType (PowType (SinCosType t) Integer) (PowType (SinCosType t) Integer)), Show (SinCosType (SubType t t)), Show (SubType (MulType (SinCosType t) (SinCosType t)) (MulType (SinCosType t) (SinCosType t))), Show (AddType (MulType (SinCosType t) (SinCosType t)) (MulType (SinCosType t) (SinCosType t))), Show (DivType (SinCosType t) (SinCosType t)), Show (EnsureCN t), Arbitrary t, CanEnsureCN t, CanTestCertainly (OrderCompareType Integer (SinCosType t)), CanTestCertainly (OrderCompareType (SinCosType t) Integer), CanTestCertainly (EqCompareType (AddType (PowType (SinCosType t) Integer) (PowType (SinCosType t) Integer)) Integer), CanTestCertainly (EqCompareType (SinCosType (SubType t t)) (SubType (MulType (SinCosType t) (SinCosType t)) (MulType (SinCosType t) (SinCosType t)))), CanTestCertainly (EqCompareType (SinCosType (SubType t t)) (AddType (MulType (SinCosType t) (SinCosType t)) (MulType (SinCosType t) (SinCosType t)))), CanTestCertainly (OrderCompareType t Integer), CanTestCertainly (OrderCompareType t Rational), CanTestCertainly (OrderCompareType (SinCosType t) t), CanTestCertainly (OrderCompareType (EnsureCN t) (DivType (SinCosType t) (SinCosType t))), HasEqAsymmetric (AddType (PowType (SinCosType t) Integer) (PowType (SinCosType t) Integer)) Integer, HasEqAsymmetric (SinCosType (SubType t t)) (SubType (MulType (SinCosType t) (SinCosType t)) (MulType (SinCosType t) (SinCosType t))), HasEqAsymmetric (SinCosType (SubType t t)) (AddType (MulType (SinCosType t) (SinCosType t)) (MulType (SinCosType t) (SinCosType t))), HasOrderAsymmetric t Integer, HasOrderAsymmetric t Rational, HasOrderAsymmetric (SinCosType t) t, HasOrderAsymmetric (SinCosType t) Integer, HasOrderAsymmetric (EnsureCN t) (DivType (SinCosType t) (SinCosType t)), HasOrderAsymmetric Integer (SinCosType t), CanSub t t, CanSub (MulType (SinCosType t) (SinCosType t)) (MulType (SinCosType t) (SinCosType t)), CanAddAsymmetric (PowType (SinCosType t) Integer) (PowType (SinCosType t) Integer), CanAddAsymmetric (MulType (SinCosType t) (SinCosType t)) (MulType (SinCosType t) (SinCosType t)), CanPow (SinCosType t) Integer, CanMulAsymmetric (SinCosType t) (SinCosType t), CanDiv (SinCosType t) (SinCosType t), CanSinCos t, CanSinCos (SubType t t)) => T t -> Spec Source #

HSpec properties that each implementation of CanSinCos should satisfy.

Derived partially from http://math.stackexchange.com/questions/1303044/axiomatic-definition-of-sin-and-cos

approxPi :: Floating t => t Source #

Approximate pi, synonym for Prelude's pi.

We do not define (exect) pi in this package as we have no type that can represent it exactly.

Orphan instances