Copyright | (c) Levent Erkok |
---|---|
License | BSD3 |
Maintainer | erkokl@gmail.com |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
Reading/Writing hexadecimal floating-point numbers.
See: http://www.open-std.org/jtc1/sc22/wg14/www/docs/n1256.pdf, pages 57-58. We slightly diverge from the standard and do not allow for the "floating-suffix," as the type inference of Haskell makes this unnecessary.
Synopsis
- hf :: QuasiQuoter
- class RealFloat a => FloatingHexReader a where
- readHFloat :: String -> Maybe a
- showHFloat :: RealFloat a => a -> ShowS
QuasiQuoting
hf :: QuasiQuoter Source #
A quasiquoter for hexadecimal floating-point literals. See: http://www.open-std.org/jtc1/sc22/wg14/www/docs/n1256.pdf, pages 57-58. We slightly diverge from the standard and do not allow for the "floating-suffix," as the type inference of Haskell makes this unnecessary.
Example:
{-# LANGUAGE QuasiQuotes #-} import Data.Numbers.FloatingHex f :: Double f = [hf|0x1.f44abd5aa7ca4p+25|]
With these definitions, f
will be equal to the number 6.5574266708245546e7
Reading hex-floats
class RealFloat a => FloatingHexReader a where Source #
Due to intricacies of conversion between
Float
and Double
types (see http://ghc.haskell.org/trac/ghc/ticket/3676), we explicitly introduce
a class to do the reading properly.
readHFloat :: String -> Maybe a Source #
Convert a hex-float from a string, if possible.
Instances
FloatingHexReader Double Source # | The Double instance |
Defined in Data.Numbers.FloatingHex | |
FloatingHexReader Float Source # | The Float instance |
Defined in Data.Numbers.FloatingHex |
Showing hex-floats
showHFloat :: RealFloat a => a -> ShowS Source #
Show a floating-point value in the hexadecimal format, similar to the %a
specifier in C's printf.
>>>
showHFloat (212.21 :: Double) ""
"0x1.a86b851eb851fp7">>>
showHFloat (-12.76 :: Float) ""
"-0x1.9851ecp3">>>
showHFloat (-0 :: Double) ""
"-0x0p+0"