aern2-mp-0.2.2.0: Multi-precision ball (interval) arithmetic
Copyright(c) Michal Konecny
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

AERN2.MP.WithCurrentPrec

Description

Type wrapper setting default precision.

Not suitable for use with MixedTypesNumPrelude since we need binary operators to enforce the same precision on both operands via the equality of their types.

Borrowed some tricks from https://github.com/ekmett/rounded/blob/master/src/Numeric/Rounded/Precision.hs

Synopsis

Documentation

newtype WithCurrentPrec t p Source #

Constructors

WithCurrentPrec 

Fields

Instances

Instances details
CanTakeErrors NumErrors t => CanTakeErrors NumErrors (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

(HasLimits ix (CN MPBall -> CN MPBall), LimitType ix (CN MPBall -> CN MPBall) ~ (CN MPBall -> CN MPBall), HasCurrentPrecision p) => HasLimits ix (WithCurrentPrec (CN MPBall) p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

Associated Types

type LimitType ix (WithCurrentPrec (CN MPBall) p) Source #

Eq t => Eq (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

HasCurrentPrecision p => Floating (WithCurrentPrec (CN MPBall) p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

Methods

pi :: WithCurrentPrec (CN MPBall) p #

exp :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

log :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

sqrt :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

(**) :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

logBase :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

sin :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

cos :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

tan :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

asin :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

acos :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

atan :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

sinh :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

cosh :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

tanh :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

asinh :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

acosh :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

atanh :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

log1p :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

expm1 :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

log1pexp :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

log1mexp :: WithCurrentPrec (CN MPBall) p -> WithCurrentPrec (CN MPBall) p #

(HasCurrentPrecision p, Fractional t, ConvertibleWithPrecision Integer t, ConvertibleWithPrecision Rational t) => Fractional (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

(HasCurrentPrecision p, Num t, ConvertibleWithPrecision Integer t) => Num (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

Ord t => Ord (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

Show t => Show (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

(CanMinMaxAsymmetric t1 t2, p1 ~ p2) => CanMinMaxAsymmetric (WithCurrentPrec t1 p1) (WithCurrentPrec t2 p2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

Associated Types

type MinMaxType (WithCurrentPrec t1 p1) (WithCurrentPrec t2 p2) #

HasOrderAsymmetric t1 t2 => HasOrderAsymmetric (WithCurrentPrec t1 p1) (WithCurrentPrec t2 p2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

Associated Types

type OrderCompareType (WithCurrentPrec t1 p1) (WithCurrentPrec t2 p2) #

type LimitType ix (WithCurrentPrec (CN MPBall) p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

type MinMaxType (WithCurrentPrec t1 p1) (WithCurrentPrec t2 p2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

type OrderCompareType (WithCurrentPrec t1 p1) (WithCurrentPrec t2 p2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

runWithPrec :: Precision -> (forall n. KnownNat n => WithCurrentPrec t n) -> t Source #

class HasCurrentPrecision p where Source #

Methods

getCurrentPrecision :: proxy p -> Precision Source #

Instances

Instances details
KnownNat n => HasCurrentPrecision (n :: Nat) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

Methods

getCurrentPrecision :: proxy n -> Precision Source #

newtype WithAnyPrec t Source #

An existential type wrapper for convenient conversions, eg using aern2-real:

_x :: KnownNat p => WithCurrentPrec (CN MPBall) p
_x = undefined

_r_x :: CReal
_r_x = creal $ WithAnyPrec _x

Constructors

WithAnyPrec (forall p. KnownNat p => WithCurrentPrec t p)