Hello,

On Tue, 27 Dec 2005 16:39:34 +0000, Chris Kuklewicz wrote:

>Happy Holidays,

>I was wondering if it this small snippet of code could be altered to
>require fewer OPTIONS -fallow-... switches.

Here is a partial solution using only -fglasgow-exts:

> module MyShow where

> class MyShow t where
>     swim :: String -> t

> instance MyShow String where
>     swim = id

> instance (Show a, MyShow t) => MyShow (a -> t) where
>     swim s x = swim (s ++ show x)

> test foo = foo " and " 7 " are "

> main = do putStrLn $ swim "Hello" " " "World #" [17,18,19] "!"
>           putStrLn $ test (swim "I also think " [4,5,6]) "cool" "."

The problem of this solution is that, because we are using show in the 
definition of swim for (a -> t), the strings are beeing printed with extra 
"\"". 

*MyShow> main
Hello" ""World #"[17,18,19]"!"
I also think [4,5,6]" and "7" are ""cool""."

You can, ofcourse, add a new instance for (String -> t) but that will 
cost you -fallow-incoherent-instances and -fallow-overlapping-instances.

> instance MyShow t => MyShow (String -> t) where
>     swim s x = swim (s ++ x)

>Could this be improved by TypeEq machinery?  Is there a Haskell 98 way
>to make myShow work this way?

The problem of the previous solution is that you do not want, in the general 
case,
use the default instance of Show for Strings. An alternative is to just 
introduce 
a newtype S (isomorphic to String) that allows you to handle Strings 
differently:

> module MyShow where

> class MyShow t where
>     swim :: S -> t

> newtype S = S {unS :: String}

> instance MyShow S where
>     swim = id

> instance Show S where
>     show = unS

> instance (Show a, MyShow t) => MyShow (a -> t) where
>     swim s x = swim (S $ unS s ++ show x)

> putSLn = putStrLn . unS

> test foo = foo (S " and ") 7 (S " are ")

> main = do putSLn $ swim (S "Hello") (S " ") (S "World #") [17,18,19] (S "!")
>                 putSLn $ test (swim (S "I also think ") [4,5,6]) (S "cool") 
> (S ".")

By using the newtype S instead of Haskell String, you obtain an Haskell 98 
solution. I am not sure if this is good enough for you but it seems a good 
compromise.

Hope it helps!

Cheers,

Bruno


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to