Copyright | (c) Michal Konecny |
---|---|
License | BSD3 |
Maintainer | mikkonecny@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class CanSqrt t where
- type CanSqrtSameType t = (CanSqrt t, SqrtType t ~ t)
- specCanSqrtReal :: _ => T t -> Spec
- class CanExp t where
- type CanExpSameType t = (CanExp t, ExpType t ~ t)
- specCanExpReal :: _ => T t -> Spec
- class CanLog t where
- type CanLogSameType t = (CanLog t, LogType t ~ t)
- specCanLogReal :: _ => T t -> Spec
- powUsingExpLog :: (CanLogSameType t, CanExpSameType t, CanMulSameType t, CanTestInteger t, CanTestZero t, CanRecipSameType t) => t -> t -> t -> t
- class CanSinCos t where
- type SinCosType t
- cos :: t -> SinCosType t
- sin :: t -> SinCosType t
- type CanSinCosSameType t = (CanSinCos t, SinCosType t ~ t)
- specCanSinCosReal :: _ => 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
.
Nothing
type CanSqrtSameType t = (CanSqrt t, SqrtType t ~ t) Source #
specCanSqrtReal :: _ => 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
.
Nothing
type CanExpSameType t = (CanExp t, ExpType t ~ t) Source #
specCanExpReal :: _ => 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
.
Nothing
Instances
type CanLogSameType t = (CanLog t, LogType t ~ t) Source #
specCanLogReal :: _ => T t -> Spec Source #
HSpec properties that each implementation of CanLog should satisfy.
powUsingExpLog :: (CanLogSameType t, CanExpSameType t, CanMulSameType t, CanTestInteger t, CanTestZero t, CanRecipSameType t) => t -> t -> 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
.
Nothing
type SinCosType t Source #
type SinCosType t = t
cos :: t -> SinCosType t Source #
default cos :: (SinCosType t ~ t, Floating t) => t -> SinCosType t Source #
sin :: t -> SinCosType t Source #
default sin :: (SinCosType t ~ t, Floating t) => t -> SinCosType t Source #
Instances
CanSinCos Double Source # | |
Defined in Numeric.MixedTypes.Elementary type SinCosType Double Source # | |
CanSinCos a => CanSinCos (CN a) Source # | |
Defined in Numeric.MixedTypes.Elementary type SinCosType (CN a) Source # |
type CanSinCosSameType t = (CanSinCos t, SinCosType t ~ t) Source #
specCanSinCosReal :: _ => 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