| Copyright | (c) Michal Konecny |
|---|---|
| License | BSD3 |
| Maintainer | mikkonecny@gmail.com |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell98 |
Numeric.MixedTypes.Elementary
Description
- class CanSqrt t where
- type SqrtType t
- type CanSqrtSameType t = (CanSqrt t, SqrtType t ~ t)
- type CanSqrtCNSameType t = (CanSqrt t, SqrtType t ~ EnsureCN t)
- specCanSqrtReal :: (CanSqrtX t, CanPowX (SqrtType t) Integer, HasEqCertainly t (PowType (SqrtType t) Integer)) => T t -> Spec
- class CanExp t where
- type ExpType t
- type CanExpSameType t = (CanExp t, ExpType t ~ t)
- specCanExpReal :: CanExpX t => T t -> Spec
- class CanLog t where
- type LogType t
- type CanLogSameType t = (CanLog t, LogType t ~ t)
- type CanLogCNSameType t = (CanLog t, LogType t ~ EnsureCN t)
- specCanLogReal :: (CanLogX t, CanLogX (DivType Integer t), CanExp t, CanLogX (ExpType t), HasEqCertainly (LogType t) (LogType (EnsureCN t)), HasEqCertainlyCN t (LogType (ExpType t))) => T t -> Spec
- powUsingExpLog :: (CanTestPosNeg t, CanEnsureCN t, CanEnsureCN (EnsureCN t), EnsureCN t ~ EnsureCN (EnsureCN t), CanLogCNSameType t, CanMulSameType t, CanMulSameType (EnsureCN t), CanExpSameType (EnsureCN t), CanTestInteger t, HasIntegers t, CanTestZero t, CanRecipCNSameType t, HasIntegers (EnsureCN t)) => t -> t -> EnsureCN t
- class CanSinCos t where
- type SinCosType t
- type CanSinCosSameType t = (CanSinCos t, SinCosType t ~ t)
- specCanSinCosReal :: CanSinCosX t => T t -> Spec
- approxPi :: Floating t => t
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.
Instances
| CanSqrt Double Source # | |
| (CanSqrt a, CanEnsureCE es (SqrtType a), SuitableForCE es) => CanSqrt (CollectErrors es a) Source # | |
type CanSqrtSameType t = (CanSqrt t, SqrtType t ~ t) Source #
specCanSqrtReal :: (CanSqrtX t, CanPowX (SqrtType t) Integer, HasEqCertainly t (PowType (SqrtType t) Integer)) => T t -> Spec Source #
HSpec properties that each implementation of CanSqrt should satisfy.
Exp
A replacement for Prelude's exp. If Floating t,
then one can use the default implementation to mirror Prelude's exp.
Instances
| CanExp Double Source # | |
| (CanExp a, CanEnsureCE es (ExpType a), SuitableForCE es) => CanExp (CollectErrors es a) Source # | |
type CanExpSameType t = (CanExp t, ExpType t ~ t) Source #
specCanExpReal :: CanExpX t => T t -> Spec Source #
HSpec properties that each implementation of CanExp should satisfy.
Log
A replacement for Prelude's log. If Floating t,
then one can use the default implementation to mirror Prelude's log.
Instances
| CanLog Double Source # | |
| (CanLog a, CanEnsureCE es (LogType a), SuitableForCE es) => CanLog (CollectErrors es a) Source # | |
type CanLogSameType t = (CanLog t, LogType t ~ t) Source #
specCanLogReal :: (CanLogX t, CanLogX (DivType Integer t), CanExp t, CanLogX (ExpType t), HasEqCertainly (LogType t) (LogType (EnsureCN t)), HasEqCertainlyCN t (LogType (ExpType t))) => T t -> Spec Source #
HSpec properties that each implementation of CanLog should satisfy.
powUsingExpLog :: (CanTestPosNeg t, CanEnsureCN t, CanEnsureCN (EnsureCN t), EnsureCN t ~ EnsureCN (EnsureCN t), CanLogCNSameType t, CanMulSameType t, CanMulSameType (EnsureCN t), CanExpSameType (EnsureCN t), CanTestInteger t, HasIntegers t, CanTestZero t, CanRecipCNSameType t, HasIntegers (EnsureCN t)) => t -> t -> EnsureCN 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 -> t Source #
sin :: t -> SinCosType t Source #
sin :: (SinCosType t ~ t, Floating t) => t -> t Source #
Instances
| CanSinCos Double Source # | |
| (CanSinCos a, CanEnsureCE es (SinCosType a), SuitableForCE es) => CanSinCos (CollectErrors es a) Source # | |
type CanSinCosSameType t = (CanSinCos t, SinCosType t ~ t) Source #
specCanSinCosReal :: CanSinCosX 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.