
Faster version:
instance (Integral a, PrintfArg a) => PrintfArg (Ratio a) where
formatArg x f@(FieldFormat w p a s l _ c) = if elem c "gGv"
then let
d = " % " ++ formatArg (denominator x) (FieldFormat Nothing
Nothing Nothing s l "" 'd') ""
(w',a') = case a of
Just LeftAdjust -> (Nothing, Nothing)
_ -> (fmap (subtract (length d)) w, a)
n = formatArg (numerator x) (f {fmtWidth = w', fmtAdjust = a',
fmtChar = 'd'}) ""
in formatArg (n ++ d) (f {fmtPrecision = Nothing, fmtChar =
's'})
else if elem c "doxXb"
then formatArg (round x :: Integer) f
else case p of
Nothing -> error "Text.Printf.formatArg: precision not
given"
Just p' -> if p' <= 0
then formatArg x (f {fmtPrecision = Nothing, fmtChar =
'd'})
else if elem c "fF"
then let
n = truncate x
sig = '.' : formatArg (round ((x - fromInteger
n) * 10^p') :: Integer) (FieldFormat Nothing Nothing Nothing Nothing False
"" 'd') ""
(w',a') = case a of
Just LeftAdjust -> (Nothing, Nothing)
_ -> (fmap (subtract (length sig)) w, a)
b = formatArg n (FieldFormat w' Nothing a' s l
"" 'd') ""
in formatArg (b ++ sig) (f {fmtPrecision =
Nothing, fmtChar = 's'})
else if elem c "eE"
then let
(q,e) = log10 x
sig = c : show e
(w',a') = case a of
Just LeftAdjust -> (Nothing, Nothing)
_ -> (fmap (subtract (length sig)) w, a)
fp = formatArg q (f {fmtWidth = w',
fmtAdjust = a', fmtChar = 'f'}) ""
in formatArg (fp ++ sig) (f {fmtPrecision =
Nothing, fmtChar = 's'})
else error "Text.Printf.formatArg: bad format
character"
where
goF _ 0 = ""
goF x p = case compare x 0 of
LT -> '-' : goF (negate x) p
EQ -> "0"
GT -> if 1 == p
then show (round (10 * x) :: Integer)
else let
x10 = 10 * x
n = truncate x10
in show n ++ goF (x10 - fromIntegral n) (p - 1)
log10 x
| x < 1 = let
(q,e) = log10 (x * 10)
in (q, e - 1)
| 10 <= x = let
(q,e) = log10 (x / 10)
in (q, e + 1)
| otherwise = (x, 0)
2020년 2월 8일 (토) 오전 8:40, Dannyu NDos
---------- Forwarded message --------- 보낸사람: Dannyu NDos
Date: 2020년 2월 8일 (토) 오전 8:22 Subject: Re: add instance PrintfArg Ratio To: Henning Thielemann In that case, here (with some bugfixes):
instance (Integral a, PrintfArg a) => PrintfArg (Ratio a) where formatArg x f@(FieldFormat w p a s l _ c) = if elem c "gGv" then let d = " % " ++ formatArg (denominator x) (FieldFormat Nothing Nothing Nothing s l "" 'd') "" (w',a') = case a of Just LeftAdjust -> (Nothing, Nothing) _ -> (fmap (subtract (length d)) w, a) n = formatArg (numerator x) (f {fmtWidth = w', fmtAdjust = a', fmtChar = 'd'}) "" in formatArg (n ++ d) (f {fmtPrecision = Nothing, fmtChar = 's'}) else if elem c "doxXb" then formatArg (round x :: Integer) f else case p of Nothing -> error "Text.Printf.formatArg: precision not given" Just p' -> if p' <= 0 then formatArg x (f {fmtPrecision = Nothing, fmtChar = 'd'}) else if elem c "fF" then let n = truncate x sig = '.' : goF (x - fromInteger n) p' (w',a') = case a of Just LeftAdjust -> (Nothing, Nothing) _ -> (fmap (subtract (length sig)) w, a) b = formatArg n (FieldFormat w' Nothing a' s l "" 'd') "" in formatArg (b ++ sig) (f {fmtPrecision = Nothing, fmtChar = 's'}) else if elem c "eE" then let (q,e) = log10 x sig = c : show e (w',a') = case a of Just LeftAdjust -> (Nothing, Nothing) _ -> (fmap (subtract (length sig)) w, a) fp = formatArg q (f {fmtWidth = w', fmtAdjust = a', fmtChar = 'f'}) "" in formatArg (fp ++ sig) (f {fmtPrecision = Nothing, fmtChar = 's'}) else error "Text.Printf.formatArg: bad format character" where goF _ 0 = "" goF x p = case compare x 0 of LT -> '-' : goF (negate x) p EQ -> "0" GT -> if 1 == p then show (round (10 * x) :: Integer) else let x10 = 10 * x n = truncate x10 in show n ++ goF (x10 - fromIntegral n) (p - 1) log10 x | x < 1 = let (q,e) = log10 (x * 10) in (q, e - 1) | 10 <= x = let (q,e) = log10 (x / 10) in (q, e + 1) | otherwise = (x, 0)
2020년 2월 8일 (토) 오전 6:44, Henning Thielemann
님이 작성: On Fri, 7 Feb 2020, Dannyu NDos wrote:
It just is so convenient.
instance (Integral a, Show a) => PrintfArg (Ratio a) where
Why should a Printf instance be base on Show? Wouldn't it better to format numerator and denominator using printf, too?