add instance PrintfArg Ratio

Dannyu NDos ndospark320 at gmail.com
Fri Feb 7 11:01:39 UTC 2020


It just is so convenient.

instance (Integral a, Show a) => PrintfArg (Ratio a) where
    formatArg x f@(FieldFormat w p a s l _ c) = if elem c "gGv"
        then showsPrec 0 x
        else if elem c "doxXb"
            then formatArg (round x :: Integer) (f {fmtPrecision = Nothing,
fmtChar = 'd'})
            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'
                            b = case a of
                                Just ZeroPad -> formatArg n (f {fmtWidth =
fmap (subtract (length sig)) w, fmtPrecision = Nothing, fmtChar = 'd'}) ""
                                _ -> show n
                            in formatArg (b ++ sig) (f {fmtPrecision =
Nothing, fmtChar = 's'})
                        else if elem c "eE"
                            then let
                                (q,e) = log10 x
                                sig = c : show e
                                a' = case a of
                                    Just ZeroPad -> a
                                    _ -> Nothing
                                fp = formatArg q (f {fmtWidth = fmap
(subtract (length sig)) 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)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20200207/a267ca1d/attachment.html>


More information about the Libraries mailing list