> > > (b) allow throwing and catching of dynamically typed values,
> > >     e.g. using an interface like the Hugs/ghc Dynamic library

[discussion of Dynamic library, etc deleted]

[The following is a bit of a straw-man: it doesn't quite work but
may have good parts which can be used in other designs.]

(part of) Another approach is to extend Haskell with extensible
datatypes as is done in ML.  This is what I did in the late,
unlamented GreenCard 1 - you could define a new IOError constructor
whenever you wanted.  

This was easy to do because GreenCard 1's implementation exploited the
fact that it had full access to Hugs' internal data structures.  When
we moved onto GreenCard 2 and had to add GHC support, this was no
longer such an easy choice and we reluctantly switched to encoding
errors as strings.

If Haskell supported extensible datatypes, it would be easy to define a
hierarchy of exception values.  For example, the attached pseudocode
creates a hierarchy like this:

  IOError
    Win32Error
      GDIError
        BadRegion
        BadBrush
    PosixError
      ENOTDIR
      ENAMETOOLONG
      EINTR
    UserError
    AlreadyExists

Disadvantages of this approach include:

o Most Haskell features can be described as "just syntactic sugar"
  - it's hard to do this here.

o It's hard to write total functions over extensible datatypes (eg
  try writing a Show function for the attached definition of IOError).

o This is the only compelling use for extensible datatypes - wouldn't
  it be better to support exception handling more directly?



--
Alastair Reid        [EMAIL PROTECTED]        http://www2.cs.utah.edu/~reid/


module IO(...) where
  ...
  -- define the type
  extensible  IOError :: *  
  
  -- define some constructors
  constructor UserError     :: String   -> IOError  
  constructor AlreadyExists :: FilePath -> IOError
  

module Posix(...) where   -- Posix Stuff

  import IO(IOError)

  -- define a new hierarchy of errors
  extensible  PosixError :: *

  -- link the new hierarchy into IOError
  constructor PosixError :: PosixError -> IOError

  -- define some Posix errors
  constructor ENOTDIR      :: FilePath -> PosixError
  constructor ENAMETOOLONG :: FilePath -> PosixError
  constructor EINTR        :: PosixError
  ...


module Win32(...) where   -- Windows 95/98/NT stuff

  import IO(IOError)

  -- define a new hierarchy of errors
  extensible  Win32Error :: *

  -- link the new hierarchy into IOError
  constructor Win32Error :: Win32Error -> IOError



module Win32GDI(...) where   -- Windows graphics primitives

  import Win32(Win32Error)

  -- define a new hierarchy of errors
  extensible  GDIError :: *

  -- link the new hierarchy into IOError
  constructor GDIError :: GDIError -> Win32Error

  -- define some GDI errors
  constructor BadRegion :: HREGION -> GDIError
  constructor BadBrush  :: HBRUSH  -> GDIError
  ...



Reply via email to