|
| Data.Number.MPFR | | Portability | non-portable | | Stability | experimental | | Maintainer | ales.bizjak0@gmail.com |
|
|
|
|
|
| Description |
This module exports a pure interface to the MPFR library functions. Functions
return new MPFR structures instead of modifying existing ones and so all
functions which produce a new MPFR structure take one more parameter than
their original C counterparts. This parameter, Precision, is the precision
of the resulting MPFR.
This is naturally slower than modifying in-place, especially when dealing
with lower precisions, so a "mutable" interface is provided in
Data.Number.MPFR.Mutable module.
Naming conventions
- functions ending with _ (underscore) usually return a pair (MPFR, Int), where
Int is a return value of a corresponding mpfr_ function. See the MPFR manual for
a description of return values.
- the same functions without the _ return just the MPFR.
- mpfr_ prefix in functions is removed
- _ui and ui_ in function becomes w (stands for Word).
For example mpfr_sub_ui becomes subw and mpfr_ui_sub becomes wsub.
- si_ and _si in functions becomes i (stands for Int).
For example mpfr_sub_si becomes subi and mpfr_si_sub becomes isub.
- comparison functions which have _p appended loose it.
For example mpfr_less_p becomes less.
Instances
- Eq
-
- NaN /= NaN,
- Infinity = Infinity,
- -Infinity = -Infinity
- otherwise normal comparison
- Ord
-
- compare NaN _ = GT
- compare _ NaN = GT
- infinity < _ = False
- -infinity > _ = False
- NaN [<,>,>=,<=] _ = False
This mimics the behaviour of built in Haskell Float and Double.
If you need instances of numeric typeclasses import one of the
Data.Number.MPFR.Instances.* modules.
|
|
| Synopsis |
|
| | | data MPFR | | | data Precision | | | type Exp = Int32 | | | type MpSize = Int32 | | | set :: RoundMode -> Precision -> MPFR -> MPFR | | | set_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | fromWord :: RoundMode -> Precision -> Word -> MPFR | | | fromInt :: RoundMode -> Precision -> Int -> MPFR | | | fromDouble :: RoundMode -> Precision -> Double -> MPFR | | | fromWord_ :: RoundMode -> Precision -> Word -> (MPFR, Int) | | | fromInt_ :: RoundMode -> Precision -> Int -> (MPFR, Int) | | | fromDouble_ :: RoundMode -> Precision -> Double -> (MPFR, Int) | | | int2w :: RoundMode -> Precision -> Word -> Int -> MPFR | | | int2i :: RoundMode -> Precision -> Int -> Int -> MPFR | | | int2w_ :: RoundMode -> Precision -> Word -> Int -> (MPFR, Int) | | | int2i_ :: RoundMode -> Precision -> Int -> Int -> (MPFR, Int) | | | stringToMPFR :: RoundMode -> Precision -> Word -> String -> MPFR | | | stringToMPFR_ :: RoundMode -> Precision -> Word -> String -> (MPFR, Int) | | | strtofr :: RoundMode -> Precision -> Word -> String -> (MPFR, String) | | | strtofr_ :: RoundMode -> Precision -> Word -> String -> (MPFR, String, Int) | | | setInf :: Precision -> Int -> MPFR | | | setNaN :: Precision -> MPFR | | | fromIntegerA :: RoundMode -> Precision -> Integer -> MPFR | | | compose :: RoundMode -> Precision -> (Integer, Int) -> MPFR | | | fromString :: String -> Precision -> Word -> MPFR | | | toDouble :: RoundMode -> MPFR -> Double | | | toDouble2exp :: RoundMode -> MPFR -> (Double, Int) | | | toInt :: RoundMode -> MPFR -> Int | | | toWord :: RoundMode -> MPFR -> Word | | | mpfrToString :: RoundMode -> Word -> Word -> MPFR -> (String, Exp) | | | fitsULong :: RoundMode -> MPFR -> Bool | | | fitsSLong :: RoundMode -> MPFR -> Bool | | | fitsUInt :: RoundMode -> MPFR -> Bool | | | fitsSInt :: RoundMode -> MPFR -> Bool | | | fitsUShort :: RoundMode -> MPFR -> Bool | | | fitsSShort :: RoundMode -> MPFR -> Bool | | | decompose :: MPFR -> (Integer, Exp) | | | toStringExp :: Word -> MPFR -> String | | | toString :: Word -> MPFR -> String | | | add :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | addw :: RoundMode -> Precision -> MPFR -> Word -> MPFR | | | addi :: RoundMode -> Precision -> MPFR -> Int -> MPFR | | | addd :: RoundMode -> Precision -> MPFR -> Double -> MPFR | | | sub :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | subw :: RoundMode -> Precision -> MPFR -> Word -> MPFR | | | subi :: RoundMode -> Precision -> MPFR -> Int -> MPFR | | | subd :: RoundMode -> Precision -> MPFR -> Double -> MPFR | | | wsub :: RoundMode -> Precision -> Word -> MPFR -> MPFR | | | isub :: RoundMode -> Precision -> Int -> MPFR -> MPFR | | | dsub :: RoundMode -> Precision -> Double -> MPFR -> MPFR | | | mul :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | mulw :: RoundMode -> Precision -> MPFR -> Word -> MPFR | | | muli :: RoundMode -> Precision -> MPFR -> Int -> MPFR | | | muld :: RoundMode -> Precision -> MPFR -> Double -> MPFR | | | sqr :: RoundMode -> Precision -> MPFR -> MPFR | | | div :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | divw :: RoundMode -> Precision -> MPFR -> Word -> MPFR | | | divi :: RoundMode -> Precision -> MPFR -> Int -> MPFR | | | divd :: RoundMode -> Precision -> MPFR -> Double -> MPFR | | | wdiv :: RoundMode -> Precision -> Word -> MPFR -> MPFR | | | idiv :: RoundMode -> Precision -> Int -> MPFR -> MPFR | | | ddiv :: RoundMode -> Precision -> Double -> MPFR -> MPFR | | | sqrt :: RoundMode -> Precision -> MPFR -> MPFR | | | sqrtw :: RoundMode -> Precision -> Word -> MPFR | | | recSqrt :: RoundMode -> Precision -> MPFR -> MPFR | | | cbrt :: RoundMode -> Precision -> MPFR -> MPFR | | | root :: RoundMode -> Precision -> MPFR -> Word -> MPFR | | | pow :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | poww :: RoundMode -> Precision -> MPFR -> Word -> MPFR | | | powi :: RoundMode -> Precision -> MPFR -> Int -> MPFR | | | wpoww :: RoundMode -> Precision -> Word -> Word -> MPFR | | | wpow :: RoundMode -> Precision -> Word -> MPFR -> MPFR | | | neg :: RoundMode -> Precision -> MPFR -> MPFR | | | absD :: RoundMode -> Precision -> MPFR -> MPFR | | | dim :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | mul2w :: RoundMode -> Precision -> MPFR -> Word -> MPFR | | | mul2i :: RoundMode -> Precision -> MPFR -> Int -> MPFR | | | div2w :: RoundMode -> Precision -> MPFR -> Word -> MPFR | | | div2i :: RoundMode -> Precision -> MPFR -> Int -> MPFR | | | add_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | addw_ :: RoundMode -> Precision -> MPFR -> Word -> (MPFR, Int) | | | addi_ :: RoundMode -> Precision -> MPFR -> Int -> (MPFR, Int) | | | addd_ :: RoundMode -> Precision -> MPFR -> Double -> (MPFR, Int) | | | sub_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | subw_ :: RoundMode -> Precision -> MPFR -> Word -> (MPFR, Int) | | | subi_ :: RoundMode -> Precision -> MPFR -> Int -> (MPFR, Int) | | | subd_ :: RoundMode -> Precision -> MPFR -> Double -> (MPFR, Int) | | | wsub_ :: RoundMode -> Precision -> Word -> MPFR -> (MPFR, Int) | | | isub_ :: RoundMode -> Precision -> Int -> MPFR -> (MPFR, Int) | | | dsub_ :: RoundMode -> Precision -> Double -> MPFR -> (MPFR, Int) | | | mul_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | mulw_ :: RoundMode -> Precision -> MPFR -> Word -> (MPFR, Int) | | | muli_ :: RoundMode -> Precision -> MPFR -> Int -> (MPFR, Int) | | | muld_ :: RoundMode -> Precision -> MPFR -> Double -> (MPFR, Int) | | | sqr_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | div_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | divw_ :: RoundMode -> Precision -> MPFR -> Word -> (MPFR, Int) | | | divi_ :: RoundMode -> Precision -> MPFR -> Int -> (MPFR, Int) | | | divd_ :: RoundMode -> Precision -> MPFR -> Double -> (MPFR, Int) | | | wdiv_ :: RoundMode -> Precision -> Word -> MPFR -> (MPFR, Int) | | | idiv_ :: RoundMode -> Precision -> Int -> MPFR -> (MPFR, Int) | | | ddiv_ :: RoundMode -> Precision -> Double -> MPFR -> (MPFR, Int) | | | sqrt_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | sqrtw_ :: RoundMode -> Precision -> Word -> (MPFR, Int) | | | recSqrt_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | cbrt_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | root_ :: RoundMode -> Precision -> MPFR -> Word -> (MPFR, Int) | | | pow_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | poww_ :: RoundMode -> Precision -> MPFR -> Word -> (MPFR, Int) | | | powi_ :: RoundMode -> Precision -> MPFR -> Int -> (MPFR, Int) | | | wpoww_ :: RoundMode -> Precision -> Word -> Word -> (MPFR, Int) | | | wpow_ :: RoundMode -> Precision -> Word -> MPFR -> (MPFR, Int) | | | neg_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | absD_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | dim_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | mul2w_ :: RoundMode -> Precision -> MPFR -> Word -> (MPFR, Int) | | | mul2i_ :: RoundMode -> Precision -> MPFR -> Int -> (MPFR, Int) | | | div2w_ :: RoundMode -> Precision -> MPFR -> Word -> (MPFR, Int) | | | div2i_ :: RoundMode -> Precision -> MPFR -> Int -> (MPFR, Int) | | | cmp :: MPFR -> MPFR -> Maybe Ordering | | | cmpw :: MPFR -> Word -> Maybe Ordering | | | cmpi :: MPFR -> Int -> Maybe Ordering | | | cmpd :: MPFR -> Double -> Maybe Ordering | | | cmp2w :: MPFR -> Word -> Exp -> Maybe Ordering | | | cmp2i :: MPFR -> Int -> Exp -> Maybe Ordering | | | cmpabs :: MPFR -> MPFR -> Maybe Ordering | | | isNaN :: MPFR -> Bool | | | isInfinite :: MPFR -> Bool | | | isNumber :: MPFR -> Bool | | | isZero :: MPFR -> Bool | | | sgn :: MPFR -> Maybe Int | | | greater :: MPFR -> MPFR -> Bool | | | greatereq :: MPFR -> MPFR -> Bool | | | less :: MPFR -> MPFR -> Bool | | | lesseq :: MPFR -> MPFR -> Bool | | | lessgreater :: MPFR -> MPFR -> Maybe Bool | | | equal :: MPFR -> MPFR -> Bool | | | unordered :: MPFR -> MPFR -> Maybe Bool | | | log :: RoundMode -> Precision -> MPFR -> MPFR | | | log2 :: RoundMode -> Precision -> MPFR -> MPFR | | | log10 :: RoundMode -> Precision -> MPFR -> MPFR | | | exp :: RoundMode -> Precision -> MPFR -> MPFR | | | exp2 :: RoundMode -> Precision -> MPFR -> MPFR | | | exp10 :: RoundMode -> Precision -> MPFR -> MPFR | | | sin :: RoundMode -> Precision -> MPFR -> MPFR | | | cos :: RoundMode -> Precision -> MPFR -> MPFR | | | tan :: RoundMode -> Precision -> MPFR -> MPFR | | | sec :: RoundMode -> Precision -> MPFR -> MPFR | | | csc :: RoundMode -> Precision -> MPFR -> MPFR | | | cot :: RoundMode -> Precision -> MPFR -> MPFR | | | sincos :: RoundMode -> Precision -> Precision -> MPFR -> (MPFR, MPFR) | | | asin :: RoundMode -> Precision -> MPFR -> MPFR | | | acos :: RoundMode -> Precision -> MPFR -> MPFR | | | atan :: RoundMode -> Precision -> MPFR -> MPFR | | | atan2 :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | sinh :: RoundMode -> Precision -> MPFR -> MPFR | | | cosh :: RoundMode -> Precision -> MPFR -> MPFR | | | tanh :: RoundMode -> Precision -> MPFR -> MPFR | | | sinhcosh :: RoundMode -> Precision -> Precision -> MPFR -> (MPFR, MPFR) | | | sech :: RoundMode -> Precision -> MPFR -> MPFR | | | csch :: RoundMode -> Precision -> MPFR -> MPFR | | | coth :: RoundMode -> Precision -> MPFR -> MPFR | | | acosh :: RoundMode -> Precision -> MPFR -> MPFR | | | asinh :: RoundMode -> Precision -> MPFR -> MPFR | | | atanh :: RoundMode -> Precision -> MPFR -> MPFR | | | facw :: RoundMode -> Precision -> Word -> MPFR | | | log1p :: RoundMode -> Precision -> MPFR -> MPFR | | | expm1 :: RoundMode -> Precision -> MPFR -> MPFR | | | eint :: RoundMode -> Precision -> MPFR -> MPFR | | | li2 :: RoundMode -> Precision -> MPFR -> MPFR | | | gamma :: RoundMode -> Precision -> MPFR -> MPFR | | | lngamma :: RoundMode -> Precision -> MPFR -> MPFR | | | lgamma :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | zeta :: RoundMode -> Precision -> MPFR -> MPFR | | | zetaw :: RoundMode -> Precision -> Word -> MPFR | | | erf :: RoundMode -> Precision -> MPFR -> MPFR | | | erfc :: RoundMode -> Precision -> MPFR -> MPFR | | | j0 :: RoundMode -> Precision -> MPFR -> MPFR | | | j1 :: RoundMode -> Precision -> MPFR -> MPFR | | | jn :: RoundMode -> Precision -> Int -> MPFR -> MPFR | | | y0 :: RoundMode -> Precision -> MPFR -> MPFR | | | y1 :: RoundMode -> Precision -> MPFR -> MPFR | | | yn :: RoundMode -> Precision -> Int -> MPFR -> MPFR | | | fma :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR -> MPFR | | | fms :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR -> MPFR | | | agm :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | hypot :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | pi :: RoundMode -> Precision -> MPFR | | | log2c :: RoundMode -> Precision -> MPFR | | | euler :: RoundMode -> Precision -> MPFR | | | catalan :: RoundMode -> Precision -> MPFR | | | log_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | log2_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | log10_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | exp_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | exp2_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | exp10_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | sin_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | cos_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | tan_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | sec_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | csc_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | cot_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | sincos_ :: RoundMode -> Precision -> Precision -> MPFR -> (MPFR, MPFR, Int) | | | asin_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | acos_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | atan_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | atan2_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | sinh_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | cosh_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | tanh_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | sinhcosh_ :: RoundMode -> Precision -> Precision -> MPFR -> (MPFR, MPFR, Int) | | | sech_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | csch_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | coth_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | acosh_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | asinh_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | atanh_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | facw_ :: RoundMode -> Precision -> Word -> (MPFR, Int) | | | log1p_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | expm1_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | eint_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | li2_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | gamma_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | lngamma_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | lgamma_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int, Int) | | | zeta_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | zetaw_ :: RoundMode -> Precision -> Word -> (MPFR, Int) | | | erf_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | erfc_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | j0_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | j1_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | jn_ :: RoundMode -> Precision -> Int -> MPFR -> (MPFR, Int) | | | y0_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | y1_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | yn_ :: RoundMode -> Precision -> Int -> MPFR -> (MPFR, Int) | | | fma_ :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR -> (MPFR, Int) | | | fms_ :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR -> (MPFR, Int) | | | agm_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | hypot_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | pi_ :: RoundMode -> Precision -> (MPFR, Int) | | | log2c_ :: RoundMode -> Precision -> (MPFR, Int) | | | euler_ :: RoundMode -> Precision -> (MPFR, Int) | | | catalan_ :: RoundMode -> Precision -> (MPFR, Int) | | | freeCache :: IO () | | | rint :: RoundMode -> Precision -> MPFR -> MPFR | | | ceil :: Precision -> MPFR -> MPFR | | | floor :: Precision -> MPFR -> MPFR | | | round :: Precision -> MPFR -> MPFR | | | trunc :: Precision -> MPFR -> MPFR | | | rintCeil :: RoundMode -> Precision -> MPFR -> MPFR | | | rintFloor :: RoundMode -> Precision -> MPFR -> MPFR | | | rintRound :: RoundMode -> Precision -> MPFR -> MPFR | | | rintTrunc :: RoundMode -> Precision -> MPFR -> MPFR | | | modf :: RoundMode -> Precision -> Precision -> MPFR -> (MPFR, MPFR) | | | frac :: RoundMode -> Precision -> MPFR -> MPFR | | | fmod :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | remainder :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | remquo :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | rint_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | ceil_ :: Precision -> MPFR -> (MPFR, Int) | | | floor_ :: Precision -> MPFR -> (MPFR, Int) | | | round_ :: Precision -> MPFR -> (MPFR, Int) | | | trunc_ :: Precision -> MPFR -> (MPFR, Int) | | | rintCeil_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | rintFloor_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | rintRound_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | rintTrunc_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | modf_ :: RoundMode -> Precision -> Precision -> MPFR -> (MPFR, MPFR, Int) | | | frac_ :: RoundMode -> Precision -> MPFR -> (MPFR, Int) | | | fmod_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | remainder_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | remquo_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int, Int) | | | isInteger :: MPFR -> Bool | | | nextToward :: MPFR -> MPFR -> MPFR | | | nextAbove :: MPFR -> MPFR | | | nextBelow :: MPFR -> MPFR | | | maxD :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | minD :: RoundMode -> Precision -> MPFR -> MPFR -> MPFR | | | random2 :: Precision -> MpSize -> Exp -> IO MPFR | | | getExp :: MPFR -> Exp | | | setExp :: MPFR -> Exp -> MPFR | | | signbit :: MPFR -> Bool | | | maxD_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | minD_ :: RoundMode -> Precision -> MPFR -> MPFR -> (MPFR, Int) | | | getPrec :: MPFR -> Precision | | | getMantissa :: MPFR -> Integer | | | one :: MPFR | | | zero :: MPFR | | | maxPrec :: MPFR -> MPFR -> Precision |
|
|
| Documentation |
|
|
| Constructors | | Instances | |
|
|
|
Instances | |
|
|
|
Instances | |
|
|
|
|
|
|
| Assignment functions
|
|
| See http://www.mpfr.org/mpfr-current/mpfr.html#Assignment-Functions
documentation on particular functions.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| x * 2 ^ y
|
|
|
| x * 2 ^ y
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| stringToMPFR with default rounding to Near.
|
|
| Conversion functions
|
|
| See http://www.mpfr.org/mpfr-current/mpfr.html#Conversion-Functions
documentation on particular functions.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| :: Word | number of digits
| | -> MPFR | | | -> String | | | Output a string in base 10 rounded to Near in exponential form.
|
|
|
|
| Output a string in base 10 rounded to Near. The difference from toStringExp is that
it won't output in exponential form if it is sensible to do so.
|
|
| Basic arithmetic functions
|
|
| For documentation on particular functions see
http://www.mpfr.org/mpfr-current/mpfr.html#Basic-Arithmetic-Functions.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Comparison functions
|
|
| For documentation on particular functions see
http://www.mpfr.org/mpfr-current/mpfr.html#Comparison-Functions
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Special functions
|
|
| For documentation on particular functions see
http://www.mpfr.org/mpfr-current/mpfr.html#Special-Functions.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Integer related functions
|
|
| For documentation on particular functions see
http://www.mpfr.org/mpfr-chttp://www.mpfr.org/mpfr-current/mpfr.html#Integer-Related-Functions
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Miscellaneous functions
|
|
| For documentation on particular functions see
http://www.mpfr.org/mpfr-current/mpfr.html#Miscellaneous-Functions.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
getMantissa and getExp return values such that
d = getMantissa d * 2^(getExp d - ceiling ((getPrec d) / bitsPerMPLimb)* bitsPerMPLimb )
In case of 0, NaN or +-Inf getMantissa will return 0
|
|
|
|
|
|
|
|
| Produced by Haddock version 2.4.2 |