Poll: System.exitWith behaviour

Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl
22 May 2001 17:57:28 GMT


Tue, 22 May 2001 17:30:39 +0100, Simon Marlow <simonmar@microsoft.com> pisze:

> Well, we could do a proper job of extensible data types, which
> probably isn't hard but is certainly a fair amount of work.

This would be IMHO the only right way, but I doubt that it's that
simple. For example it would be irritating that you can't extend
function definitions accepting values of extensible data types as
arguments; even (==) is problematic.

It's a pity that there is no direct translation of the OO style open
polymorphism. You can use an algebraic type, but it casts all variants
in stone; you can store extracted concrete-typed interface in function
closures, but it doesn't allow to cast down (retrieve the original,
more specific type); you can use existential quantification, with the
same limitations; you can use Dynamic, which is not nice to define
instances of, puts everything in one big bag, and doesn't provide
any hierarchy or extraction by partial matches.


I was recently thinking on a similar thing; it would not help
with exceptions though, only with MonadError-based exceptions and
extensible abstract syntax trees. The idea is to dualize my record
proposal by introducing overloaded constructors. It provides views
for free, i.e. allows having pattern matching on abstract types
with programmer-defined semantics.

Details aren't finished yet, but I imagine something like this:

data HsExp e n l p = variant -- I like layout :-)
    -- The proposal doesn't eliminate the need to have type parameters
    -- here and close the recursion on types later :-(
    Var n
    Con n
    Literal l
    App e e
    etc.

This introduces overloaded constructors:
    HsVar   :: (e > Var n) => n -> e
    Con     :: (e > Con n) => n -> e
    Literal :: (e > Literal l) => l -> e
    App     :: (e > App e1 e2) => e1 -> e2 -> e
and instances:
    instance HsExp e n l p > Var n
    instance HsExp e n l p > Con n
    instance HsExp e n l p > Literal l
    instance HsExp e n l p > App e e

A class of the form 't > C t1 t2' allows to create values of type t by
applying the constructor C to values of types t1 and t2, and pattern
match on values of type t using the constructor C with arguments of
types t1 and t2.

In another module you can reuse the same constructor names (they
don't collide as long as the arity is the same). You can also inherit
constructors from other types, similarly as in my records:

data GhcExp e n l p = variant
    Haskell98Exp :: HsExp e n l p
    Haskell98Exp (Var, Con, Literal, App, etc.)
        -- This creates forwarding instances of the appropriate
        -- classes, so Var etc. can be used with GhcExp too.
        -- Using the constructor Haskell98Exp expresses explicit
        -- subtyping/supertyping coercions.
    UnboxedTuple [e]
    CCall String [e]

And you can define such instances yourself:

instance PackedString > Nil where
    -- Construction:
    (Nil) = nilPs -- Needs a better syntax. This *defines* Nil.
    
    -- Pattern matching:
    s | nullPs -> Nil
        -- Matching failure here (because of a failed guard)
        -- means that the given value is not considered Nil.

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK