Re: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-16 Thread ozone
On 11/09/2003, at 9:46 PM, Simon Marlow wrote:

I know that some of these problems can be addressed, at least in
part, by careful use of Makefiles, {-# custom pragmas #-}, and perhaps
by committing to a single tool solution.  But I'd like to propose
a new approach that eliminates some of the command line complexities
by integrating the selection of language extensions more tightly
with the rest of the language.
Initially I liked the idea, but now I'm not so sure (more about that
later). But first I'll point out that the situation isn't nearly as bad
as you make out.  In GHC, the approved way to add these flags is by
using a pragma to the source code, for example:
  {-# OPTIONS -fth -fffi #-}
  module Foo where
  ...
this in itself addresses most of your complaints.  Using a
compiler-independent syntax would address another one.  We're left 
with:
I'll second Simon on this suggestion.  I'm using {-# OPTIONS ... #-} 
pragmas on all my modules now, and it works great: no extra parameters 
need to be specified on the command-line, and I get only the extensions 
I want.  This seems to be more simple than the hierarchical module 
scheme, too.  (I'm a big fan of KISS.)

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-11 Thread Mark P Jones
| We at GHC HQ agree, and for future extensions we'll move to 
| using separate options to enable them rather than lumping 
| everything into -fglasgow-exts.  This is starting to happen 
| already: we have -farrows, -fwith, -fffi (currently implied 
| by -fglasgow-exts).
| 
| Of course, if we change the language that is implied by 
| -fglasgow-exts now, we risk breaking old code :-)  Would folk 
| prefer existing syntax extensions be moved into their own 
| flags, or left in -fglasgow-exts for now?  I'm thinking of:
| 
|   - implicit parameters
|   - template haskell
|   - FFI
|   - rank-N polymorphism (forall keyword)
|   - recursive 'do' (mdo keyword)


Haskell gets pulled in many different directions to meet the needs
and whims of developers, researchers, and educators, among others.
For quite a long time, it seemed that the choice between Standard
Haskell 98 and Kitchen Sink Haskell with all the extras was
adequately dealt with using a single command line option.  Those
looking for the stability of Haskell 98 got what they wanted by
default, while the adventurers looking to play with all the new
toys just added an extra -fglasgow-exts or -98 or ... etc.

As the number of extensions grows (and the potential for unexpected
interactions), it is clear that we can't get by with that simple
scheme any more.  It's important that implementations continue to
provide the stable foundation, but people also need a more flexible
way to select extensions when they need them.

As a solution to that problem, the many-command-line-options
scheme described seems quite poor!  It's far too tool specific,
not particularly scalable, and somewhat troublesome from a software
engineering perspective.  We're not talking about a choice between
two points any more; there's a whole lattice of options, which, by
the proposal above might be controlled through a slew of tool-specific
and either cryptic or verbose command line switches.  Will you
remember which switches you need to give to compile your code for
the first time in two months?  How easy will it be to translate
those settings if you want to run your code through a different
compiler?  How much help will the compiler give you in tracking
down a problem if you forget to include all the necessary switches?
And how will you figure out what options you need to use when you
try to combine code from library X with code from library Y, each
of which uses its own interesting slice through the feature set?

I know that some of these problems can be addressed, at least in
part, by careful use of Makefiles, {-# custom pragmas #-}, and perhaps
by committing to a single tool solution.  But I'd like to propose
a new approach that eliminates some of the command line complexities
by integrating the selection of language extensions more tightly
with the rest of the language.

The main idea is to use the module system to capture information
about which language features are needed in a particular program.
For example, if you have a module that needs implicit parameters
Template Haskell, and TREX, then you'll indicate this by including
something like the following imports at the top of your code:

  import Extensions.Types.ImplicitParams
  import Extensions.Language.TemplateHaskell
  import Extensions.Records.TREX

Code that needs recursive do, O'Haskell style structs, rank-n
polymorphism, and multiple parameter classes might specify:

  import Extensions.Language.Mdo
  import Extensions.Records.Structs
  import Extensions.Types.RankN
  import Extensions.Types.Multiparam

Imports are always at the top of a module, so they're easy to
find, and so provide clear, accessible documentation.  (Don't
worry about the names I've picked here; they're intended to
suggest possibilities, but they're not part of the proposal.)

What, exactly is in those modules?  Perhaps they just provide
tool-specific pragmas that enable/disable the corresponding
features.  Or perhaps the compiler detects attempts to import
particular module names and instead toggles internal flags.
But that's just an implementation detail: it matters only to the
people who write the compiler, and not the people who use it.
It's the old computer science trick: an extra level of indirection,
in this case through the module system, that helps to decouple
details that matter to Haskell programmers from details that
matter to Haskell implementers.

Of course, code that does:

  import Extensions.Types.Multiparam

is not standard Haskell 98 because there's no such library in the
standard.  This is a good thing; our code is clearly annotated as
relying on a particular extension, without relying on the command
line syntax for a particular tool.  Moreover, if the implementers
of different tools can agree on the names they use, then code that
imports Extensions.Types.Multiparam will work on any compiler that
supports multiple parameter classes, even if the underlying
mechanisms for enabling/disabling those features are different.
When somebody 

Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-11 Thread Koen Claessen
Karl-Filip Faxen wrote:

 | Yes, things are clearer and I rather like the idea.
 | The only thorny issue is that the update function for
 | field 'wibble' is formed from but not equal to the
 | field name itself.

This could be solved by having an abstract type Field
thusly (*):

  type Field r a

  set :: r - Field r a - a - r
  get :: r - Field r a - a

The example would then look like:

  class Wibble r where
wibble :: Field r Int
wobble :: Field r String

  data Foo =
MkFoo{ wibble :: Int
 , wobble :: String
 }
deriving Wibble

What do you think of this?

The type Field can be implemented as:

  data Field r a = MkField (r - a - r) (r - a)

  set rec (MkField f _) x = f rec x
  get rec (MkField _ g)   = g rec

Regards,
/Koen



(*) I prefer the following operators but I realize that
there are other people who are less fond of binary operator
symbols :-)

  type Field r a
  type Setting r

  (=:) :: Field r a - a - Setting r
  (!)  :: r - Setting r - r
  (?)  :: r - Field r a - a

Such that selecting the field wibble from a record rec would
look like:

  rec ? wibble

And setting the field wibble from the record rec to the
value val would look like:

  rec ! wibble =: val

The last should parse as:

  rec ! (wibble =: val)

/K


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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-11 Thread Robert Ennals
 Karl-Filip Faxen wrote:
 
  | Yes, things are clearer and I rather like the idea.
  | The only thorny issue is that the update function for
  | field 'wibble' is formed from but not equal to the
  | field name itself.
 
 This could be solved by having an abstract type Field
 thusly (*):

[snip]

All very cute :-))

The downside is of course that it would no longer be a compatible extension to 
the existing Haskell language.

Current Haskell programs consider the field name to be a function from types 
to field values. If we are to retain compatibility then we need to preserve 
this.


Still very cute though :-)


[snip]


-Rob

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


RE: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-11 Thread Simon Marlow

Mark Jones writes: 
 As a solution to that problem, the many-command-line-options
 scheme described seems quite poor!  It's far too tool specific,
 not particularly scalable, and somewhat troublesome from a software
 engineering perspective.  We're not talking about a choice between
 two points any more; there's a whole lattice of options, which, by
 the proposal above might be controlled through a slew of tool-specific
 and either cryptic or verbose command line switches.  Will you
 remember which switches you need to give to compile your code for
 the first time in two months?  How easy will it be to translate
 those settings if you want to run your code through a different
 compiler?  How much help will the compiler give you in tracking
 down a problem if you forget to include all the necessary switches?
 And how will you figure out what options you need to use when you
 try to combine code from library X with code from library Y, each
 of which uses its own interesting slice through the feature set?
 
 I know that some of these problems can be addressed, at least in
 part, by careful use of Makefiles, {-# custom pragmas #-}, and perhaps
 by committing to a single tool solution.  But I'd like to propose
 a new approach that eliminates some of the command line complexities
 by integrating the selection of language extensions more tightly
 with the rest of the language.

Initially I liked the idea, but now I'm not so sure (more about that
later). But first I'll point out that the situation isn't nearly as bad
as you make out.  In GHC, the approved way to add these flags is by
using a pragma to the source code, for example:

  {-# OPTIONS -fth -fffi #-}
  module Foo where
  ...

this in itself addresses most of your complaints.  Using a
compiler-independent syntax would address another one.  We're left with:

 How much help will the compiler give you in tracking
 down a problem if you forget to include all the necessary
 switches?

We don't make any attempt to address this, but there are various ways we
could be more helpful: eg. finding a stray 'forall' in a type when
rank-N is not turned on is a clear indication.  Nevertheless, this seems
orthogonal to the issue of how to specify the language flavour in the
first place.

 And how will you figure out what options you need to use when you
 try to combine code from library X with code from library Y, each
 of which uses its own interesting slice through the feature set?

Interesting point.  Our take on this is that the extension-flags specify
the language variant in which the source code *in this module* is
written.  For example, if I define a multi-parameter type class C in
module A, then it is completely legal to import A into any other module
regardless of the settings of the flags, but I will only be able to
write an instance of C if multi-parameter type classes are enabled.

This is a consistent position which has the benefit of being easy to
understand.

 The main idea is to use the module system to capture information
 about which language features are needed in a particular program.
 For example, if you have a module that needs implicit parameters
 Template Haskell, and TREX, then you'll indicate this by including
 something like the following imports at the top of your code:
 
   import Extensions.Types.ImplicitParams
   import Extensions.Language.TemplateHaskell
   import Extensions.Records.TREX

How do I enable hierarchical modules using this scheme? ;-)

Can any of these extensions affect the syntax of the export list?  If
so, how do I parse the module?  (perhaps I have to use a most-general
syntax for the export list, parse up to and including the imports, then
re-parse the export list).

[snip]
 Of course, code that does:
 
   import Extensions.Types.Multiparam
 
 is not standard Haskell 98 because there's no such library in the
 standard.  This is a good thing; our code is clearly annotated as
 relying on a particular extension, without relying on the command
 line syntax for a particular tool.  Moreover, if the implementers
 of different tools can agree on the names they use, then code that
 imports Extensions.Types.Multiparam will work on any compiler that
 supports multiple parameter classes, even if the underlying
 mechanisms for enabling/disabling those features are different.
 When somebody tries to compile that same piece of code using a
 tool that doesn't support the feature, they'll get an error
 message about a missing import with a (hopefully) suggestive
 name/description, instead of a cryptic Syntax error in constraint
 or similar.

This complaint is also addressed by using a compiler-independent pragma,
except the error message would be unsupported extension.

 Also, when you come back to compile your code after some
 time away, you won't need to remember which command line options you
 need because it's all there, built in to the source in a readable and
 perhaps even portable notation. You just invoke the compiler (without
 

RE: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-11 Thread Magnus Carlsson
Mark P Jones writes an interesting suggestion:
 ...
  Hmm, ok, but perhaps you're worrying now about having to enumerate
  a verbose list of language features at the top of each module you
  write.  Isn't that going to detract from readability?  This is where
  the module system wins big!  Just define a new module that imports all
  the features you need, and then allows you to access them by a single
  name.  For example, you could capture the second feature set above
  in the following:
  
module HackersDelight where
import Extensions.Language.Mdo
import Extensions.Records.Structs
import Extensions.Types.RankN
import Extensions.Types.Multiparam
  
  Now the only thing you have to write at the top of a module that
  needs some or all of these features is:
  
import HackersDelight
 ...

Neat!  But maybe it is not always desirable to impose an extension on
the client of a module, just because the module itself needs it.  If
extensions were a kind of entity that can be mentioned in export and
import lists, we could write

  module HackersDelight(mdo,structs,rankN,multiparam) where
  import Extensions.Language(mdo)
  ...

Now, familiar mechanisms can be used from the module system.  In
particular, we can encode Hal's example (all extensions except
Template Haskell):

  import HackersDelight hiding (th)

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


Re: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-11 Thread Iavor Diatchki
hello,

it's a pity i don't know how to get my mailer to reply to a few messages 
at once :-)

i also like mark's idea.  i know that ghc can alredy achive some of that 
with the OPTION pragmas, but i think it is nice if we can reuse what is 
already in the language rather than making programmers learn yet another 
construct.  reduce the cognitive overhead so to speak (i've wanted to 
use this phrase since i learned it in HCI class :-)

Magnus Carlsson wrote:
Mark P Jones writes an interesting suggestion:
 ...
  Hmm, ok, but perhaps you're worrying now about having to enumerate
  a verbose list of language features at the top of each module you
  write.  Isn't that going to detract from readability?  This is where
  the module system wins big!  Just define a new module that imports all
  the features you need, and then allows you to access them by a single
  name.  For example, you could capture the second feature set above
  in the following:
  
module HackersDelight where
import Extensions.Language.Mdo
import Extensions.Records.Structs
import Extensions.Types.RankN
import Extensions.Types.Multiparam
actually the way the module system works at the moment this sould 
probably be written as:

module HackersDelight (module A) where
import Extensions.Language.Mdo  as A
import Extensions.Records.Structs   as A
import Extensions.Types.RankN   as A
import Extensions.Types.Multiparam  as A
otherwise i would assume that the extensions only apply to the current 
module.

Neat!  But maybe it is not always desirable to impose an extension on
the client of a module, just because the module itself needs it.
i think with the above interpretation no extensions would be forced on a 
client, unless a module actually re-exports the extensions it used.

If extensions were a kind of entity that can be mentioned in export and
import lists, we could write
  module HackersDelight(mdo,structs,rankN,multiparam) where
  import Extensions.Language(mdo)
  ...
Now, familiar mechanisms can be used from the module system.  In
particular, we can encode Hal's example (all extensions except
Template Haskell):
  import HackersDelight hiding (th)
yes, this is nice. and i don't think it can be done if extnesions are 
modules (as mark suggested) rather than entities (as magnus suggested). 
 one thing to consider though is that if extensions are entities they 
can presumably be mentioned in expressions, etc.  one way to handle that 
is to introduce a new kind, e.g. something like:

mdo :: Extension :: ExtensionKind

an alternative (perhaps simpler) approach would be to have extensions 
live in another name space, so that they can't syntactically be placed 
in expressions, e.g. something like:
import HackersDelight hidning (#th)

bye
iavor
--
==
| Iavor S. Diatchki, Ph.D. student   |
| Department of Computer Science and Engineering |
| School of OGI at OHSU  |
| http://www.cse.ogi.edu/~diatchki   |
==
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Adrian Hey
On Wednesday 10 September 2003 04:54, Andrew J Bromage wrote:
 G'day all.

 On Tue, Sep 09, 2003 at 02:52:48PM +0200, Johannes Waldmann wrote:
  but this might be an issue for others, who have to maintain legacy
  code.

 You know a language has made it when we're talking about legacy code.

 On the other hand, you have to worry about a pure declarative language
 where support for anything legacy is a priority.  Just a little bit.

On reflection, I can think of one group of Haskellers who might get
a bit upset by such changes. If I'd written (or purchased) a text book
which was now full of obsoleted code examples I wouldn't be very happy.
But I guess it would be possible to do something too suit users of old
and new Haskell with suitably chosen pragmas or compiler switches without
too much difficulty.

Regards
--
Adrian Hey

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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Ketil Z. Malde
Iavor Diatchki [EMAIL PROTECTED] writes:

 Adrian Hey wrote:

 IMHO preserving the status quo wrt records should be low priority.
 It really doesn't bother me much if new (useful) language features break
 existing code. I think this is a better option than permanently
 impoverishing the language and/or forcing users to migrate their
 entire code to some other less impoverished language which may
 appear in the future.

 I also think that having backwards compatability is not much of an
 issue.  After all, ghc has introduces a  number of not backward
 compatable changes to haskell, and I never heard any complaints. 

Oh no?

Implicit parameters: I'm sure it is a great thing, but I'd already
used the (?) operator, and need -fglasgow-exts.  Now my program
depends on a bunch of well places spaces to compile.

Template Haskell: really cool new feature, which just happens to use
a syntax that overlaps with the list comprehension syntax.

And now, let's just screw any backwards compatibility, and re-engineer
the records system¹.

I don't need any of this, and it makes my life harder.  Are you guys
going to keep at it, until I regret ever using Haskell?  There was
recently a thread about using Haskell for something else than Haskell
compilers; well, if you actually want people to do this, then you
can't constantly keep changing the language.

-kzm

PS: For the record, I think the compiler developers are in general
doing a great job of augmenting the language *without sacrificing
backwards compatibility*.  But compatibility is important.  Branch GHC
and develop a new language instead!

-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Johannes Waldmann
What about ad-hoc overloading (allowing visible entities to share names,
as long as they can be distinugished by their typing).

This is orthogonal to the proper records issue (?)
but it might improve the current situtation (?)
and it seems backward-compatible (?)

Of course this would need an extension of the type checker
(but not in the interface files, since this kind of overloading
should only happen when using an name, not when defining it).
-- 
-- Johannes Waldmann  http://www.informatik.uni-leipzig.de/~joe/ --
-- [EMAIL PROTECTED] -- phone/fax (+49) 341 9732 204/209 --

.. ..  Viertes Leipziger Jongliertreffen, 17. - 19. Oktober 2003  .. ..
.. ..  http://www.informatik.uni-leipzig.de/~joe/juggling/vier/   .. ..

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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Ketil Z. Malde
Johannes Waldmann [EMAIL PROTECTED] writes:

 What about ad-hoc overloading (allowing visible entities to share names,
 as long as they can be distinugished by their typing).

 This is orthogonal to the proper records issue (?)
 but it might improve the current situtation (?)
 and it seems backward-compatible (?)

Yes.  Don't get me wrong; please go and define proper records,
improve the record system accordingly, adapt and implement. 

I just wanted to correct the impression that there were no complaints
about broken backwards compatibility.  Because it is - or at least, it
can be - a real problem.

Sometimes it has to be done in order to set things right, but it
shouldn't be done lightly.

There is also the issue of weighing down the language with features
and extensions.  It may give you more expressive power, but it also
makes the language harder to master, and programs more difficult to
maintain. 

 Of course this would need an extension of the type checker

Doesn't worry me overly, it is Somebody Else's Problem :-)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Robert Ennals

I'd like to add a voice of dissent here.

I would much prefer it if Haskell didn't add specific extensible records 
support - even if it could be done without breaking backwards compatibility.


This is because I believe that extensible records encourage poor style. They 
encourage people to expose the internal representation of their structures, 
allowing users to match on internal fields rather than using accessor 
functions.


One of the things that I like about the current Haskell record system is the 
fact that record selectors are functions. This means that, if I change the 
structure of a type, I can just replace the record selector with a normal 
function.


On a similar line of argument, one change that I think would be nice would be 
for record updaters to also be functions.

Then the following code

x {name1 = bla, name2 = blob}

would translate to the following:

set_name1 bla $ set_name2 blob $ x

This would allow record updates to be overridden in the same way that record 
selectors can be.



Perhaps the best way to get the record extensibility features that people seem 
to want would be to allow record selectors (and updaters) to be in type 
classes, just like other functions.



So in summary, here is my proposal:


No specific extensible records system.

Define record update to be a function just like record selection is.

Allow these functions to be in type classes.



-Rob



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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Karl-Filip Faxen
Hi!

 So in summary, here is my proposal:
 
 No specific extensible records system.
 
 Define record update to be a function just like record selection is.
 
 Allow these functions to be in type classes.

I do not understand the second and third point: As I understand your
idea, record selectors and updaters should still be defined by the
datatype declaration. What does it then mean that they be allowed
to be defined in type classes? Would that happen automatically?

Cheers,

   /kff



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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Robert Ennals
 Hi!
 
  So in summary, here is my proposal:
  
  No specific extensible records system.
  
  Define record update to be a function just like record selection is.
  
  Allow these functions to be in type classes.
 
 I do not understand the second and third point: As I understand your
 idea, record selectors and updaters should still be defined by the
 datatype declaration. What does it then mean that they be allowed
 to be defined in type classes? Would that happen automatically?

I was thinking of something along the following lines:


class Wibble a where
wibble :: a - Int
wobble :: a - String
set_wibble :: Int - a - a
set_wobble :: String - a - a


data Foo = Foo {wibble :: Int, wobble :: String}
deriving Wibble


The Wibble class defines selector and updater functions for fields called 
wibble and wobble.

When I define the datatype Foo, I give it fields called wibble and wobble, 
which will define the functions in Wibble. If I say deriving Wibble then the 
type system acknowledges that these functions are implementing the class 
Wibble. If I had not derived Wibble then there would have been a name clash.


We could imagine the definition of Foo being automatically desugared to the 
following:

data Foo = Foo Int String

instance Wibble Foo where
wibble (x,_) = x
wobbble (_,y) = y
set_wibble x (_,y) = (x,y)
set_wobble y (x,_) = (x,y)




Note that Wibble is a normal class. I could thus implement Wibble in a class 
that was not a record. For example, the following, rather dull, implementation:

instance Wibble () where
wibble () = 3
wobble () = hello
set_wibble _ _ = ()
set_wobble _ _ = ()


Does that make things clearer?



-Rob





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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Karl-Filip Faxen
Yes, things are clearer and I rather like the idea. The only
thorny issue is that the update function for field 'wibble'
is formed from but not equal to the field name itself.

In short, the magic thing would be in the 'deriving' clause:

If the data type declares fields with names x_1, ..., x_n
and the class mentioned declares operators y_1, ..., y_k
and set_y_1, ..., set_y_k where {y_1, ..., y_k} is a subset
of {x_1, ..., x_k}, of the appropriate types, then the
corresponding instance declarations are generated.

Cheers,

/kff


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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Robert Ennals
 Yes, things are clearer and I rather like the idea. The only
 thorny issue is that the update function for field 'wibble'
 is formed from but not equal to the field name itself.
 
 In short, the magic thing would be in the 'deriving' clause:
 
 If the data type declares fields with names x_1, ..., x_n
 and the class mentioned declares operators y_1, ..., y_k
 and set_y_1, ..., set_y_k where {y_1, ..., y_k} is a subset
 of {x_1, ..., x_k}, of the appropriate types, then the
 corresponding instance declarations are generated.

Yep. 

It would also be possible for a class to declare only the selector or only the 
updater for a field. E.g.:

class FooGet a where
foo :: a - Int

class FooSet a where
set_foo :: Int - a - a


data Bar = Bar {foo :: Int}
deriving (FooGet, FooSet)



-Rob



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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Ganesh Sittampalam
On Wed, 10 Sep 2003 10:26:04 +0100, Robert Ennals
[EMAIL PROTECTED] wrote:

class Wibble a where
wibble :: a - Int
wobble :: a - String
set_wibble :: Int - a - a
set_wobble :: String - a - a


data Foo = Foo {wibble :: Int, wobble :: String}
   deriving Wibble


The Wibble class defines selector and updater functions for fields called 
wibble and wobble.

When I define the datatype Foo, I give it fields called wibble and wobble, 
which will define the functions in Wibble. If I say deriving Wibble then the 
type system acknowledges that these functions are implementing the class 
Wibble. If I had not derived Wibble then there would have been a name clash.

What would you do if Wibble had more functions than just those 4? You'd need
somewhere to put the implementations of the other functions for Foo.

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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Ketil Z. Malde
Robert Ennals [EMAIL PROTECTED] writes:

[Heavy snippage, hopefully preserving semantics]

 data Foo = Foo {wibble :: Int, wobble :: String}
   deriving Wibble

 We could imagine the definition of Foo being automatically desugared to the 
 following:

 data Foo = Foo Int String

 instance Wibble Foo where
 wibble (x,_) = x
 wobbble (_,y) = y
 set_wibble x (_,y) = (x,y)
 set_wobble y (x,_) = (x,y)

Shouldn't that rather be:

class HasWibble a where
wibble :: a - Int
set_wibble :: a - Int - a

class HasWobble a where ...

data Foo = Foo Int String

instance HasWibble Foo where 
wibble (Foo x _) = x
set_wibble (Foo x y) z = Foo z y

instance HasWobble Fo where...

In order to let another record provide just a 'wibble' without a
'wobble'?

One danger of such an approach (implicit classes and instances) might
be non-intuitive error messages.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes:

 Robert Ennals [EMAIL PROTECTED] writes:

BTW, isn't this more or less exactly what Simon suggested (at the very
top of this thread)?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Tomasz Zielonka
On Wed, Sep 10, 2003 at 02:27:33PM +0200, Ketil Z. Malde wrote:
 
 Shouldn't that rather be:
 
 class HasWibble a where
 wibble :: a - Int
 set_wibble :: a - Int - a
 
 class HasWobble a where ...

Or even:

  class HasWibble a b | a - b where
  wibble :: a - b
  set_wibble :: a - b - a
 
  class HasWobble a b | a - b where ...

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Robert Ennals
 [EMAIL PROTECTED] (Ketil Z. Malde) writes:
 
  Robert Ennals [EMAIL PROTECTED] writes:
 
 BTW, isn't this more or less exactly what Simon suggested (at the very
 top of this thread)?

Not really, no.

I assume you mean the system suggested by Peter Thieman, outlined in the 
initial email by Henrik Nilsson.


My system has the following differences:


Record updaters become normal functions. (and recold selectors remain 
functions)

Normal type classes are used to implement them. 
(no magic has constraints)

Type classes are not magically inferred. They are manually declared just like
any other type class would be.



As I interpret it, the system proposed at the top of the thread treats record 
fields as something special, and I am very keen that this should not happen. I 
think that it is important that one should be able to replace a record field 
with accessor functions.


-Rob



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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Robert Ennals
 On Wed, Sep 10, 2003 at 02:27:33PM +0200, Ketil Z. Malde wrote:
  
  Shouldn't that rather be:
  
  class HasWibble a where
  wibble :: a - Int
  set_wibble :: a - Int - a
  
  class HasWobble a where ...
 
 Or even:
 
   class HasWibble a b | a - b where
   wibble :: a - b
   set_wibble :: a - b - a
  
   class HasWobble a b | a - b where ...

It can be.

The programmer can declare the type classes however they like.

It is important to note that type classes are NOT automatically generated in 
my proposal. The type classes I describe are bog standard normal type classes.

The only magic takes place when records are made instances of type classes, at 
which point the fields are translated into default instances.


-Rob

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


Re: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-10 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes:

 Of course, if we change the language that is implied by -fglasgow-exts now,
 we risk breaking old code :-)  Would folk prefer existing syntax extensions
 be moved into their own flags, or left in -fglasgow-exts for now?  I'm
 thinking of:
 
   - implicit parameters
   - template haskell
   - FFI
   - rank-N polymorphism (forall keyword)
   - recursive 'do' (mdo keyword)

The obvious approach is to do both (in exactly the manner of
{-fffi, -farrows, -fwith}), namely to introduce a separate flag
for each extension, but (temporarily) retain -fglasgow-exts as
a catch-all for the complete set.  Eventually, -fglasgow-exts
could disappear.

With this suggestion, I would certainly be in favour of separate
flags for existing extensions.

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


Re: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-10 Thread Hal Daume III
I agree with Malcolm, with the possible addition of:

  keep -fglasgow-exts as it is (or, even, perhaps continue making it the
add all extensions keyword).  also have -fffi, -farrows, -fth, etc. 
but also have, -fnoth and -fnoffi.  that way, if a lot of us have code
that uses all the extensions other than TH and have lots of code that
looks like (foo$bar), we can just to -fglasgow-exts -fnoth.

seems to be a win-win.

 The obvious approach is to do both (in exactly the manner of
 {-fffi, -farrows, -fwith}), namely to introduce a separate flag
 for each extension, but (temporarily) retain -fglasgow-exts as
 a catch-all for the complete set.  Eventually, -fglasgow-exts
 could disappear.
 
 With this suggestion, I would certainly be in favour of separate
 flags for existing extensions.
 
 Regards,
 Malcolm
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell
-- 
--
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume


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


Re: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-10 Thread Andy Moran
On Wednesday 10 September 2003 07:22 am, Hal Daume III wrote:
 I agree with Malcolm, with the possible addition of:

   keep -fglasgow-exts as it is (or, even, perhaps continue making it the
 add all extensions keyword).  also have -fffi, -farrows, -fth, etc.
 but also have, -fnoth and -fnoffi.  that way, if a lot of us have code
 that uses all the extensions other than TH and have lots of code that
 looks like (foo$bar), we can just to -fglasgow-exts -fnoth.

 seems to be a win-win.

I agree; I want a catch-all flag, but I also want to flexibility to be able 
to pick and choose.  Both -ffeature and -fnofeature is the way to go 
IMHO.

A

-- 
Andy Moran Ph. (503) 626 6616, x113
Galois Connections Inc. Fax. (503) 350 0833
12725 SW Millikan Way, Suite #290 http://www.galois.com
Beaverton, OR 97005[EMAIL PROTECTED]

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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-10 Thread Adrian Hey
On Wednesday 10 September 2003 10:51, Ketil Z. Malde wrote:
 And now, let's just screw any backwards compatibility, and re-engineer
 the records system¹.

 I don't need any of this, and it makes my life harder.  Are you guys
 going to keep at it, until I regret ever using Haskell?

I can't speak for any Haskell implementors or whether or not they intend
to keep going at it. But maybe there are people who will regret ever
using Haskell if nothing is done about the current records/modules
situation (me for one). I don't mind waiting a while, if it's still
unclear what should be done or can reasonably done given current
state of the art re. the necessary type theory. But my understanding
of the original summary was that I might as well give up hope of
ever seeing anything like this in Haskell, for fear of upsetting
the status quo. I don't like that idea much.

I think if you want to use a language which is close to state of the art
you have to accept some change. Better this than see it permanently
crippled by backwards compatibility constraints. That said, I don't
see why any backwards compatibility problems can't be managed with
suitable compiler switches or whatever, which seems to be what
Simon.M. is proposing for ghc.

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


Re: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-10 Thread Graham Klyne
At 13:13 10/09/03 +0100, Simon Marlow wrote:
Of course, if we change the language that is implied by -fglasgow-exts 
now, we risk breaking old code :-)  Would folk prefer existing syntax 
extensions be moved into their own flags, or left in -fglasgow-exts for 
now?  I'm thinking of:

  - implicit parameters
  - template haskell
  - FFI
  - rank-N polymorphism (forall keyword)
  - recursive 'do' (mdo keyword)
My 2p is that extensions that might be regarded as mainstream would 
usefully be included in a single easy-to-use switch like -fglasgow-exts.  I 
think the only part I use from the above list is rank-N polymorphism, and 
that is imported from useful libraries.

Where do multi-parameter classes fit in?

#g


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


Re: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-10 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 Graham Klyne [EMAIL PROTECTED] wrote:

- implicit parameters
- template haskell
- FFI
- rank-N polymorphism (forall keyword)
- recursive 'do' (mdo keyword)
...
 Where do multi-parameter classes fit in?

I think some of the type extensions such as rank-N and multi-parameter 
classes could be grouped under a single flag.

-- 
Ashley Yakeley, Seattle WA

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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-09 Thread Johannes Waldmann
On Tue, 9 Sep 2003, Adrian Hey wrote:

 I rarely use named fields in my Haskell progs with Haskell as it is ...

but you sure agree records are useful for collecting heterogenous data? 
for example, see data DynFlags here:

http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/main/CmdLineOpts.lhs

 IMHO preserving the status quo wrt records should be low priority.
 It really doesn't bother me much if new (useful) language features break
 existing code. 

but this might be an issue for others, who have to maintain legacy code.

best regards,
-- 
-- Johannes Waldmann  http://www.informatik.uni-leipzig.de/~joe/ --
-- [EMAIL PROTECTED] -- phone/fax (+49) 341 9732 204/209 --

.. ..  Viertes Leipziger Jongliertreffen, 17. - 19. Oktober 2003  .. ..
.. ..  http://www.informatik.uni-leipzig.de/~joe/juggling/vier/   .. ..

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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-09 Thread Nicolas Oury
Hello,

I may be wrong but can't we keep old records and add new ones (as  
proposed in the First Class Modules paper)
with a different syntax?

Ussual records and extensible records are both usefull, in different  
cases.

Best regards,

Nicolas Oury
Le mardi, 9 sep 2003, à 14:52 Europe/Paris, Johannes Waldmann a écrit :
On Tue, 9 Sep 2003, Adrian Hey wrote:

I rarely use named fields in my Haskell progs with Haskell as it is  
...
but you sure agree records are useful for collecting heterogenous data?
for example, see data DynFlags here:
http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/main/ 
CmdLineOpts.lhs

IMHO preserving the status quo wrt records should be low priority.
It really doesn't bother me much if new (useful) language features  
break
existing code.
but this might be an issue for others, who have to maintain legacy  
code.

best regards,
--
-- Johannes Waldmann  http://www.informatik.uni-leipzig.de/~joe/ --
-- [EMAIL PROTECTED] -- phone/fax (+49) 341 9732 204/209 --
.. ..  Viertes Leipziger Jongliertreffen, 17. - 19. Oktober 2003  .. ..
.. ..  http://www.informatik.uni-leipzig.de/~joe/juggling/vier/   .. ..
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-09 Thread Adrian Hey
On Tuesday 09 September 2003 13:52, Johannes Waldmann wrote:
 On Tue, 9 Sep 2003, Adrian Hey wrote:
  I rarely use named fields in my Haskell progs with Haskell as it is ...

 but you sure agree records are useful for collecting heterogenous data?

Yes, I would agree that even the current situation is sometimes better
than having a large number of unnamed fields (as a huge-tuple say).
But for the average product type or constructor (2..3 fields),
it just isn't worth the aggrovation IMO.

Regards
--
Adrian Hey



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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-09 Thread Iavor Diatchki
hello,

i think records are very useful, and we don't use them much in haskell, 
becuase the current record system is not very good.

Adrian Hey wrote:
IMHO preserving the status quo wrt records should be low priority.
It really doesn't bother me much if new (useful) language features break
existing code. I think this is a better option than permanently
impoverishing the language and/or forcing users to migrate their
entire code to some other less impoverished language which may
appear in the future.
i also think that having backwards compatability is not much of an 
issue.  after all, ghc has introduces a  number of not backward 
compatable changes to haskell, and i never heard any complaints.  i am 
referring to the hirarchical modules, and more recently template 
haskell, which has introduced a number of syntactic differences, and we 
had to actually go through our code and fix it to work with ghc 6.

What I don't particularly want to see is some half baked record system,
the usefulness of which has been compromised by the need to retain
backwards compatibility. I quite liked what I saw of the First Class
Modules paper. Is there some reason why we can't have (shouldn't have?) that.
(Apart from the additional workload it places on Haskell implementors :-)
there has been a lot of work on record systems, so there really is no 
excuse for having a half-baked recrod system.  the trex implementation 
in hugs tried to retain backward compatability with haskell, which 
resulted in a rather ugly syntax (this of course is just my opinion :-)

my preference would be to have something simillar to trex but with a 
nicer syntax, i.e. extensible records that do not need to be declared.

incidently i gathered that people wanted reocrds that support record 
concatenation, does anyone have any examples of what that might be used for?

bye
iavor
--
==
| Iavor S. Diatchki, Ph.D. student   |
| Department of Computer Science and Engineering |
| School of OGI at OHSU  |
| http://www.cse.ogi.edu/~diatchki   |
==
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: The Future of Haskell discussion at the Haskell Workshop

2003-09-09 Thread Gregory Morrisett
Coming from the ML world, I can say that I find the lack of
proper records a real loss.  It is extremely convenient to
write functions which take many parameters as taking a record,
for then you don't have to worry so much about the order
of arguments.  SML gets this much right, but the ad hoc
treatment of record selection in SML is a royal pain.  Haskell
has all of the machinery needed to support this nicely
so it seems a shame for it to be omitted.

I can say from experience that forcing records to be declared
(as in Ocaml) so that there is at most one record type that
a given label can come from in any given scope is a royal
pain.  You're then forced to come up with unique names for
the labels so that you don't get a conflict (much as we have
to do with datatype constructors.)  In Ocaml, you tend to get
around this by putting the record types in different modules,
but this is only marginally better namespace control.

Neither SML nor Ocaml supports polymorphic record selection
which is absolutely crucial.  I've found few needs for extension
or polymorphic update, though there are some compelling
examples, and I suspect that more will crop up if these
features are widely available.  

Finally, it seems that good record support at the core level
is a nice stepping stone to (first-class) modules.  

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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-09 Thread Tom Pledger
Hi.

Here's another opinion for the Records! Records! chorus:

  - The record and module system is one of the two big things I'd like
to see changed in Haskell.  (OT: the other is subtyping.)

  - It shouldn't happen before Haskell 2, because of backward
compatability.  (The dot operator for function composition is
widely used, but is the obvious choice for record projection.)

  - The way to get a feature into Haskell 2 begins with contributing
it as an optional extension to GHC and/or nhc98 and/or Hugs.

  - I'd like something similar to Cayenne's record system, which
combines records, modules and let-expressions.  But with these
refinements:

  * Dot notation for record opening.  Instead of Cayenne's

open rec_expr in expr

allow

(rec_expr).(expr)

which has the familiar single-field projection as a special
case

(rec_expr).field_name

  * Some sort of catenation or merge facility.  Speaking of
which...

Iavor Diatchki writes:
 :
 | incidently i gathered that people wanted reocrds that support record 
 | concatenation, does anyone have any examples of what that might be used for?

When a module imports and reexports some other modules, it is
effectively doing record catenation.  (It may add a few fields of its
own, if it exports any declarations, but that can be handled by record
extension as opposed to catenation.)

The (relational database) join operator also needs it - if you're into
doing such things in Haskell.



I've implemented a language with a record system along the lines I've
just described.  It's part of my work, but the record system isn't
commercially sensitive.  If it pans out well, I'll look into
contributing it to a Haskell implementation.  (O'Hugs may well be the
best fit.)

- Tom

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


Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-09 Thread Andrew J Bromage
G'day all.

On Tue, Sep 09, 2003 at 02:52:48PM +0200, Johannes Waldmann wrote:

 but this might be an issue for others, who have to maintain legacy code.

You know a language has made it when we're talking about legacy code.

On the other hand, you have to worry about a pure declarative language
where support for anything legacy is a priority.  Just a little bit.

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


The Future of Haskell discussion at the Haskell Workshop

2003-09-08 Thread nilsson
Dear Haskellers,

This year's Haskell Workshop, held in Uppsala as a part of PLI, traditionally
concluded with a discussion on the future of Haskell. This time an attempt
was made to structure the discussion a little bit by focusing on two specific
topics, and by having each topic being introduced by a short presentation.
The first topic was Haskell records, introduced by Simon Peyton Jones,
Microsoft Research, Cambridge, UK. The second topic was GUI libraries for
Haskell, introduced by Axel Simon, the University of Kent, UK.

While the current Haskell record system, or rather support for labeled fields,
is vastly superior to not having any record facility at all, and appealing
due to its simplicity and not incurring any run-time penalty, most people
would agree that it does leave a lot be desired. However, they would not
necessarily agree on exactly what is to be desired: the design space is quite
large, and it is not easy to evaluate how useful various record features
would be in practice, and if the cost in terms of increased language 
complexity and backwards compatibility issues is warranted.

Unsurprisingly, opinions expressed during the discussion were rather divided.
In the end, it seemed that the fact that the present system, despite its
faults, is simple and has proved to be useful convinced a majority of the
people present that if the system were to be improved, it should only be
rather modest improvements that would not break backward compatibility.
For example, one of the most annoying limitations of the present system is
that record labels have to be distinct. Maybe this restriction could
be lifted without sacrificing compatibility.

Here is how Simon Peyton Jones summarized the discussion:

The conclusion I took away was this

There are undoubted advantages to having better records, but

  (a) they all make the language more complicated

  (b) there are many possible design choices
(not only has/lacks, but also record concatenation,
length vs depth subtyping, and more I'm sure)

  (c) they almost certainly conflict with existing programs

  (d) the existing system is really not too bad

That all argues for the status quo.

I did have a conversation with Peter Thiemann afterwards.  We 
discussed a record system which is an upward compatible extension
of what we have now, though less powerful than the variants I have 
previously proposed.

  * Records are not anonymous.  
  
e.g. {x::Int, y::Bool} is not a type
  
They are declared exactly as now, so that

data T = T { x::Int, y::Bool }

declares a type T.

  * However, you can have more than one record with the same
field name.  So the field selectors are overloaded, much as
with has-predicates

x :: (t has x::a) = t - a

  * So a function like

f v = v.x + v.y

would get the inferred type

f :: (t has x::a, t has y::a, Num a) = t - a

 * Also retain Haskell's existing record construction and update
   syntax could be possible.

The GUI library discussion focused on questions such as what exactly
are the desirable properties of such a library. For example, to what
extent is it necessary that applications are able to adopt the look-and-feel
of the platform on which they happen to be running. Related to this was
the question of whether to focus efforts on a Common GUI API (CGA) that
would allow applications to adapt to specific platforms, or whether it
would be sufficient to go for something based on an existing cross-platform
API, such as wxWindows, even if that meant violating certain look-and-feel
aspects on certain platforms, and inability to access platform-specific
functionality.

Axel Simon has promised to e-mail a more complete record of the GUI-part of
the discussion shortly.

All the best,

/Henrik

-- 
Henrik Nilsson
Yale University
Department of Computer Science
[EMAIL PROTECTED]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


The future of Haskell discussion at the Haskell workshop, Oct 3, 2002

2002-10-11 Thread Johan Jeuring
This is a brief account of the discussion on the future of
Haskell at the Haskell workshop, Oct 3, 2002, in Pittsburgh.

After Simon Peyton Jones discussed the copy-right issue of
publishing the report, we had a brief discussion about the
future of Haskell.

The first point raised was that the addition of unsafe
extensions to Haskell, like unsafePerformIO and unsafeCoerce,
goes against the original design requirements for Haskell.
The presence of unsafe extensions makes quick but dirty
solutions possible, for example for problems that need
concurrency. This hampers the development of semantically
clean theories, and makes building tools that reason
about Haskell much harder. Reactions on this point differed:
some people heartily agreed, some other people thought
unsafePerformIO was often just a cosmetic thing, and that
whenever a theory/abstraction/method for an application for
which unsafe extensions are used now is in sight, people
will try to develop it.

Another suggestion was to develop methods for separation of
threads so that you can reason locally about threads.

-- Johan Jeuring

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