[Haskell-cafe] Number formatting
Stephen Tetley
stephen.tetley at gmail.com
Mon Feb 8 09:16:35 EST 2010
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 <stephen.tetley at gmail.com> wrote:
> Ahem...
>
> *FormatDecimal> formatDecimal (888.005)
> ",888.01"
>
> I'll post a revision shortly (that handles negatives as well) ...
>
More information about the Haskell-Cafe
mailing list