Guy asks the following (non-stupid) Haskell question, which I reply to
below.  The question points out an area in the Haskell report that
seems to be unclear; and a place where it might be worthwhile to change
the design to be less conservative but more uniform.

Guy's question:


----- Begin Included Message -----

>From [EMAIL PROTECTED] Thu Feb 18 17:21:56 1993
From: Guy Steele <[EMAIL PROTECTED]>
Date: Thu, 18 Feb 93 12:20:44 EST
To: wadler <[EMAIL PROTECTED]>
Cc: [EMAIL PROTECTED]
Subject: Re: Stupid Haskell question
Cc: [EMAIL PROTECTED], [EMAIL PROTECTED], [EMAIL PROTECTED], 
    [EMAIL PROTECTED], [EMAIL PROTECTED], [EMAIL PROTECTED]


Haskell theoretically allows recursive datatypes.  But the following
example does not work (he said innocently).

    module Rec where

    data Unary a = Zero | Successor a

    f :: Unary z -> [Unary z]
    f x = [x, Successor x]

I think that the compiler ought to deduce the restriction
x::q  where  q = Unary q.  It ought to be okay for q to be Unary q
because "an algebraic datatype intervenes" (Haskell report, 4.2.2).

But the Glasgow compiler says

    "/users/lang1/gls/Haskell/monads/Rec.hs", line 6:
        Type variable "a" occurs within the type "Unary a".
        In a list expression: [x, Successor x]

and the Chalmers compiler says

    Errors:
    "/users/lang1/gls/Haskell/monads/Rec.hs", line 6, [63] unify1 (occurence)
        a
    and Unary a
     in  (:) A1_f ((:) (Successor A1_f) ([]))
     in f

Now everything is okay if I write

    module Rec where

    data Unary a = Zero | Successor (Unary a)

    f :: Unary z -> [Unary z]
    f x = [x, Successor x]

but I have reasons in my actual code (which is hairy--this is a
stripped-down example) not to force the data type to be recursive,
but to let the type analysis deduce it where necessary.  Am I foolish
to expect this?

--Guy


----- End Included Message -----

Phil's response:

Guy,

Haskell requires that `an algebraic datatype intervenes' in order that
all types can be written as a finite tree.  The type you refer to,

        q where q = Unary q,

is an infinite tree (though a finite graph).  If we intended to allow
such infinite solutions, we wouldn't need the restriction to algebraic
datatypes at all.  This suggests we should clear up the wording in the
Haskell report, so I've forwarded your question and this response to
the Haskell mailing list.

Why not allow cyclic types (i.e., any type expressible as a
finite graph)?  It turns out there is a unification algorithm
that works for finite graphs, so this is in theory possible.
But the intent of Haskell was to be a conservative design, so
we stuck with what we were familiar with.  Your example of
a place where cyclic types are useful provides an impetus
to step into the less familiar but more uniform territory.

Cheers,  -- P
  

Reply via email to