RFE: Extensible algebraic user-defined data types?

Hi, Is it possible to have such a feature in the future versions of the Haskell language? For example, there is an Either datatype which is Left a| Right b. Suppose I want to extend this datatype to the one including possibility of neither Left or Right (i. e. None). Currently I have to use Maybe Either, so my options are: Just (Left a) Just (Right b) Nothing If I could extend the Either datatype I might have (syntax may be different, this is just an example) data NEither a b = <Either a b> | None where datatype in angles is a parent datatype, and all its possible data constructors are included, and their list is extended with None. which gave me possibilities: Left a | Right b | None Probably I wouldn't expect to be able to reuse Nothing here (although I might want to) because Nothing already has been defined to be of the type Maybe. This is just a suggestion, that's why it is posted in the Cafe. PS Or is there a similar feature in the language already? Regarding reusing constructor names across several datatypes: is it possible to qualify them with their enclosing datatype name, like Maybe.Nothing where there is a name conflict? Then I might reuse Nothing in my hypothetical data type, and it would be NEither.Nothing if conflicting with Maybe.Nothing PPS I may be missing something again, as always ;) -- Dimitry Golubovsky Anywhere on the Web

On Thursday 28 April 2005 16:48, Dimitry Golubovsky wrote:
Is it possible to have such a feature in the future versions of the Haskell language?
For example, there is an Either datatype which is Left a| Right b.
Suppose I want to extend this datatype to the one including possibility of neither Left or Right (i. e. None). [...]
data NEither a b = <Either a b> | None
where datatype in angles is a parent datatype, and all its possible data constructors are included, and their list is extended with None.
which gave me possibilities: Left a | Right b | None
Surely NEitehr must be a different type than Either, since it allows the constructor None, whereas Either does not. But then we have two different types with overlapping constructor names. That means the type of Right "x" can no longer be infered: it could be one of {NEither String a, Either String a}, but which? Thus, in order to have such a feature, you have to drop complete type inference and instead allow subtyping. This has been studied to some extent, for instance in http://www.cs.chalmers.se/~nordland/ohaskell/ especially http://www.cs.chalmers.se/~nordland/ohaskell/survey.html#sect5 Unfortunately, O'Haskell is no longer being maintained, nor (or so it seems) is its successor Timber (http://www.cse.ogi.edu/pacsoft/projects/Timber/).
Probably I wouldn't expect to be able to reuse Nothing here (although I might want to) because Nothing already has been defined to be of the type Maybe.
This is just a suggestion, that's why it is posted in the Cafe.
PS Or is there a similar feature in the language already?
Not one I know of.
Regarding reusing constructor names across several datatypes: is it possible to qualify them with their enclosing datatype name, like Maybe.Nothing where there is a name conflict? Then I might reuse Nothing in my hypothetical data type, and it would be NEither.Nothing if conflicting with Maybe.Nothing
The problem is that you would either need to do this sort of qualification for all terms (i.e. loose type inference completely), or else loose the property that the inference engine always inferes the most general type. See the above link (the second one) for a detailed (but quite readable) discussion. Cheers, Ben

Benjamin Franksen writes:
On Thursday 28 April 2005 16:48, Dimitry Golubovsky wrote:
PS Or is there a similar feature in the language already?
Not one I know of.
The type-indexed co-products from Appendix C of the HList paper[1] are
along those lines, but probably not convenient enough for casual use.
For example,
data Left a = Inl a deriving (Typeable)
data Right a = Inr a deriving (Typeable)
data Nada = Nada deriving (Typeable)
type HEither a b = Left a :+: Right b :+: HNil
type HNEither a b = Nada :+: HEither a b
You can write functions which expect a TIC that contains Left a or Right
b, and they will accept TIC (HEither a b) and TIC (HNEither a b) without
modification.
The downside is that a function that might normally be typed "Either A B
-> C" now will have the type:
(HTypeIndexed l,
HTypeProxied l,
HOccurs (Proxy (Left A)) l,
HOccurs (Proxy (Right B)) l) =>
TIC l -> C
But it will accept a TIC (HEither A B) and a TIC (HNEither A B) and any
other TIC that contains Left A and Right B among its possible values.
[1] http://homepages.cwi.nl/~ralf/HList/
--
David Menendez

David Menendez wrote:
The downside is that a function that might normally be typed "Either A B -> C" now will have the type:
(HTypeIndexed l, HTypeProxied l, HOccurs (Proxy (Left A)) l, HOccurs (Proxy (Right B)) l) => TIC l -> C
But it will accept a TIC (HEither A B) and a TIC (HNEither A B) and any other TIC that contains Left A and Right B among its possible values.
Of course the compiler will infer this type for you. I find it very handy to use explicitly typed funtions to compose constraints, thus avoiding the need to have big type signatures... something like: constrainInt :: Int -> Int constrainInt = id constrainSomeClass :: SomeClass a => a -> a constrainSomeClass = id you can then write: f i c = someFn (constrainInt i) (constrainSomeClass c) Where "someFn" has a complicated type like that above... In this way you can avoid having to specify all the constraints a function, and it effectively gives you the same functionality as partial type signatures. Keean.

So many words about a simple thing? I wrote to Dimitry that subtyping in O'Haskell and Timber provides exactly what he wants: data Either a b = Left a | Right b data NEither > Either = None Why has this elegant concept not yet been implemented in standard Haskell? Peter
participants (5)
-
Benjamin Franksen
-
David Menendez
-
Dimitry Golubovsky
-
Keean Schupke
-
Peter Padawitz