
Hello, One thing that bugs me about Haskell is that exceptions are not extensible. I don't know how to craft a good solution, but perhaps if I explain the problem well, someone would come up with one. In a language such as Python or Java, and exception is an object. Let's consider Python for a quick example. Python has an IOError exception. So if I want to write a handler that deals with IOErrors, that's easy enough. Now maybe I want to do something like report socket errors specially. I could define a SocketError class that subclasses IOError. I could take this further, and define a URLError that subclasses SocketError. Now the beauty of it is that I can: * Have a handler that catches URLErrors only and does nothing special with SocketErrors or IOErrors. * Have a handler -- perhaps not even mine -- that catches and works with IOErrors. Since SocketError and URLError are descendants of IOError, that handler will *automatically* work if I raise a SocketError or a URLError. I can see no such mechanism in Haskell. Haskell's I/O exceptions have a certain defined set of errors that they can report, and I can't subclass them and make them more specific for my purposes if I want. Ditto for all the others. The Dynamic exception support is necessary and good to have, but it also under-documented and can be complex. And of course, they still suffer from the same lack of extensibility Are there any suggestions on how we might improve this situation in Haskell? -- John

John Goerzen wrote:
One thing that bugs me about Haskell is that exceptions are not extensible.
I don't know how to craft a good solution, but perhaps if I explain the problem well, someone would come up with one.
Open datatypes would be the best solution, I think. http://www.informatik.uni-bonn.de/~loeh/OpenDatatypes.pdf -- Ashley Yakeley Seattle, WA

On 30 August 2006 20:20, Ashley Yakeley wrote:
John Goerzen wrote:
One thing that bugs me about Haskell is that exceptions are not extensible.
I don't know how to craft a good solution, but perhaps if I explain the problem well, someone would come up with one.
Open datatypes would be the best solution, I think. http://www.informatik.uni-bonn.de/~loeh/OpenDatatypes.pdf
I don't think we need more extensions to do a reasonable job of extensible exceptions: http://www.haskell.org/~simonmar/papers/ext-exceptions.pdf Cheers, Simon

In article
<2E9B33CE230409489A7ED37E5E34090F0541A61D@EUR-MSG-20.europe.corp.microso
ft.com>,
"Simon Marlow"
I don't think we need more extensions to do a reasonable job of extensible exceptions:
You write:
Compared to our approach, theirs requires new extensions to the language (although not deep),
"Typeable" is an extension to Haskell, and a rather ugly one at that. The open datatypes extension is both cleaner and more general.
and has difficulties with separate compilation.
They claim to solve this I think, though I haven't examined it really carefully. You may know better, of course.
Arguably the open data types approach is more direct and more accessible,
Yes,
as is often the case with extensions designed to solve a particular problem.
That's not fair. Open datatypes have other applications. A general "file interpreter" for instance, that given a MIME type string and a list of bytes yields an object. Or a collection of variable "resources" of various types that could be passed to a program. Or a hierarchy of UI widgets. Or anything that Typeable and Dynamic are currently used for, but more cleanly. Hs-plugins, for instance. It's the missing piece.
Still, the argument for adding open data types to the language is weakened by the fact that they are subsumed by type classes: in fact the authors give an encoding of open data types into type classes,
Well not really. The "encoding" involves lifting everything from values to types, which means a function still can't return a value of an open type determined at run-time. -- Ashley Yakeley Seattle WA

Hi Ashley. Thanks for your interest in open data types. As one of the authors of the "open data types" paper, I'd like to comment on the current discussion. You comment Simon's upcoming HW paper on extensible exceptions:
You write:
Compared to our approach, theirs requires new extensions to the language (although not deep),
"Typeable" is an extension to Haskell, and a rather ugly one at that. The open datatypes extension is both cleaner and more general.
I think the stress here is on *new* extensions. I agree that an open type of type representations might be a more beautiful solution to the problem that Typeable solves. Nevertheless, the fact is that Simon's solution can be used in current GHC without further implementation work.
and has difficulties with separate compilation.
They claim to solve this I think, though I haven't examined it really carefully. You may know better, of course.
I've discussed this with Simon PJ. Apart from minor technical problems, everything seems doable in GHC, but it is quite some work and it's not clear that I will have the time to study GHC closely enough to do it in the near future. I hope I can say more after the Hackathon ...
Arguably the open data types approach is more direct and more accessible,
Yes,
as is often the case with extensions designed to solve a particular problem.
That's not fair. Open datatypes have other applications. A general "file interpreter" for instance, that given a MIME type string and a list of bytes yields an object. Or a collection of variable "resources" of various types that could be passed to a program. Or a hierarchy of UI widgets. Or anything that Typeable and Dynamic are currently used for, but more cleanly. Hs-plugins, for instance.
It's the missing piece.
True, open data types have never been invented as a solution to the problem of extensible exceptions. It is an application that we found afterwards.
Still, the argument for adding open data types to the language is weakened by the fact that they are subsumed by type classes: in fact the authors give an encoding of open data types into type classes,
Well not really. The "encoding" involves lifting everything from values to types, which means a function still can't return a value of an open type determined at run-time.
Even if both approaches would be equally expressive, the type class encoding still has a lot of syntactic overhead. Moving from a closed to an open data type encoded by type classes requires changing your whole program, whereas with open data types, it is a local change. Apart from this discussion however, open data types are clearly not Haskell' material, because the proposal is new and currently unimplemented. The extensions required for Simon's approach to exceptions have a good chance of being included in Haskell'. Cheers, Andres

Hello Andres, Friday, September 1, 2006, 2:27:34 PM, you wrote:
Thanks for your interest in open data types. As one of the authors of the "open data types" paper, I'd like to comment on the current discussion.
i'm not yet read about this, but may be open types have something in common with type families already implemented by Manuel Chakravarty? http://hackage.haskell.org/trac/ghc/wiki/TypeFunctions one more question what i still plan to ask him is what is the difference between GADTs and type families -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Friday, September 1, 2006, 2:27:34 PM, you wrote:
Thanks for your interest in open data types. As one of the authors of the "open data types" paper, I'd like to comment on the current discussion.
i'm not yet read about this, but may be open types have something in common with type families already implemented by Manuel Chakravarty?
Löh/Hinze-style open data types are orthogonal to the type indexed data types described at the above wiki page. Instances of type indexed data types (or indexed type families as I am tending to call them currently) may not overlap. For example, while it is fine to write data family T a :: * data instance T Bool = TBool data instance T Int = TInt the following two instances are bad: data instance T (Int, a) = TL -- BAD data instance T (a, Int) = TR -- DEFINITION as they overlap at T (Int, Int). In contrast, Löh/Hinze open data types are about *fully* overlapping data declarations. So, in their proposal (using a slightly different syntax) open data S :: * S1 :: S S2 :: S is a perfectly fine definition. This distinction between overlapping and non-overlapping definitions continues on the value level (ie, with functions operating on these data types). Given the indexed type family T above, I can write a function foo :: T Bool -> () foo TBool = () but I cannot write a *toplevel* function pattern matching on more than one data instance at once; ie, the following gives a type error: foo :: T a -> a foo TBool = False -- BAD foo TInt = 0 -- DEFINITION If I want to write such a function, I need to use a type class, as follows: class Foo a where foo :: T a -> a instance Foo Bool where foo TBool = False instance Foo Int where foo TInt = 0 Again, in contrast, Löh/Hinze open data types enable us to write open bar :: S -> Bool bar S1 = False bar S2 = True So, both features are truly orthogonal and, in fact, they are synergetic! More precisely, an alternative syntax for Löh/Hinze open types are overlapping type families. So, we might define S alternatively as data family S :: * data instance S = S1 data instance S = S2 Then, one might hope we can allow overlapping indexed type families, such as the instances for T (Int, a) and T (a, Int) above, and implement them by a combination of the implementation of indexed data types that I already added to GHC and Löh/Hinze's method for open data types. NB: Curiously, the application of open data types that AFAIK got Andres and Ralf into open data types, namely spine-view SYB http://www.iai.uni-bonn.de/~loeh/SYB1.html, can already be implemented with *non-overlapping* indexed type families if I am not mistaken.
one more question what i still plan to ask him is what is the difference between GADTs and type families
GADTS: * Closed definition * Local type-refinement in case alternatives Data families: * Open definitions (much like classes are open, you can always add more instances) * Type constraints due to indexes is propagated globally In other words, the relationship between GADTs and data families is not unlike that between toplevel function definitions (closed) and class methods (open). Moreover, you can perfectly well have indexed newtypes. (They are already implemented and quite interesting as Haskell guarantees that newtypes are unlifted.) In fact, there is nothing essential preventing us from having indexed families of GADTs - well, maybe except the occasional exploding head ;) For example, you might define data family T a :: * data instance T [a] where IList :: Int -> T [Int] BList :: Bool -> T [Bool] data instance T (Maybe a) where IMaybe :: Int -> T (Maybe Int) BMaybe :: Bool -> T (Maybe Bool) (This definition is not supposed to make much sense, it just illustrates the idea of an indexed GADT.) However, I haven't fully implemented indexed GADT families yet, as I want to finish other functionality first. So, maybe there are problems that I haven't stumbled over yet. Manuel

Hello Manuel, Wednesday, September 6, 2006, 9:17:46 PM, you wrote:
So, both features are truly orthogonal and, in fact, they are synergetic! More precisely, an alternative syntax for Löh/Hinze open types are overlapping type families. So, we might define S alternatively as
data family S :: * data instance S = S1 data instance S = S2
to be exact, it's alternative syntax for GADT "data S = S1 | S2" while open types just allows to split GADT definition into several chunks. It seems that you skipped this point - they also propose to use open technique for GADT-style definitions. as a result, while open data types are truly orthogonal to GADT, together they implement something very close to type families. the only difference between GADT+OT vs TF remains:
GADTS+open types: * Local type-refinement in case alternatives
Data families: * Type constraints due to indexes is propagated globally
can you please explain that this means?
In fact, there is nothing essential preventing us from having indexed families of GADTs
for why? the only difference is that TF define a one-to-one relationship (each type index defines just one data constructor) while GADT define one-to-many relationship (one type index may be mapped to several data constructors). are we really need this difference and especially different syntax for such close things? just for curiosity, i was also interested in ideas of type-level programming and invented my own syntax that is more like yours. but really my syntax just based on the syntax of ordinary functions: type BaseType [a] = BaseType a BaseType (Set a) = BaseType a BaseType (Map a b) = BaseType a BaseType a = a is a recursive definition which may be evaluated with first-fit or best-fit strategy data Expr a = If (Expr Bool) (Expr a) (Expr a) Expr Int = Zero Expr Int = Succ (Expr Int) Expr Bool = TRUE Expr Bool = Not (Expr Bool) is alternative syntax for GADT. we may consider it as multi-value function, and 'data' defines functions that maps types into data constructors while 'type' defines functions that maps types into types. going further, why not allow 'type' to define multi-value functions? and vice versa, why not use 'data' to define one-to-one relation by best-fit or first-fit strategy? going further, why not define type of relation in "function" head? so that we can both use 'data' and 'type' to define one-to-one (non-overlapped) type families or one-to-many (overlapped, GADT-style) ones and even select matching strategy here? for example: data nonOverlapped T TTrue = CTrue T TFalse = CFalse data bestFit Eq a b = CFalse Eq a a = CTrue type firstFit Eq a a = TTrue Eq a b = TFalse -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

In article <20060901102733.GF21467@iai.uni-bonn.de>,
Andres Loeh
I think the stress here is on *new* extensions. I agree that an open type of type representations might be a more beautiful solution to the problem that Typeable solves. Nevertheless, the fact is that Simon's solution can be used in current GHC without further implementation work.
OK, fair enough. Open datatypes and functions will not, as you point out, be in Haskell'. I'd also like to query O'Haskell here. Simon writes in the paper:
O'Haskell extends Haskell with object-oriented subtyping. As such, it would be entirely possible to implement extensible exceptions using inheritance in O'Haskell.
I believe O'Haskell (like OOHaskell) doesn't provide the required dynamic downcasting operation either. AFAICT the extensions are essentially syntactic sugar: the subtyping is strictly static. -- Ashley Yakeley, Seattle WA

On 02 September 2006 06:29, Ashley Yakeley wrote:
I'd also like to query O'Haskell here. Simon writes in the paper:
O'Haskell extends Haskell with object-oriented subtyping. As such, it would be entirely possible to implement extensible exceptions using inheritance in O'Haskell.
I believe O'Haskell (like OOHaskell) doesn't provide the required dynamic downcasting operation either. AFAICT the extensions are essentially syntactic sugar: the subtyping is strictly static.
Good point; thanks for spotting that. Simon

Hello Simon, Thursday, August 31, 2006, 12:33:26 PM, you wrote:
I don't think we need more extensions to do a reasonable job of extensible exceptions:
i'm not yet read but guess that this is paper you will present at ICFP? can you please say in 2 words - what is the current state of this? is it can be used with ghc 6.4, or 6.6, or ...? some solution in this area, imho, is a must for serious application development -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 31 August 2006 12:43, Bulat Ziganshin wrote:
Hello Simon,
Thursday, August 31, 2006, 12:33:26 PM, you wrote:
I don't think we need more extensions to do a reasonable job of extensible exceptions:
i'm not yet read but guess that this is paper you will present at ICFP?
can you please say in 2 words - what is the current state of this?
"not" "yet" (well that was about all I could say in 2 words :-).
is it can be used with ghc 6.4, or 6.6, or ...? some solution in this area, imho, is a must for serious application development
I didn't want to unilaterally implement something without having a discussion about exactly what to do, as there are various design issues. The Haskell Workshop paper advocates one particular point in the design space, and I think the point it occupies is a local maximum for various reasons, but it's not 100% clear that this is the right thing for Haskell'. Cheers, Simon

Hello Simon, Friday, September 1, 2006, 5:05:42 PM, you wrote:
I don't think we need more extensions to do a reasonable job of extensible exceptions:
it can be used with ghc 6.4, or 6.6, or ...? some solution in this area, imho, is a must for serious application development
I didn't want to unilaterally implement something without having a discussion about exactly what to do, as there are various design issues. The Haskell Workshop paper advocates one particular point in the design space, and I think the point it occupies is a local maximum for various reasons, but it's not 100% clear that this is the right thing for Haskell'.
but afai understood your idea don't require language changes? so it can be implemented as some library that can be used with 6.4, 6.6 and other ghc versions? moreover, although i don't yet read papers, i guess that extensible extensions can be implemented in the same way over any extensible/dynamic types. so imho your discussion don't make much sense - exceptions is just one of applications of such types and at current stage can be implemented only over Dynamic. when open types will be added to Haskell, they should be used for all current applications of Dynamic, including these exceptions -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (6)
-
Andres Loeh
-
Ashley Yakeley
-
Bulat Ziganshin
-
John Goerzen
-
Manuel M T Chakravarty
-
Simon Marlow