Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
LibBF.Mutable
Description
Mutable big-float computation.
Synopsis
- newContext :: IO BFContext
- data BFContext
- new :: BFContext -> IO BF
- data BF
- setNaN :: BF -> IO ()
- setZero :: Sign -> BF -> IO ()
- setInf :: Sign -> BF -> IO ()
- data Sign
- setWord :: Word64 -> BF -> IO ()
- setInt :: Int64 -> BF -> IO ()
- setDouble :: Double -> BF -> IO ()
- setInteger :: Integer -> BF -> IO ()
- setBF :: BF -> BF -> IO ()
- setString :: Int -> BFOpts -> String -> BF -> IO (Status, Int, Bool)
- cmpEq :: BF -> BF -> IO Bool
- cmpLT :: BF -> BF -> IO Bool
- cmpLEQ :: BF -> BF -> IO Bool
- cmpAbs :: BF -> BF -> IO Ordering
- cmp :: BF -> BF -> IO Ordering
- getSign :: BF -> IO (Maybe Sign)
- getExp :: BF -> IO (Maybe Int64)
- isFinite :: BF -> IO Bool
- isInf :: BF -> IO Bool
- isNaN :: BF -> IO Bool
- isZero :: BF -> IO Bool
- fneg :: BF -> IO ()
- fadd :: BFOpts -> BF -> BF -> BF -> IO Status
- faddInt :: BFOpts -> BF -> Int64 -> BF -> IO Status
- fsub :: BFOpts -> BF -> BF -> BF -> IO Status
- fmul :: BFOpts -> BF -> BF -> BF -> IO Status
- fmulInt :: BFOpts -> BF -> Int64 -> BF -> IO Status
- fmulWord :: BFOpts -> BF -> Word64 -> BF -> IO Status
- fmul2Exp :: BFOpts -> Int -> BF -> IO Status
- ffma :: BFOpts -> BF -> BF -> BF -> BF -> IO Status
- fdiv :: BFOpts -> BF -> BF -> BF -> IO Status
- frem :: BFOpts -> BF -> BF -> BF -> IO Status
- fsqrt :: BFOpts -> BF -> BF -> IO Status
- fpow :: BFOpts -> BF -> BF -> BF -> IO Status
- fround :: BFOpts -> BF -> IO Status
- frint :: RoundMode -> BF -> IO Status
- toDouble :: RoundMode -> BF -> IO (Double, Status)
- toString :: Int -> ShowFmt -> BF -> IO String
- toRep :: BF -> IO BFRep
- data BFRep
- data BFNum
- module LibBF.Opts
- toChunks :: Integer -> [LimbT]
Allocation
newContext :: IO BFContext Source #
Allocate a new numeric context.
Assignment
Indicates if a number is positive or negative.
Instances
Data Sign Source # | |
Defined in LibBF.Mutable Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sign -> c Sign # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sign # dataTypeOf :: Sign -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Sign) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sign) # gmapT :: (forall b. Data b => b -> b) -> Sign -> Sign # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r # gmapQ :: (forall d. Data d => d -> u) -> Sign -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sign -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sign -> m Sign # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign # | |
Show Sign Source # | |
Eq Sign Source # | |
Ord Sign Source # | |
setInteger :: Integer -> BF -> IO () Source #
Set an integer. If the integer is larger than the primitive types, this does repreated Int64 additions and multiplications.
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
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
getExp :: BF -> IO (Maybe Int64) Source #
Get the exponent of the number.
Returns Nothing
for inifinity, zero and NaN.
Arithmetic
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.
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.
Convert from a number
toString :: Int -> ShowFmt -> BF -> IO String Source #
Render a big-float as a Haskell string.
The radix should not exceed maxRadix
.
An explicit representation for big nums.
Instances
Data BFRep Source # | |
Defined in LibBF.Mutable Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BFRep -> c BFRep # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BFRep # dataTypeOf :: BFRep -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BFRep) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BFRep) # gmapT :: (forall b. Data b => b -> b) -> BFRep -> BFRep # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BFRep -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BFRep -> r # gmapQ :: (forall d. Data d => d -> u) -> BFRep -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BFRep -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BFRep -> m BFRep # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BFRep -> m BFRep # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BFRep -> m BFRep # | |
Show BFRep Source # | |
Eq BFRep Source # | |
Ord BFRep Source # | |
Hashable BFRep Source # | |
Defined in LibBF.Mutable |
Representations for unsigned floating point numbers.
Instances
Data BFNum Source # | |
Defined in LibBF.Mutable Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BFNum -> c BFNum # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BFNum # dataTypeOf :: BFNum -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BFNum) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BFNum) # gmapT :: (forall b. Data b => b -> b) -> BFNum -> BFNum # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BFNum -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BFNum -> r # gmapQ :: (forall d. Data d => d -> u) -> BFNum -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BFNum -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BFNum -> m BFNum # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BFNum -> m BFNum # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BFNum -> m BFNum # | |
Show BFNum Source # | |
Eq BFNum Source # | |
Ord BFNum Source # | |
Hashable BFNum Source # | |
Defined in LibBF.Mutable |
Configuration
module LibBF.Opts