Reading showables

Hi, Is there a way to read Showables? main = do putStrLn $ show $ read Thanks -John

John,
By convention, read . show is supposed to be id.
However, in real life, this is often not the case. It all depends on
the implementor, and this is a convention that seems to be broken
pretty frequently.
Often there is a show instance with no read or vice versa, and
sometimes even when there is both read and show they are not inverses.
Thomas.
main = show . read
Am 7. Dezember 2008 14:11 schrieb John Ky
Hi,
Is there a way to read Showables?
main = do putStrLn $ show $ read
Thanks
-John
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Thomas,
So "show . read" and "\x -> show (read x)" are actually mean different
things?
Also, I never suspected that something like this should succeed:
putStrLn $ (read . show) $ "!@#%$^DFD"
Thanks,
-John
On Mon, Dec 8, 2008 at 12:38 AM, Thomas Hartman
John,
By convention, read . show is supposed to be id.
However, in real life, this is often not the case. It all depends on the implementor, and this is a convention that seems to be broken pretty frequently.
Often there is a show instance with no read or vice versa, and sometimes even when there is both read and show they are not inverses.
Thomas.
main = show . read
Am 7. Dezember 2008 14:11 schrieb John Ky
: Hi,
Is there a way to read Showables?
main = do putStrLn $ show $ read
Thanks
-John
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, 2008-12-08 at 11:16 +1100, John Ky wrote:
Hi Thomas,
So "show . read" and "\x -> show (read x)" are actually mean different things?
No. Of course not. But there's no guarantee that show (read x) = x either.
Also, I never suspected that something like this should succeed:
putStrLn $ (read . show) $ "!@#%$^DFD"
Of course it succeeds. You put the `show' first; show always succeeds and --- for the Show instances in the Prelude, plus some --- read (show x) = x for finite, total x. (Note that read . show /= show . read; they don't even have the same type! show . read :: forall alpha. Show alpha => String -> String read . show :: forall alpha beta. (Read alpha, Show beta) => alpha -> beta NB: The reason why show . read is illegal should be screaming out at you about now. The caveat --- other than the one I mentioned above --- to claims that read . show = id should also be screaming out.) jcc

Thanks for the clarification.
They're all the same, as you've explained:
Prelude> putStrLn $ (show . read) "123"
*** Exception: Prelude.read: no parse
Prelude> putStrLn $ show $ read "123"
*** Exception: Prelude.read: no parse
Prelude> putStrLn $ (\x -> show (read x)) "123"
*** Exception: Prelude.read: no parse
-John
On Mon, Dec 8, 2008 at 12:08 PM, Jonathan Cast
On Mon, 2008-12-08 at 11:16 +1100, John Ky wrote:
Hi Thomas,
So "show . read" and "\x -> show (read x)" are actually mean different things?
No. Of course not. But there's no guarantee that
show (read x) = x
either.
Also, I never suspected that something like this should succeed:
putStrLn $ (read . show) $ "!@#%$^DFD"
Of course it succeeds. You put the `show' first; show always succeeds and --- for the Show instances in the Prelude, plus some ---
read (show x) = x
for finite, total x.
(Note that read . show /= show . read; they don't even have the same type!
show . read :: forall alpha. Show alpha => String -> String read . show :: forall alpha beta. (Read alpha, Show beta) => alpha -> beta
NB: The reason why show . read is illegal should be screaming out at you about now. The caveat --- other than the one I mentioned above --- to claims that read . show = id should also be screaming out.)
jcc

2008/12/7 John Ky
Thanks for the clarification.
They're all the same, as you've explained:
Prelude> putStrLn $ (show . read) "123" *** Exception: Prelude.read: no parse
The "no parse" is an artifact of defaulting: Prelude> putstrLn $ (show . read) "()" () It's because ghci defaults the free type variables to (). The signatures for show and read are: show :: (Show a) => a -> String read :: (Read a) => String -> a So when you do show . read, you get String -> String, but where did the a's go? What type were they (what type is "read" trying to parse)? Ghci makes them (), because it's weird like that. A compiler will complain that there is an unconstrained type variable that it doesn't know what to do with. You can constrain it yourself with something like: showAs :: (Show a) => a -> a -> String showAs typ x = show (x `asTypeOf` typ) Then: Prelude> putStrLn $ (showAs (undefined::Int) . read) "123" 123 But this situation doesn't arise in practice, because usually you do something with a value you've read other than just printing it, and that something will determine the type to read. Luke

2008/12/7 John Ky
Thanks for the clarification.
They're all the same, as you've explained:
Prelude> putStrLn $ (show . read) "123" *** Exception: Prelude.read: no parse
Prelude> putStrLn $ show $ read "123" *** Exception: Prelude.read: no parse
Prelude> putStrLn $ (\x -> show (read x)) "123" *** Exception: Prelude.read: no parse
Luke explained why the Exception is raised, I'll try to explain why this kind of problem happens in general: First two ways that work: Prelude> putStrLn $ (show :: Int -> String) . read $ "123" 123 Prelude> putStrLn $ show . (read :: String -> Int) $ "123" 123 In these examples we explicitly typed either the polymorphic producer (i.e. read) or the producer (i.e. show) so ghci can unify the type variables and figure out what is the right instance of the type class. Generally this happen wherever the type class member has a type variable only to the right of the type (either foo :: a or foo :: Something ->a). This kind of member is polymorphic on the result so the caller must define what it's expecting. "show . read" is saying to ghc both the result of read will define the type and the argument of show will define the type, which is a (kind of) mutually recursive typing issue.
-John
Best regards, Daniel Yokomizo

One more thing.
If your Read/Show instances are created by
data (or newtype) ...
deriving (Read,Show)
then read . show will do the right thing.
Thomas.
Am 7. Dezember 2008 14:11 schrieb John Ky
Hi,
Is there a way to read Showables?
main = do putStrLn $ show $ read
Thanks
-John
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Given two different types T1 and T2, it's possible to have two different results of
let {x :: T1; x = read s} in show x
and
let {x :: T2; x = read s} in show x
so that neither of two "read"s fails. For example
let {x :: Int; x = read "1000000000000"} in show x
produces the answer "-727379968". BTW, I'd love to be able to give default instances locally, so that something like
main = withdef Read Int {putStrLn $ show $ read "1000000000000"}
would typecheck successfully. On 7 Dec 2008, at 16:11, John Ky wrote:
Hi,
Is there a way to read Showables?
main = do putStrLn $ show $ read
Thanks
-John
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
Daniel Yokomizo
-
John Ky
-
Jonathan Cast
-
Luke Palmer
-
Miguel Mitrofanov
-
Thomas Hartman