[Yhc] Yhc (and Catch?) bugs

Isaac Dupree isaacdupree at charter.net
Mon Aug 6 19:13:34 EDT 2007


>> --Bug: Always specifying an import list when importing Prelude,
>> --breaks handling of some built-in syntax.  However, Hugs also has
>> --this bug so I'll keep my workaround.
>> {-
>> import Prelude ( )
>>
>> simple :: ()
>> simple = ()
>> -}

Maybe implicitly always adding
import qualified Prelude as SecretNameNoOneWillEverUse
would be a hack that would fix that?

It relies on:
(1) the instances in Prelude are always imported in every module anyway, 
in standard Haskell.

(2) Another Yhc bug!!! :

module Test where
import Prelude hiding ( (==) )
data Foo = Bar
instance Eq Foo where (==) = undefined

compiles.  It should not compile because (==) has not been imported, 
even qualified. In standard Haskell, you would have to add at least
import qualified Prelude ( (==) )
.

So maybe, to prevent incorrect programs from compiling after the other 
bug is no more, it is preferably
import qualified Prelude as SecretNameNoOneWillEverUse hiding (Eq(..), 
Ord(..) and the rest)
or if possible, name those elusive things (), [] etc, to import...

But none of that is necessary for the basic hack - IS IT POSSIBLE? (even 
if so, is it too hacky? I believe Jhc *always* implicitly imports 
something like Jhc.Prelude that contains definitions of [] and a few 
other things, in addition to the standard Prelude stuff, and that feels 
*right*, to me)

Isaac


More information about the Yhc mailing list