Ghci has unusual non-configurable numeric representations (?)

I’m surprised that ghci is so eager to use scientific notation:

Prelude> 0.1
0.1
Prelude> 0.01
1.0e-2

I understand defaulting to scientific notation for long numbers (although I don’t like that), but ghci switches to scientific notation after only two digits. This is an unusual policy for a repl, in my experience. My understanding from :h and StackOverflow (links below) is that this behavior cannot be configured without hacking the prelude (for example). Is that correct?

I know that I can use other means such as Text.Printf.printf or defining my own Show instance to format numbers, but that’s not worth the trouble. ghci’s behavior is only a very small annoyance–but it is a continual annoyance.

Well, it’s not a big deal, but I wondered if I am misunderstanding something.

2 Likes

Maybe you can try this: http://stackoverflow.com/questions/38339190/ddg#38339303

So you don’t override show but instead define a subclass that falls back on show for most cases, but overrides the behavior for floating point numbers. That shouldn’t require modifying the Prelude.

P.S. also look at the Numeric module in base, it has a lot of number formatting functions.

I have been able to make it work with the following code:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
module DecimalFloatShow
  ( DecimalFloatShow
  , decimalFloatShow
  , decimalFloatPrint
  )
where

import           Text.Show
import           Numeric

class DecimalFloatShow a where
  decimalFloatShowsPrec :: Maybe Int -> Int -> a -> ShowS

decimalFloatShow :: DecimalFloatShow a => a -> String
decimalFloatShow x = decimalFloatShowsPrec Nothing 0 x ""

instance {-# OVERLAPPABLE #-} Show a => DecimalFloatShow a where
  decimalFloatShowsPrec _ = showsPrec

instance DecimalFloatShow Double  where
  decimalFloatShowsPrec d _ = showFFloat d
instance DecimalFloatShow Float   where
  decimalFloatShowsPrec d _ = showFFloat d

decimalFloatPrint :: DecimalFloatShow a => a -> IO ()
decimalFloatPrint = putStrLn . decimalFloatShow

And then running this command:

$ ghci DecimalFloatShow.hs -interactive-print=decimalFloatPrint
...
*DecimalFloatShow> 0.01
0.01

Another and in my opinion better way is to run a parser after showing it, that doesn’t require any type class hacks (I stole this approach from the shower pretty printing package):

module DecimalFloatShow
  ( decimalFloatShow
  , decimalFloatPrint
  )
where

import           Numeric

decimalFloatShow :: Show a => a -> String
decimalFloatShow = go . show where
  go "" = ""
  go s | ((x,xs):_) <- readFloat s = showFFloat Nothing x (go xs)
  go (x:xs) = x : go xs

decimalFloatPrint :: Show a => a -> IO ()
decimalFloatPrint = putStrLn . decimalFloatShow

You can use this in the same way as the code above, but this also works for lists and other data structures that contain floats:

$ ghci DecimalFloatShow.hs -interactive-print=decimalFloatPrint
...
*DecimalFloatShow> [0.01]
[0.01]
*DecimalFloatShow> (0.01, 0.001)
(0.01,0.001)
2 Likes