Copyright | (c) Michal Konecny |
---|---|
License | BSD3 |
Maintainer | mikkonecny@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Exact real numbers represented by fast-converging Cauchy sequences of MPBalls.
- module AERN2.MP
- module AERN2.AccuracySG
- type CauchyRealP = SequenceP MPBall
- pCR :: CauchyRealP
- type CauchyRealA to = SequenceA to MPBall
- type CauchyReal = CauchyRealA (->)
- newCR :: QAArrow to => String -> [AnyProtocolQA to] -> ((Maybe (QAId to), Maybe (QAId to)) -> AccuracySG `to` MPBall) -> CauchyRealA to
- type CauchyRealCNA to = SequenceA to (CN MPBall)
- type CauchyRealCN = CauchyRealCNA (->)
- newCRCN :: QAArrow to => String -> [AnyProtocolQA to] -> ((Maybe (QAId to), Maybe (QAId to)) -> AccuracySG `to` CN MPBall) -> CauchyRealCNA to
- realName :: SequenceA to a -> String
- realId :: QA to p -> Maybe (QAId to)
- realSources :: QA to p -> [QAId to]
- realRename :: (String -> String) -> SequenceA to a -> SequenceA to a
- realWithAccuracy :: QAArrow to => CauchyRealA to -> AccuracySG `to` MPBall
- (?) :: QAArrow to => QA to p -> Q p `to` A p
- realWithAccuracyA :: QAArrow to => Maybe (QAId to) -> (CauchyRealA to, AccuracySG) `to` MPBall
- realsWithAccuracyA :: QAArrow to => Maybe (QAId to) -> ([CauchyRealA to], AccuracySG) `to` [MPBall]
- (-:-) :: (QAArrow to, QAProtocolCacheable p) => QA to p `to` QA to p
- convergentList2CauchyRealA :: QAArrow to => String -> [MPBall] -> CauchyRealA to
- seqByPrecision2CauchyRealA :: QAArrow to => String -> (Precision -> MPBall) -> CauchyRealA to
- type CanBeReal t = CanBeRealA (->) t
- real :: CanBeRealA (->) t => t -> CauchyReal
- type CanBeRealA to t = ConvertibleExactly t (CauchyRealA to)
- realA :: CanBeRealA to t => t -> CauchyRealA to
- type CanBeComplex t = CanBeComplexA (->) t
- complex :: CanBeComplexA (->) t => t -> Complex CauchyReal
- type CanBeComplexA to t = ConvertibleExactly t (Complex (CauchyRealA to))
- complexA :: CanBeComplexA to t => t -> Complex (CauchyRealA to)
- pi :: CauchyReal
- piA :: QAArrow to => CauchyRealA to
- _addslACachedPrint :: IO ()
- _addslAParPrint :: IO ()
- _example_pif :: CauchyReal -> CauchyRealCN
- _nsection :: Integer -> (Rational -> CauchyReal) -> (Rational, Rational) -> CauchyRealCN
Re-exported dependencies
module AERN2.MP
module AERN2.AccuracySG
The type of real numbers
type CauchyRealP = SequenceP MPBall Source #
pCR :: CauchyRealP Source #
type CauchyRealA to = SequenceA to MPBall Source #
type CauchyReal = CauchyRealA (->) Source #
newCR :: QAArrow to => String -> [AnyProtocolQA to] -> ((Maybe (QAId to), Maybe (QAId to)) -> AccuracySG `to` MPBall) -> CauchyRealA to Source #
type CauchyRealCN = CauchyRealCNA (->) Source #
newCRCN :: QAArrow to => String -> [AnyProtocolQA to] -> ((Maybe (QAId to), Maybe (QAId to)) -> AccuracySG `to` CN MPBall) -> CauchyRealCNA to Source #
Sequence ops specialised to reals
realSources :: QA to p -> [QAId to] Source #
realWithAccuracy :: QAArrow to => CauchyRealA to -> AccuracySG `to` MPBall Source #
Get a ball approximation of the real number with at least the specified accuracy.
(A specialisation of qaMakeQuery
for Cauchy reals.)
(?) :: QAArrow to => QA to p -> Q p `to` A p infix 1 Source #
An infix synonym of qaMakeQuery
with no source
realWithAccuracyA :: QAArrow to => Maybe (QAId to) -> (CauchyRealA to, AccuracySG) `to` MPBall Source #
realsWithAccuracyA :: QAArrow to => Maybe (QAId to) -> ([CauchyRealA to], AccuracySG) `to` [MPBall] Source #
(-:-) :: (QAArrow to, QAProtocolCacheable p) => QA to p `to` QA to p infix 0 Source #
An infix synonym of qaRegister
convergentList2CauchyRealA :: QAArrow to => String -> [MPBall] -> CauchyRealA to Source #
seqByPrecision2CauchyRealA :: QAArrow to => String -> (Precision -> MPBall) -> CauchyRealA to Source #
Conversions
type CanBeReal t = CanBeRealA (->) t Source #
real :: CanBeRealA (->) t => t -> CauchyReal Source #
type CanBeRealA to t = ConvertibleExactly t (CauchyRealA to) Source #
realA :: CanBeRealA to t => t -> CauchyRealA to Source #
type CanBeComplex t = CanBeComplexA (->) t Source #
complex :: CanBeComplexA (->) t => t -> Complex CauchyReal Source #
type CanBeComplexA to t = ConvertibleExactly t (Complex (CauchyRealA to)) Source #
complexA :: CanBeComplexA to t => t -> Complex (CauchyRealA to) Source #
Constants
pi :: CauchyReal Source #
To get pi
in an arbitrary arrow, use piA
.
piA :: QAArrow to => CauchyRealA to Source #
Mini demos
_addslACachedPrint :: IO () Source #
_addslAParPrint :: IO () Source #
_nsection :: Integer -> (Rational -> CauchyReal) -> (Rational, Rational) -> CauchyRealCN Source #