[Haskell-cafe] Hiding functions

Lyle Kopnicky lists at qseep.net
Thu Aug 12 15:23:03 EDT 2004


Hi all,

I'm working on a program that uses my own brand of exceptions, and I 
created two functions called 'throw' and 'catch'.  In order for this to 
work, I hide the Prelude 'catch' in my module, called 'Cont.hs'.  Thus:

module Cont where
import Prelude hiding (catch)
...
throw = ...
catch = ...

This works hunky-dory until I create another file that imports Cont.  I 
get a conflict when I use 'catch', so I have to  hide the Prelude one again:

import Prelude hiding (catch)
import Cont
...
... throw ...
... catch ...

So I'm a bit annoyed by this 'propagation' of hiding clauses.  Then I 
created a new file,  that redefined throw:

module ResumableExceptions where
import Cont hiding (throw)
import qualified Cont (throw)
...
throw = ... Cont.throw ...

Finally, I created a file using ResumableExceptions:

import Cont hiding (throw)
import ResumableExceptions
...
... throw ...

If I wanted to also use 'catch' I'd have to hide that from the Prelude 
as well.

I can't use type classes to solve this problem, because the types of the 
two 'throw' functions are different.

Perhaps I should just make up new names for these things, eh?  But there 
might be code that uses 'throw' and doesn't really care which one is 
used, and it would be nice to just modify the import line and be done 
with it.

Any opinions?

Thanks,
Lyle


More information about the Haskell-Cafe mailing list