RE: [Haskell-cafe] Hiding functions

What is wrong with creating your own catch and throw with different names? e.g. data MyException = MyException ... deriving (Typeable, Show) catchMyEx :: IO a -> (MyException -> IO a) -> IO a catchMyEx = catchDyn throwMyEx :: MyException -> a throwMyEx = throwDyn
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.
Can you expand on this? (more example code?) If you want to throw your own exceptions, then you must use throwDyn/catchDyn, so you have to use something other than catch/throw anyway. Alistair.
-----Original Message----- From: Lyle Kopnicky [mailto:lists@qseep.net] Sent: 12 August 2004 20:23 To: Haskell Cafe Subject: [Haskell-cafe] Hiding functions
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
----------------------------------------- ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

Alistair, I'm throwing my own exceptions in my own monad, not the IO one. But thanks for pointing me to the stuff about dynamic types. I'm going to be creative and pick some new names. - Lyle Bayley, Alistair wrote:
What is wrong with creating your own catch and throw with different names? e.g.
data MyException = MyException ... deriving (Typeable, Show)
catchMyEx :: IO a -> (MyException -> IO a) -> IO a catchMyEx = catchDyn throwMyEx :: MyException -> a throwMyEx = throwDyn
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.
Can you expand on this? (more example code?) If you want to throw your own exceptions, then you must use throwDyn/catchDyn, so you have to use something other than catch/throw anyway.
Alistair.
participants (2)
-
Bayley, Alistair
-
Lyle Kopnicky