<div dir="ltr"><div>Faster version:<br></div><div><br></div><div>instance (Integral a, PrintfArg a) => PrintfArg (Ratio a) where</div>  formatArg x f@(FieldFormat w p a s l _ c) = if elem c "gGv"<br>    then let<br>      d = " % " ++ formatArg (denominator x) (FieldFormat Nothing Nothing Nothing s l "" 'd') ""<br>      (w',a') = case a of<br>        Just LeftAdjust -> (Nothing, Nothing)<br>        _ -> (fmap (subtract (length d)) w, a)<br>      n = formatArg (numerator x) (f {fmtWidth = w', fmtAdjust = a', fmtChar = 'd'}) ""<br>      in formatArg (n ++ d) (f {fmtPrecision = Nothing, fmtChar = 's'})<br>    else if elem c "doxXb"<br>      then formatArg (round x :: Integer) f<br>      else case p of <br>        Nothing -> error "Text.Printf.formatArg: precision not given"<br>        Just p' -> if p' <= 0<br>          then formatArg x (f {fmtPrecision = Nothing, fmtChar = 'd'})<br>          else if elem c "fF"<br>            then let<br>              n = truncate x<br>              sig = '.' : formatArg (round ((x - fromInteger n) * 10^p') :: Integer) (FieldFormat Nothing Nothing Nothing Nothing False "" 'd') ""<br>              (w',a') = case a of<br>                Just LeftAdjust -> (Nothing, Nothing)<br>                _ -> (fmap (subtract (length sig)) w, a)<br>              b = formatArg n (FieldFormat w' Nothing a' s l "" 'd') ""<br>              in formatArg (b ++ sig) (f {fmtPrecision = Nothing, fmtChar = 's'})<br>            else if elem c "eE"<br>              then let<br>                (q,e) = log10 x<br>                sig = c : show e<br>                (w',a') = case a of<br>                  Just LeftAdjust -> (Nothing, Nothing)<br>                  _ -> (fmap (subtract (length sig)) w, a)<br>                fp = formatArg q (f {fmtWidth = w', fmtAdjust = a', fmtChar = 'f'}) ""<br>                in formatArg (fp ++ sig) (f {fmtPrecision = Nothing, fmtChar = 's'})<br>              else error "Text.Printf.formatArg: bad format character"<br>   where<br>    goF _ 0 = ""<br>    goF x p = case compare x 0 of<br>      LT -> '-' : goF (negate x) p<br>      EQ -> "0"<br>      GT -> if 1 == p<br>        then show (round (10 * x) :: Integer)<br>        else let<br>          x10 = 10 * x<br>          n = truncate x10<br>          in show n ++ goF (x10 - fromIntegral n) (p - 1)<br>    log10 x<br>      | x < 1 = let<br>        (q,e) = log10 (x * 10)<br>        in (q, e - 1)<br>      | 10 <= x = let<br>        (q,e) = log10 (x / 10)<br>        in (q, e + 1)<br>      | otherwise = (x, 0)<br></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">2020ë…„ 2ì›” 8ì¼ (í† ) ì˜¤ì „ 8:40, Dannyu NDos <<a href="mailto:ndospark320@gmail.com">ndospark320@gmail.com</a>>ë‹˜ì´ ìž‘ì„±:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex"><div dir="ltr"><br><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">---------- Forwarded message ---------<br>보낸사람: <b class="gmail_sendername" dir="auto">Dannyu NDos</b> <span dir="auto"><<a href="mailto:ndospark320@gmail.com" target="_blank">ndospark320@gmail.com</a>></span><br>Date: 2020ë…„ 2ì›” 8ì¼ (í† ) ì˜¤ì „ 8:22<br>Subject: Re: add instance PrintfArg Ratio<br>To: Henning Thielemann <<a href="mailto:lemming@henning-thielemann.de" target="_blank">lemming@henning-thielemann.de</a>><br></div><br><br><div dir="ltr"><div>In that case, here (with some bugfixes):</div><div><br></div><div>instance (Integral a, PrintfArg a) => PrintfArg (Ratio a) where<br>  formatArg x f@(FieldFormat w p a s l _ c) = if elem c "gGv"<br>    then let<br>      d = " % " ++ formatArg (denominator x) (FieldFormat Nothing Nothing Nothing s l "" 'd') ""<br>      (w',a') = case a of<br>        Just LeftAdjust -> (Nothing, Nothing)<br>        _ -> (fmap (subtract (length d)) w, a)<br>      n = formatArg (numerator x) (f {fmtWidth = w', fmtAdjust = a', fmtChar = 'd'}) ""<br>      in formatArg (n ++ d) (f {fmtPrecision = Nothing, fmtChar = 's'})<br>    else if elem c "doxXb"<br>      then formatArg (round x :: Integer) f<br>      else case p of <br>        Nothing -> error "Text.Printf.formatArg: precision not given"<br>        Just p' -> if p' <= 0<br>          then formatArg x (f {fmtPrecision = Nothing, fmtChar = 'd'})<br>          else if elem c "fF"<br>            then let<br>              n = truncate x<br>              sig = '.' : goF (x - fromInteger n) p'<br>              (w',a') = case a of<br>                Just LeftAdjust -> (Nothing, Nothing)<br>                _ -> (fmap (subtract (length sig)) w, a)<br>              b = formatArg n (FieldFormat w' Nothing a' s l "" 'd') ""<br>              in formatArg (b ++ sig) (f {fmtPrecision = Nothing, fmtChar = 's'})<br>            else if elem c "eE"<br>              then let<br>                (q,e) = log10 x<br>                sig = c : show e<br>                (w',a') = case a of<br>                  Just LeftAdjust -> (Nothing, Nothing)<br>                  _ -> (fmap (subtract (length sig)) w, a)<br>                fp = formatArg q (f {fmtWidth = w', fmtAdjust = a', fmtChar = 'f'}) ""<br>                in formatArg (fp ++ sig) (f {fmtPrecision = Nothing, fmtChar = 's'})<br>              else error "Text.Printf.formatArg: bad format character"<br>   where<br>    goF _ 0 = ""<br>    goF x p = case compare x 0 of<br>      LT -> '-' : goF (negate x) p<br>      EQ -> "0"<br>      GT -> if 1 == p<br>        then show (round (10 * x) :: Integer)<br>        else let<br>          x10 = 10 * x<br>          n = truncate x10<br>          in show n ++ goF (x10 - fromIntegral n) (p - 1)<br>    log10 x<br>      | x < 1 = let<br>        (q,e) = log10 (x * 10)<br>        in (q, e - 1)<br>      | 10 <= x = let<br>        (q,e) = log10 (x / 10)<br>        in (q, e + 1)<br>      | otherwise = (x, 0)<br></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">2020ë…„ 2ì›” 8ì¼ (í† ) ì˜¤ì „ 6:44, Henning Thielemann <<a href="mailto:lemming@henning-thielemann.de" target="_blank">lemming@henning-thielemann.de</a>>ë‹˜ì´ ìž‘ì„±:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex"><br>
On Fri, 7 Feb 2020, Dannyu NDos wrote:<br>
<br>
> It just is so convenient.<br>
> <br>
> instance (Integral a, Show a) => PrintfArg (Ratio a) where<br>
<br>
Why should a Printf instance be base on Show? Wouldn't it better to format <br>
numerator and denominator using printf, too?<br>
</blockquote></div>
</div></div>
</blockquote></div>