module Text.FShow.RealFloat
( FShow(..)
, fshows
, DispFloat(..)
, fshowFloat
, fshowEFloat
, fshowFFloat
, fshowGFloat
, Double7(..)
, Float7(..)
) where
import GHC.Show
import GHC.Float (showSignedFloat)
import Text.FShow.RealFloat.Internals
class (RealFloat a) => DispFloat a where
decDigits :: a -> Int
decDigits x = 2 + (8651*(floatDigits x)) `quot` 28738
binExp :: a -> Int
binExp x = floatDigits x 1
instance DispFloat Double where
decDigits _ = 17
binExp _ = 52
instance DispFloat Float where
decDigits _ = 9
binExp _ = 23
newtype Double7 = D7 Double
deriving (Eq, Ord, Num, Fractional, Real, RealFrac, Floating, RealFloat)
instance DispFloat Double7 where
decDigits _ = 7
binExp _ = 52
instance Show Double7 where
showsPrec p = showSignedFloat fshowFloat p
instance FShow Double7 where
fshowsPrec p = showSignedFloat fshowFloat p
fshowList = showList__ (fshowsPrec 0)
newtype Float7 = F7 Float
deriving (Eq, Ord, Num, Fractional, Real, RealFrac, Floating, RealFloat)
instance DispFloat Float7 where
decDigits _ = 7
binExp _ = 23
instance Show Float7 where
showsPrec p = showSignedFloat fshowFloat p
instance FShow Float7 where
fshowsPrec p = showSignedFloat fshowFloat p
fshowList = showList__ (fshowsPrec 0)
class FShow a where
fshow :: a -> String
fshowsPrec :: Int -> a -> ShowS
fshowList :: [a] -> ShowS
fshow x = fshowsPrec 0 x ""
fshowsPrec _ x s = fshow x ++ s
fshowList xs s = showList__ fshows xs s
fshows :: FShow a => a -> ShowS
fshows x = showString (fshow x)
instance FShow Double where
fshowsPrec p = showSignedFloat fshowFloat p
fshowList = showList__ (fshowsPrec 0)
instance FShow Float where
fshowsPrec p = showSignedFloat fshowFloat p
fshowList = showList__ (fshowsPrec 0)
instance (FShow a) => FShow [a] where
fshowsPrec _ = fshowList
fshowFloat :: (DispFloat a) => a -> ShowS
fshowFloat x = showString (formatFloat FFGeneric Nothing x)
fshowEFloat :: (DispFloat a) => Maybe Int -> a -> ShowS
fshowEFloat d x = showString (formatFloat FFExponent d x)
fshowFFloat :: (DispFloat a) => Maybe Int -> a -> ShowS
fshowFFloat d x = showString (formatFloat FFFixed d x)
fshowGFloat :: (DispFloat a) => Maybe Int -> a -> ShowS
fshowGFloat d x = showString (formatFloat FFGeneric d x)
data FFFormat = FFExponent | FFFixed | FFGeneric
formatFloat :: DispFloat a => FFFormat -> Maybe Int -> a -> String
formatFloat fmt decs x
| isNaN x = "NaN"
| isInfinite x = if x < 0 then "-Infinity" else "Infinity"
| x < 0 || isNegativeZero x = '-':doFmt fmt (fltDigs (x))
| otherwise = doFmt fmt (fltDigs x)
where
fltDigs 0 = ([0],0)
fltDigs y = uncurry (posToDigits (decDigits y) (binExp y)) (decodeFloat y)
fluff :: [Int] -> [Int]
fluff [] = [0]
fluff xs = xs
doFmt format (is, e) =
case format of
FFGeneric ->
doFmt (if e < 0 || e > 7 then FFExponent else FFFixed) (is,e)
FFExponent ->
case decs of
Nothing ->
let show_e' = if ei == 0 then show (e1) else show e
(ei,(d:ds)) = roundToS (decDigits x) is
in case is of
[0] -> "0.0e0"
_ -> i2D d : '.' : map i2D (fluff ds) ++ ('e' : show_e')
Just dec ->
let dec' = max dec 1 in
case is of
[0] -> '0' :'.' : take dec' (repeat '0') ++ "e0"
_ -> let (ei,is') = roundTo (dec'+1) is
(d:ds') = map i2D (if ei > 0 then init is' else is')
in d:'.':ds' ++ 'e':show (e1+ei)
FFFixed ->
let mk0 ls = case ls of { "" -> "0" ; _ -> ls} in
case decs of
Nothing ->
let (ei, is') = roundToS (decDigits x) is
e' = e+ei
ds = map i2D is'
in case is of
[0] -> "0.0"
_ | e' <= 0 -> "0." ++ replicate (e') '0' ++ map i2D is'
| otherwise ->
let f 0 s rs = mk0 (reverse s) ++ '.':mk0 rs
f n s "" = f (n1) ('0':s) ""
f n s (r:rs) = f (n1) (r:s) rs
in f e' "" ds
Just dec ->
let dec' = max dec 0 in
if e >= 0 then
let (ei,is') = roundTo (dec' + e) is
(ls,rs) = splitAt (e+ei) (map i2D is')
in mk0 ls ++ (if null rs then "" else '.':rs)
else
let (ei,is') = roundTo dec' (replicate (e) 0 ++ is)
d:ds' = map i2D (if ei > 0 then is' else 0:is')
in d : (if null ds' then "" else '.':ds')
roundToS :: Int -> [Int] -> (Int,[Int])
roundToS d is =
case f d is of
x@(0,_) -> x
(1,xs) -> (1, 1:xs)
_ -> error "roundToS: bad Value"
where
f _ [] = (0, [])
f 0 (x:_) = (if x >= 5 then 1 else 0, [])
f n (i:xs)
| i' == 10 = (1,prep 0 ds)
| otherwise = (0,prep i' ds)
where
prep 0 [] = []
prep a bs = a:bs
(c,ds) = f (n1) xs
i' = c + i
roundTo :: Int -> [Int] -> (Int,[Int])
roundTo d is =
case f d is of
x@(0,_) -> x
(1,xs) -> (1, 1:xs)
_ -> error "roundTo: bad Value"
where
f n [] = (0, replicate n 0)
f 0 (x:_) = (if x >= 5 then 1 else 0, [])
f n (i:xs)
| i' == 10 = (1,0:ds)
| otherwise = (0,i':ds)
where
(c,ds) = f (n1) xs
i' = c + i