libBF-0.6.2: A binding to the libBF library.
Safe HaskellNone
LanguageHaskell2010

LibBF.Mutable

Description

Mutable big-float computation.

Synopsis

Allocation

newContext :: IO BFContext Source #

Allocate a new numeric context.

data BFContext Source #

State of the current computation context.

new :: BFContext -> IO BF Source #

Allocate a new number. Starts off as zero.

data BF Source #

A mutable high precision floating point number.

Assignment

setNaN :: BF -> IO () Source #

Assign NaN to the number.

setZero :: Sign -> BF -> IO () Source #

Assign a zero to the number.

setInf :: Sign -> BF -> IO () Source #

Assign an infinty to the number.

data Sign Source #

Indicates if a number is positive or negative.

Constructors

Neg

Negative

Pos

Positive

Instances

Instances details
Eq Sign Source # 
Instance details

Defined in LibBF.Mutable

Methods

(==) :: Sign -> Sign -> Bool #

(/=) :: Sign -> Sign -> Bool #

Ord Sign Source # 
Instance details

Defined in LibBF.Mutable

Methods

compare :: Sign -> Sign -> Ordering #

(<) :: Sign -> Sign -> Bool #

(<=) :: Sign -> Sign -> Bool #

(>) :: Sign -> Sign -> Bool #

(>=) :: Sign -> Sign -> Bool #

max :: Sign -> Sign -> Sign #

min :: Sign -> Sign -> Sign #

Show Sign Source # 
Instance details

Defined in LibBF.Mutable

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

setWord :: Word64 -> BF -> IO () Source #

Assign from a word

setInt :: Int64 -> BF -> IO () Source #

Assign from an int

setDouble :: Double -> BF -> IO () Source #

Assign from a double

setInteger :: Integer -> BF -> IO () Source #

Set an integer. If the integer is larger than the primitive types, this does repreated Int64 additions and multiplications.

setBF Source #

Arguments

:: BF 
-> BF

This number is changed

-> IO () 

Assign from another number.

setString :: Int -> BFOpts -> String -> BF -> IO (Status, Int, Bool) Source #

Set the value to the float parsed out of the given string. * The radix should not exceed maxRadix. * Sets the number to NaN on failure. * Assumes that characters are encoded with a single byte each. * Retruns: - Status for the conversion - How many bytes we consumed - Did we consume the whole input

Queries and Comparisons

cmpEq :: BF -> BF -> IO Bool Source #

Check if the two numbers are equal.

cmpLT :: BF -> BF -> IO Bool Source #

Check if the first number is strictly less than the second.

cmpLEQ :: BF -> BF -> IO Bool Source #

Check if the first number is less than, or equal to, the second.

cmpAbs :: BF -> BF -> IO Ordering Source #

Compare the absolute values of the two numbers. See also cmp.

cmp :: BF -> BF -> IO Ordering Source #

Compare the two numbers. The special values are ordered like this:

  • -0 < 0
  • NaN == NaN
  • NaN is larger than all other numbers

getSign :: BF -> IO (Maybe Sign) Source #

Returns Nothing for NaN.

getExp :: BF -> IO (Maybe Int64) Source #

Get the exponent of the number. Returns Nothing for inifinity, zero and NaN.

isFinite :: BF -> IO Bool Source #

Check if the number is "normal", i.e. (not infinite or NaN)

isInf :: BF -> IO Bool Source #

Check if the given numer is infinite.

isNaN :: BF -> IO Bool Source #

Check if the number is NaN

isZero :: BF -> IO Bool Source #

Check if the given number is a zero.

Arithmetic

fneg :: BF -> IO () Source #

Negate the number.

fadd :: BFOpts -> BF -> BF -> BF -> IO Status Source #

Add two numbers, using the given settings, and store the result in the last.

faddInt :: BFOpts -> BF -> Int64 -> BF -> IO Status Source #

Add a number and an int64 and store the result in the last.

fsub :: BFOpts -> BF -> BF -> BF -> IO Status Source #

Subtract two numbers, using the given settings, and store the result in the last.

fmul :: BFOpts -> BF -> BF -> BF -> IO Status Source #

Multiply two numbers, using the given settings, and store the result in the last.

fmulInt :: BFOpts -> BF -> Int64 -> BF -> IO Status Source #

Multiply the number by the given int, and store the result in the second number.

fmulWord :: BFOpts -> BF -> Word64 -> BF -> IO Status Source #

Multiply the number by the given word, and store the result in the second number.

fmul2Exp :: BFOpts -> Int64 -> BF -> IO Status Source #

Multiply the number by 2^e.

ffma :: BFOpts -> BF -> BF -> BF -> BF -> IO Status Source #

Compute the fused-multiply-add. ffma opts x y z r computes r := (x*y)+z.

fdiv :: BFOpts -> BF -> BF -> BF -> IO Status Source #

Divide two numbers, using the given settings, and store the result in the last.

frem :: BFOpts -> BF -> BF -> BF -> IO Status Source #

Compute the remainder x - y * n where n is the integer nearest to x/y (with ties broken to even values of n). Output is written into the final argument.

fsqrt :: BFOpts -> BF -> BF -> IO Status Source #

Compute the square root of the first number and store the result in the second.

fpow :: BFOpts -> BF -> BF -> BF -> IO Status Source #

Exponentiate the first number by the second, and store the result in the third number.

fround :: BFOpts -> BF -> IO Status Source #

Round to the nearest float matching the configuration parameters.

frint :: RoundMode -> BF -> IO Status Source #

Round to the neareset integer.

Convert from a number

toDouble :: RoundMode -> BF -> IO (Double, Status) Source #

Get the current value of a BF as a Haskell Double.

toString :: Int -> ShowFmt -> BF -> IO String Source #

Render a big-float as a Haskell string. The radix should not exceed maxRadix.

toRep :: BF -> IO BFRep Source #

Get the representation of the number.

data BFRep Source #

An explicit representation for big nums.

Constructors

BFRep !Sign !BFNum

A signed number

BFNaN

Not a number

Instances

Instances details
Eq BFRep Source # 
Instance details

Defined in LibBF.Mutable

Methods

(==) :: BFRep -> BFRep -> Bool #

(/=) :: BFRep -> BFRep -> Bool #

Ord BFRep Source # 
Instance details

Defined in LibBF.Mutable

Methods

compare :: BFRep -> BFRep -> Ordering #

(<) :: BFRep -> BFRep -> Bool #

(<=) :: BFRep -> BFRep -> Bool #

(>) :: BFRep -> BFRep -> Bool #

(>=) :: BFRep -> BFRep -> Bool #

max :: BFRep -> BFRep -> BFRep #

min :: BFRep -> BFRep -> BFRep #

Show BFRep Source # 
Instance details

Defined in LibBF.Mutable

Methods

showsPrec :: Int -> BFRep -> ShowS #

show :: BFRep -> String #

showList :: [BFRep] -> ShowS #

Hashable BFRep Source # 
Instance details

Defined in LibBF.Mutable

Methods

hashWithSalt :: Int -> BFRep -> Int #

hash :: BFRep -> Int #

data BFNum Source #

Representations for unsigned floating point numbers.

Constructors

Zero

zero

Num Integer !Int64
x * 2 ^ y
Inf

infinity

Instances

Instances details
Eq BFNum Source # 
Instance details

Defined in LibBF.Mutable

Methods

(==) :: BFNum -> BFNum -> Bool #

(/=) :: BFNum -> BFNum -> Bool #

Ord BFNum Source # 
Instance details

Defined in LibBF.Mutable

Methods

compare :: BFNum -> BFNum -> Ordering #

(<) :: BFNum -> BFNum -> Bool #

(<=) :: BFNum -> BFNum -> Bool #

(>) :: BFNum -> BFNum -> Bool #

(>=) :: BFNum -> BFNum -> Bool #

max :: BFNum -> BFNum -> BFNum #

min :: BFNum -> BFNum -> BFNum #

Show BFNum Source # 
Instance details

Defined in LibBF.Mutable

Methods

showsPrec :: Int -> BFNum -> ShowS #

show :: BFNum -> String #

showList :: [BFNum] -> ShowS #

Hashable BFNum Source # 
Instance details

Defined in LibBF.Mutable

Methods

hashWithSalt :: Int -> BFNum -> Int #

hash :: BFNum -> Int #

Configuration

module LibBF.Opts

toChunks :: Integer -> [LimbT] Source #

Chunk a non-negative integer into words, least significatn first