How to convert a Rational into a "pretty" String?

2.5k views Asked by At

I want to display some Rational values in their decimal expansion. That is, instead of displaying 3 % 4, I would rather display 0.75. I'd like this function to be of type Int -> Rational -> String. The first Int is to specify the maximum number of decimal places, since Rational expansions may be non-terminating.

Hoogle and the haddocks for Data.Ratio didn't help me. Where can I find this function?

5

There are 5 answers

1
xnyhps On BEST ANSWER

Here is an arbitrary precision solution that doesn't use floats:

import Data.Ratio

display :: Int -> Rational -> String
display len rat = (if num < 0 then "-" else "") ++ (shows d ("." ++ take len (go next)))
    where
        (d, next) = abs num `quotRem` den
        num = numerator rat
        den = denominator rat

        go 0 = ""
        go x = let (d, next) = (10 * x) `quotRem` den
               in shows d (go next)
0
Alec On

You can make it. Not elegant, but does the job:

import Numeric
import Data.Ratio

display :: Int -> Rational -> String
display n x = (showFFloat (Just n) $ fromRat x) ""
3
Daniel Wagner On

Arbitrary precision version that re-uses library code:

import Data.Number.CReal

display :: Int -> Rational -> String
display digits num = showCReal digits (fromRational num)

I know I've seen a function before that converts rationals into digits in a way that's easier to inspect (i.e. that makes it quite clear where the digits start repeating), but I can't seem to find it now. In any case, it's not hard to write, if that turns out to be a need; you just code up the usual long-division algorithm and watch for divisions you've already done.

0
augustss On

Here's one that I wrote a few weeks ago. You can specify the number of decimals you want (correctly rounded), or just pass Nothing in which case it will print the full precision, including marking the repeated decimals.

module ShowRational where
import Data.List(findIndex, splitAt)

-- | Convert a 'Rational' to a 'String' using the given number of decimals.
-- If the number of decimals is not given the full precision is showed using (DDD) for repeating digits.
-- E.g., 13.7/3 is shown as \"4.5(6)\".
showRational :: Maybe Int -> Rational -> String
showRational (Just n) r =
    let d = round (abs r * 10^n)
        s = show (d :: Integer)
        s' = replicate (n - length s + 1) '0' ++ s
        (h, f) = splitAt (length s' - n) s'
    in  (if r < 0 then "-" else "") ++ h ++ "." ++ f
-- The length of the repeating digits is related to the totient function of the denominator.
-- This means that the complexity of computing them is at least as bad as factoring, i.e., it quickly becomes infeasible.
showRational Nothing r =
    let (i, f) = properFraction (abs r) :: (Integer, Rational)
        si = if r < 0 then "-" ++ show i else show i
        decimals f = loop f [] ""
        loop x fs ds =
            if x == 0 then
                ds
            else
                case findIndex (x ==) fs of
                    Just i  -> let (l, r) = splitAt i ds in l ++ "(" ++ r ++ ")"
                    Nothing -> let (c, f) = properFraction (10 * x) :: (Integer, Rational) in loop f (fs ++ [x]) (ds ++ show c)
    in  if f == 0 then si else si ++ "." ++ decimals f
0
George Rogers On
import Data.List as L
import Data.Ratio

display :: (Integral i, Show i) => Int -> Ratio i -> String
display len rat = (if num < 0 then "-" else "") ++ show ip ++ "." ++ L.take len (go (abs num - ip * den))
  where
    num = numerator rat
    den = denominator rat
    ip  = abs num `quot` den

    go 0 = ""
    go x = shows d (go next)
      where
        (d, next) = (10 * x) `quotRem` den