Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2001-01-08 Thread Tom Pledger

Marcin 'Qrczak' Kowalczyk writes:
 [...]
  My new record scheme proposal does not provide such lightweight
  extensibility, but fields can be added and deleted in a controlled
  way if the right types and instances are made.

Johan Nordlander must be on holiday or something, so I'll deputise for
him.   :-)

O'Haskell also has add-a-field subtyping.  Here's the coloured point
example (from http://www.cs.chalmers.se/~nordland/ohaskell/survey.html):

   struct Point =
  x,y :: Float

   struct CPoint  Point =
  color :: Color

Regards,
Tom

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2001-01-05 Thread Peter Douglass

Julian Assange wrote (Dec 28, 2000):

 This is why all non S-exp like lanaguage are doomed to progressive
 syntactic cancer as the useful parts of operator name space and syntax
 space become progressively polluted and mutated by one fad after
 another.

Could you expand on this? I would think that all languages have identifies
that, through common usage become standardized, and that this meaning
becomes a de-facto part of the language.  Do you feel that this has not
happened in Lisp/Scheme?

--PeterD

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2001-01-05 Thread Julian Assange

Peter Douglass [EMAIL PROTECTED] writes:

 Julian Assange wrote (Dec 28, 2000):
 
  This is why all non S-exp like lanaguage are doomed to progressive
  syntactic cancer as the useful parts of operator name space and syntax
  space become progressively polluted and mutated by one fad after
  another.
 
 Could you expand on this? I would think that all languages have identifies
 that, through common usage become standardized, and that this meaning
 becomes a de-facto part of the language.  Do you feel that this has not
 happened in Lisp/Scheme?

The identifier space in lisp/scheme has wide tree depth and is
(essentially) lexically scoped. Infix operator identifiers in other
languages are the antithesis of this. It could be argued, both fairly
and unfairly, that the verbosity of S-exp bracketing leaves short
identifiers less desirable than they otherwise would be, however
tree-width arguments remain.

Polution of syntax space is a more difficult problem. As new syntactic
axioms are intruded, they should remain consistant with the existing
syntax elements. This poses ever increasing restraint on the evolution
of the language. New syntax elements appear less intuitive and more
arbitary in an attempt to fit in with the morass of ever increasing
restraints. If these restraints are not honnored, the language becomes
inconsistant. Eventually the language is guarenteed to become either
inconsistant or moribund as the number of interactions between
language elements overwhelms a language designers attempts understand
them.

The same is even more true of language semantics. The trouble lays in
finding initial axioms which can cleave large sections of future
concept space between them.

--
 Julian Assange|If you want to build a ship, don't drum up people
   |together to collect wood or assign them tasks and
 [EMAIL PROTECTED]  |work, but rather teach them to long for the endless
 [EMAIL PROTECTED]  |immensity of the sea. -- Antoine de Saint Exupery

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2001-01-03 Thread Stefan Karrmann

A syntax to choose the active instances may be useful, too.

E.g.:

use EccenticOrd, SetCollection in exp

then in exp the instances  EccenticOrd, SetCollection are known (or preferred).
This is similiar to the open syntax in Cayenne.

-- 
Stefan Karrmann

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2000-12-30 Thread Marcin 'Qrczak' Kowalczyk

Fri, 29 Dec 2000 00:37:45 -0800, John Meacham [EMAIL PROTECTED] pisze:

 http://www.cse.ogi.edu/~mpj/pubs/lightrec.html

I've read it and posted some comments in February 2000. There was no
answer AFAIR. Here are they again, slightly edited and extended:

I don't understand why to separate kinds of rows and record types,
instead of having "a type which is known to be a record type", at
least on the level visible for the programmer. So instead of
type Pointr = (r | x::Int, y::Int)
type Colored  r = (r | c::Color)
type ColoredPoint r = Point (Colored r)
p :: {ColoredPoint()}
-- Point, Colored, ColoredPoint :: row - row
it would be
type Pointr = {r | x::Int, y::Int}
type Colored  r = {r | c::Color}
type ColoredPoint r = Point (Colored r)
p :: ColoredPoint()
-- Point, Colored, ColoredPoint :: recordType - recordType
-- where recordType is something like a subkind of *.



It is bad to require the programmers to think in advance that a type
is going to be subtyped, and write elaborated
type Point r = (r | x::Int, y::Int)
... {Point()} ...
instead of simpler
type Point = {x::Int, y::Int}
... Point ...
which is not extensible.



I got used to () as a unit type. It would be a pity to lose it.



A minor problem. If tuples are records, field names should be such
that alphabetic order gives the sequential order of fields, or have
a special rule of field ordering for names of tuple fields...



In general I don't quite like the fact that records are getting more
anonymous. Magical instances of basic classes? How inelegant.

If I want the record type to have an identity, it will have to be
wrapped in a newtype, so I must think at the beginning if I will ever
want to write specialized insances for it and then all the code will
depend on the decision. Currently a datatype with named fields has
both an identity and convenient syntax of field access. (And why
newtype is not mentioned in section 5.1?)

I like name equivalence where it increases type safety. Extensible
records promote structural equivalence.

Unfortunately the proposal seems to increase the number of
irregularities and inelegant rules...

If expr.Constructor for a multiparameter constructor yields a tuple,
then for an unary constructor it should give a 1-tuple, no? I know
it would be extremely inconvenient, especially as newtypes are more
used, so I don't propose it, but it is getting less regular. What
about nullary constructors - empty tuple? :-)

I don't say that I don't like the proposal at all, or that I never
wanted to have several types with the same field names. But it is
not clean for me, it's a compromise between usability and elegance,
and from the elegance point of view I like current records more.

Maybe it would be helpful to show how to translate a program with
extensible records to a program without them (I guess it's possible
in a quite natural way, but requires global transformation of the
whole program).



Extensible records makes a syntactic difference between field access
and function call. So if one wants to export a type abstractly or
simply to provide functions operating on it without fixing the fact
that they are physically fields, he ends in writing functions like

size:: MyRecord - Int
size x = x.MyRecord.size

which are unnecessary now, even if size is simply a field.

It reminds me of C++ which wants us to provide methods for accessing
data fields (for allowing them to be later redefined as methods,
and for allowing everything to be uniformly used with "()" after the
feature name). Ugh.



My new record scheme proposal does not provide such lightweight
extensibility, but fields can be added and deleted in a controlled
way if the right types and instances are made.

The distinction between having a field and having a supertype is
blurred. Similarly between having itself a field called foo and having
a supertype which has a field called foo. Similarly between creating
a record by adding fields to another record and creating a record by
putting another record as one of fields. Similarly between casting
to a supertype by removing some fields and extracting the supertype
represented by a field.

An advantage is that the interface of records does not constrain the
representation in any way. It's up to how instances are defined,
with the provision of natural definitions for records implemented
physically as product types.

For example supplying a color for a colorless point and the reverse
operation can be written thus:
addColor :: (Record cp, cp.point :: p, cp.color :: Color)
 = p - Color - cp
addColor p c = record point = p; color = c

removeColor :: (cp.point :: p) = cp - p

Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2000-12-29 Thread John Meacham

I also like the approach of generalizing the record system, although I
have not evaluated your particular proposal. Speaking of record
improvements why is 
http://www.cse.ogi.edu/~mpj/pubs/lightrec.html
not listed on the future of haskell page? has it already been determined
to not be in the future of haskell or has no one gotten around to it?
Does anyone else read this proposal and drool? 

Speaking of this proposal does anyone else see parallels between the
lightweight modules proposal and the implicit parameters proposal
http://www.cse.ogi.edu/~jlewis/implicit.ps.gz as implemented in ghc.

in particular implicit parameters seem like they would be able to be
implemented as syntatic sugar on the lightweight module system,

one could rewrite implicit parameters as every function taking a record
which we can call 'imp' now '?foo' can be rewritten as 'imp.foo' and the
'with ?foo = 1' construct can be rewritten as nimp = {imp | foo := 1}
and then passing nimp to all called functions. I have not thought this
too far thorough so I could be missing something obvious but I think it
shows potential at least for the unification of two popular extensions. 

and I am pretty sure this was too obvious to mention in the lightweight
records paper but the section of (.foo) being equivalent to 
(\{_|foo=v} - v) seems appropriate.

John

-- 
--
John Meacham   http://www.ugcs.caltech.edu/~john/
California Institute of Technology, Alum.  [EMAIL PROTECTED]
--

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2000-12-28 Thread Julian Assange

George Russell [EMAIL PROTECTED] writes:

 I'm writing, but that shouldn't be too hard to tweak.  In particular I have
 followed SML in using "." to express qualification by something, even though
 Haskell already used "." for something else, because I can't be bothered right
 now to dig up a better symbol.

This is why all non S-exp like lanaguage are doomed to progressive
syntactic cancer as the useful parts of operator name space and syntax
space become progressively polluted and mutated by one fad after
another.

--
 Julian Assange|If you want to build a ship, don't drum up people
   |together to collect wood or assign them tasks
 [EMAIL PROTECTED]  |and work, but rather teach them to long for the endless
 [EMAIL PROTECTED]  |immensity of the sea. -- Antoine de Saint Exupery

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2000-12-26 Thread Marcin 'Qrczak' Kowalczyk

Tue, 26 Dec 2000 12:10:55 +1100, Fergus Henderson [EMAIL PROTECTED] pisze:

 Mercury's module system allows instance declarations (which, as in
 Haskell 98, are unnamed) to be selectively exported.

If they could be selectively exported in Haskell, how to make it
compatible with the current assumption that they are exported by
default? Selective hiding would be weird.

Perhaps there should be a separate section for exporting instances.
If not present, then everything is exported (as with plain module
contents).

I hope selective export would help with resolving conflicting
instances. There might be a confusion if a function does indeed
get a sorted list of objects of type T but it expected a different
ordering, but the danger of inability of linking two independent
libraries due to an innocent overlapping instance might be worse.

As we are at it, it would be nice to be able to specify signatures and
other interface details where they belong - in the export list. With
a different syntax of the export list; there would be an ambiguity if
..., var1, var2 :: Type, ...
gives Type to both variables or only one, and items should be
separated by layoutable semicolons.

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2000-12-25 Thread Fergus Henderson

On 21-Dec-2000, George Russell [EMAIL PROTECTED] wrote:
 (3) Finally it would be nice to extend the module syntax to allow named
 instances to be selectively exported and imported, just like variables.  

Mercury's module system allows instance declarations (which, as in
Haskell 98, are unnamed) to be selectively exported.

:- module foo.
:- interface.

:- import_module enum.

:- type t.
:- instance enum(t).

:- implementation.

:- instance enum(t) where [ ... ].

Mercury doesn't directly support selective import -- you can only
import a whole module, not part of it.  But if you really want that
you can achieve it by putting each instance declaration in its own
nested module.

:- module foo.
:- interface.
:- import_module enum.

   :- type t.

   :- module enum_t.
   :- interface.
   :- instance enum(t).
   :- end_module enum_t.

:- implementation.

   :- module enum_t.
   :- implementation.
   :- instance enum(t) where [ ... ].
   :- end_module enum_t.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
|  of excellence is a lethal habit"
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2000-12-24 Thread Marcin 'Qrczak' Kowalczyk

Thu, 21 Dec 2000 21:20:46 +0100, George Russell [EMAIL PROTECTED] pisze:

 So if you agree with me up to here, perhaps you are agreed that it is worth
 while trying to find a middle way, in which we try to combine both approaches.

I am thinking about a yet different approach. Leave classes and SML
structures as they are, and make *records* more flexible, to be used
instead of classes if instances are to be manipulated explicitly,
and instead of structures if we are using Haskell rather than SML
or OCaml, and instead of objects if we are using Haskell rather than
some OO language, and as a general way of expressing things behaving
like fixed dictionaries of values.

I have yet to play more with it. I already have some thoughts and
a working preprocessor which translates my extensions to Haskell
(with multi-parameter classes and fundeps).

 GOALS 

* Replace the current record mechanism with a better one.

* Don't require sets of fields of different record types disjoint. It's
  not only to avoid inventing unique field names, but also to have
  functions polymorphic over all records containing specific fields
  of specific types.

* Provide a way to specialize existing record types to new types that
  behave similarly except of small changes. I.e. kind of inheritance.

* Since Haskell does not have subtyping, have coercions up the
  inheritance tree. Overloading functions on record types is not
  always enough, e.g. to put records in a heterogeneous collection
  they must be coerced to a common type.

* Don't constrain the implementation of field access for different
  record types. As long as it behaves like a record, it is a record.

* Don't constrain the implementation of methods even for the same
  record type. Since Haskell does not have subtyping, records which
  would have different types in other languages can have the same
  type in Haskell, as long as the same interface suffices.

* Express keyword parameters of functions. A function might use many
  parameters refining its behavior which usually have some default
  values. Old code using that function must not break when more
  parameters are added.

* A piece of code should be understandable locally, independently
  of definitions and instances present elsewhere.

* Have a nice syntax.

* Keep it simple and easily translatable to the core language.

Fields and methods are really the same thing. Moreover, inheritance is
really delegation and coercions are the same things as field accesses
as well.

Record types are not anonymous, unlike TREX. Field names are born
implicitly and live in a separate namespace. Each field name is
associated with a class of record types having that field. Instances
of these classes are defined implicitly for types defined as records,
but can also be given explicitly for any type.

 FIELD SELECTION 

A field selection expression of the form
expr.label
is equivalent to
(.label) expr
where
(.label) :: (r.label :: a) = r - a
is an overloaded selector function.

(rec.label:: a) is a syntax for Has_label rec a, where Has_label is
the implicitly defined class for this label. Such class would look
like this if it were defined as normal classes:
class Has_label r a | r - a where
(.label)  :: r - a
set_label :: r - a - r
except that there are no real names Has_label nor set_label.

 DEFINITION OF RECORD TYPES 

The definition of a record type:
data Monoid e = record
zero :: e
plus :: e - e - e
defines the appropriate single-constructor algebraic type and
obvious instances:
instance (Monoid e).zero :: e   where ...
instance (Monoid e).plus :: e - e - e where ...

We can construct values of this type thus:
numAddMonoid :: Num e = Monoid e
numAddMonoid = record
zero = 0
plus = (+)

The meaning of such overloaded record creation expressions will be
specified later.

 INHERITANCE 

Here is another example of a record type definition:
data Group e = record
monoid :: Monoid e
minus  :: e - e - e
neg:: e - e
monoid (zero, plus)
x `minus` y = x `plus` neg y
neg y   = zero `minus` y

This record type has three direct members: monoid, minus, and neg.
monoid holds its zero and plus.

We want to be able to extract zero and plus of a group directly,
instead of going through the underlying monoid. We could define
appropriate instances:
instance (Group e).zero :: e   where ...
instance (Group e).plus :: e - e - e where ...
and this is what the inheritance declaration
monoid (zero, plus)
does automatically for us.

So groups too have zero and plus, which are deleagated to the monoid.
Seen from outside, these fields are indistinguishable from proper
Group's fields.

 DEFAULT DEFINITIONS 

minus and