[Yhc] Inconsistent compilation when type context is involved

Thomas Shackell shackell at cs.york.ac.uk
Thu Mar 22 07:06:56 EDT 2007


Dimitry Golubovsky wrote:
> =============
> 
> module Main where
> 
> import Data.Maybe
> 
> fun :: Show a => String -> Maybe a -> IO ()
> fun s mb = do
>  putStrLn s
>  case mb of
>    Nothing -> return ()
>    Just a -> do putStrLn (show a)
>                 return ()
> 
> 
> main = fun "bla" Nothing
> 
> 
> =============
> 
> compiles with Yhc and runs fine (even with only the first line of
> main, so there is no mentioning that a String is wrapped in Maybe).

This program shouldn't compile, it doesn't compile in either ghc or hugs 
and is definitely ambiguous. Looking at the core that Yhc generates:

   Main.main =
       let v234 = Prelude.Prelude.Show.Prelude.Integer
       in Main.fun v234 Main._LAMBDA243 Prelude.Nothing

   Main._LAMBDA243 = "bla"

It's arbitrarily chosen to give the Show dictionary for 'Integer' (which 
is 'Prelude.Prelude.Show.Prelude.Integer'). Given that Yhc's type system 
is unmodified since nhc98 it's likely that this is a 'carry over' bug 
from nhc98.

Thanks


Tom


More information about the Yhc mailing list