Re: Existential types: want better syntactic support (autoboxing?)

2006-02-06 Thread Ashley Yakeley

John Meacham wrote:

every single parameter type class whole parameter is of kind * 
class Foo a where


automatically declares a data type defined as

data Foo = exists a . Foo a = Foo_ a   
(where Foo_ is some internal, non user accessable name)


and an instance

instance Foo Foo where
method (Foo_ x) = method x 
...


I don't much like this, it seems like unnecessary sugar to me. My first 
preference would be not to do this at all.


My second preference would be to do this a bit more generally:

every type class
class Foo a b c where

automatically declares a data type defined as

data Foo t = exists a b c . Foo a b c = Foo_ (t a b c)
(where Foo_ is some internal, non user accessable name)

every single parameter type class whole parameter is of kind *
declares an instance

instance Foo (Foo Identity) where
 method (Foo_ x) = method x
 ...

It's still pretty ugly. I don't like special-casing classes that happen 
to have a particular kind signature.


--
Ashley Yakeley

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Existential types: want better syntactic support (autoboxing?)

2006-02-01 Thread S.J.Thompson

The wiki page

 
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/ExistentialQuantification

has been updated to reflect the discussion on existentials.

Simon T.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-31 Thread Duncan Coutts
On Tue, 2006-01-31 at 13:59 +0100, Wolfgang Jeltsch wrote:
 Am Montag, 30. Januar 2006 19:02 schrieb Duncan Coutts:
  [...]
 
  I have often thought that it would be useful to have an existential
  corresponding to a class.
 
 How would this work with multi-parameter classes, constructor classes, etc.? 
 If you propose something that only works in conjunction with a special kind 
 of classes I would hesitate to include such thing in a Haskell standard.

As John Mecham said it'd be for single parameter type class with a
parameter of kind *.

But you're probably right that people should get more experience with
using this technique before giving special support in the language to
make it convenient.

As Bulat noted we can already use this construction:

class (Monad m) = Stream m h | h-m where
vClose :: h - m ()
vIsEOF :: h - m Bool
.

data Handle = forall h . (Stream IO h) = Handle h

instance Stream IO Handle where
vClose(Handle h) = vCloseh
vIsEOF(Handle h) = vIsEOFh
.

But we have to give the name of the most general instance a different
name to the class which is rather inconvenient.

So perhaps we should start with allowing a class a data type to have the
same name and in a future standard think about making it easy to define
Bulat's Handle instance above with a short hand like:

class (Monad m) = Stream m h | h-m where
vClose :: h - m ()
vIsEOF :: h - m Bool
.
  deriving data Stream


I have to say though that I am surprised that us Haskell folk are not
more interested in making it easy or even possible to have abstract
values accessed via interfaces. Classes make it easy and elegant to have
type based dispatch but for the few times when value based dispatch
really is necessary it's a pain. The fact that we've suffered with a
non-extensible abstract Handle type for so long is an example of this.

Duncan

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-30 Thread Sebastian Sylvan
Seems like a convenient feature to me.

Also, you may want to have a function which works on a list of any
values which are both readable and showable.
Say (mockup syntax):

foo :: Show a, Read a = [a]
foo = [ 1, True, myRocketLauncher ]

Which would create a newtype called ShowReadAble or something with
extistential types and also instantiate that type in both Show and
Read.

I do agree that this is something I'd like in a lot of cases, and it
probably would be used quite a bit more if it were convenient (and
standardised!).

I leave it to someone else to figure out how to make this play nice
with e.g. type inference.

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-27 Thread Johannes Waldmann
S.J.Thompson wrote:
 Johannes - thanks for the pointer to this posting; would you have a
 concrete proposal to make on the basis of this for Haskell'?

Sort of an idea, but not fully worked out.

Referring to
http://www.haskell.org//pipermail/haskell-cafe/2005-June/010516.html
I think I want to use exactly this implementation (class Figure, data
EFigure) but hide the existence of EFigure (on the type level
and on the data level) completely, by some syntax.


E. g. a list of Figures could be written as [ Figure ], using the class
name as a type name (for the special case where the class is unary).
(This is what the Java people do but I am not sure whether this is
a good idea in the Haskell context. Mixing types and classes, hm.)


Also, when constructing objects of type EFigure, as in

box :: Size - EFigure ; box s = EFigure $ Box { ... }

I want to omit the constructor EFigure,
and the function should just read

box :: Size - Figure ; box s = Box { ... }

This is the auto-boxing I was referring to in the subject of this mail.
(We don't need auto-unboxing as we can have instance Figure EFigure,
see the reference).

While this is auto-boxing of function results (i. e. on exports),
a more difficult question is, how should we do auto-boxing for
function arguments (i. e. on imports). Assume f :: Foo - Box
and g : Figure - Bar,  is  g ( f Foo )  OK? Probably yes,
by translating to  g ( EFigure ( f Foo ) ). But then what about
f2 :: Foo - [ Box ]  and  g2 :: [ Figure ] - Bar.
We would need  g2 . f2  translated to  g2 . fmap EFigure . f2
but of course at runtime, there should be no extra cost.


(I'll have one more comment which I send in a separate message
so that it shows up under its own header in the archive.)

Best regards,
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-26 Thread S.J.Thompson

Johannes - thanks for the pointer to this posting; would you have a
concrete proposal to make on the basis of this for Haskell'?

Regards

Simon Thompson

On Wed, 25 Jan 2006, Johannes Waldmann wrote:

 It is standard practice to hide implementation details,
 in particular, not publishing the type of an object,
 but just the interfaces that its type implements. We can do this
 with existential types but the notation feels clumsy. See my message
 http://www.haskell.org//pipermail/haskell-cafe/2005-June/010516.html

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime