
Hello, is there a function which will format a number with separators, something that will turn 14509.8674 into 14,509.86? Günther

Günther Schmidt wrote:
is there a function which will format a number with separators, something that will turn 14509.8674 into 14,509.86?
There's a small function to do it here: http://bluebones.net/2007/02/formatting-decimals-in-haskell/

Hello All
Alternatively, less dependencies and a bit less golf (but not much testing...):
Best wishes
Stephen
import Data.List
import Numeric
formatDecimal :: RealFloat a => a -> String
formatDecimal d = let s = showFFloat (Just 2) d ""
(a,b) = break (=='.') s
in (intersperseN 3 ',' a) ++ b
intersperseN :: Int -> a -> [a] -> [a]
intersperseN n a = snd . para phi (1,[]) where
phi x ((_:_), (i,acc)) | i == n = (1, a : x : acc)
phi x (_, (i,acc)) = (i+1, x : acc)
-- paramorphism (generalizes fold)
para :: (a -> ([a], b) -> b) -> b -> [a] -> b
para phi b = step
where step [] = b
step (x:xs) = phi x (xs, step xs)
On 8 February 2010 11:17, Anton van Straaten
There's a small function to do it here:
http://bluebones.net/2007/02/formatting-decimals-in-haskell/

Hi Günther
Ahem...
*FormatDecimal> formatDecimal (888.005)
",888.01"
I'll post a revision shortly (that handles negatives as well) ...
On 8 February 2010 13:09, Stephen Tetley
Hello All
Alternatively, less dependencies and a bit less golf (but not much testing...): ^^^^^^^^^^^^^^^^^^^^

Hello
I'd overlooked that the left-to-right behaviour of the paramorphism
when I needed to go right-to-left, here's a version with a rather
horrible right fold (different seeds for the counter, ho-hum, but
easily testable):
import Data.List
import Numeric
formatDecimal :: RealFloat a => a -> String
formatDecimal d | d < 0 = '-' : fmt (negate d)
| otherwise = fmt d
where
fmt x = let s = showFFloat (Just 2) x ""
(a,b) = break (=='.') s
in (intersperseN_rl 3 ',' a) ++ b
intersperseN_rl :: Int -> a -> [a] -> [a]
intersperseN_rl n sep xs = snd $ foldr phi (0,[]) xs where
phi a (i,acc) | i == n = (1, a : sep : acc)
| otherwise = (i+1, a : acc)
test01 :: IO ()
test01 = mapM_ (print . (intersperseN_rl 3 ',')) $ inits "abcdefghijklmno"
*FormatDecimal> test01
""
"a"
"ab"
"abc"
"a,bcd"
"ab,cde"
"abc,def"
"a,bcd,efg"
"ab,cde,fgh"
"abc,def,ghi"
"a,bcd,efg,hij"
"ab,cde,fgh,ijk"
"abc,def,ghi,jkl"
"a,bcd,efg,hij,klm"
"ab,cde,fgh,ijk,lmn"
"abc,def,ghi,jkl,mno"
On 8 February 2010 13:40, Stephen Tetley
Ahem...
*FormatDecimal> formatDecimal (888.005) ",888.01"
I'll post a revision shortly (that handles negatives as well) ...
participants (3)
-
Anton van Straaten
-
Günther Schmidt
-
Stephen Tetley